1
0
mirror of https://github.com/msberends/AMR.git synced 2025-10-25 19:56:20 +02:00

(v0.7.1.9005) new rsi calculations, atc class removal

This commit is contained in:
2019-07-01 14:03:15 +02:00
parent 65c6702b21
commit 156d550895
78 changed files with 1169 additions and 911 deletions

View File

@@ -1,6 +1,6 @@
Package: AMR Package: AMR
Version: 0.7.1.9004 Version: 0.7.1.9005
Date: 2019-06-27 Date: 2019-07-01
Title: Antimicrobial Resistance Analysis Title: Antimicrobial Resistance Analysis
Authors@R: c( Authors@R: c(
person( person(

View File

@@ -224,7 +224,6 @@ importFrom(crayon,black)
importFrom(crayon,blue) importFrom(crayon,blue)
importFrom(crayon,bold) importFrom(crayon,bold)
importFrom(crayon,green) importFrom(crayon,green)
importFrom(crayon,has_color)
importFrom(crayon,italic) importFrom(crayon,italic)
importFrom(crayon,magenta) importFrom(crayon,magenta)
importFrom(crayon,red) importFrom(crayon,red)

35
NEWS.md
View File

@@ -1,11 +1,42 @@
# AMR 0.7.1.9004 # AMR 0.7.1.9005
### New
* Additional way to calculate co-resistance, i.e. when using multiple antibiotics as input for `portion_*` functions or `count_*` functions. This can be used to determine the empiric susceptibily of a combination therapy. A new parameter `only_all_tested` replaces the old `also_single_tested` and can be used to select one of the two methods to count isolates and calculate portions. The difference can be seen in this example table (which is also on the `portion` and `count` help pages), where the %SI is being determined:
```r
# -------------------------------------------------------------------------
# only_all_tested = FALSE only_all_tested = TRUE
# Antibiotic Antibiotic ----------------------- -----------------------
# A B include as include as include as include as
# numerator denominator numerator denominator
# ---------- ---------- ---------- ----------- ---------- -----------
# S S X X X X
# I S X X X X
# R S X X X X
# not tested S X X - -
# S I X X X X
# I I X X X X
# R I X X X X
# not tested I X X - -
# S R X X X X
# I R X X X X
# R R - X - X
# not tested R - - - -
# S not tested X X - -
# I not tested X X - -
# R not tested - - - -
# not tested not tested - - - -
# -------------------------------------------------------------------------
```
Since this is a major change, usage of the old `also_single_tested` will throw an informative error that it has been replaced by `only_all_tested`.
### Changed ### Changed
* Removed class `atc` - using `as.atc()` is now deprecated in favour of `ab_atc()` and this will return a character, not the `atc` class anymore * Removed class `atc` - using `as.atc()` is now deprecated in favour of `ab_atc()` and this will return a character, not the `atc` class anymore
* Removed deprecated functions `abname()`, `ab_official()`, `atc_name()`, `atc_official()`, `atc_property()`, `atc_tradenames()`, `atc_trivial_nl()` * Removed deprecated functions `abname()`, `ab_official()`, `atc_name()`, `atc_official()`, `atc_property()`, `atc_tradenames()`, `atc_trivial_nl()`
* Fix and speed improvement for `mo_shortname()` * Fix and speed improvement for `mo_shortname()`
* Fix for `as.mo()` where misspelled input would not be understood * Fix for `as.mo()` where misspelled input would not be understood
* Fix for `also_single_tested` parameter in `count_*` functions * Fix for using `mo_*` functions where the coercion uncertainties and failures would not be available through `mo_uncertainties()` and `mo_failures()` anymore
# AMR 0.7.1 # AMR 0.7.1

View File

@@ -34,6 +34,7 @@
#' The function \code{count_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and counts the amounts of S, I and R. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}. #' The function \code{count_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and counts the amounts of S, I and R. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}.
#' #'
#' The function \code{rsi_df} works exactly like \code{count_df}, but adds the percentage of S, I and R. #' The function \code{rsi_df} works exactly like \code{count_df}, but adds the percentage of S, I and R.
#' @inheritSection portion Combination therapy
#' @source Wickham H. \strong{Tidy Data.} The Journal of Statistical Software, vol. 59, 2014. \url{http://vita.had.co.nz/papers/tidy-data.html} #' @source Wickham H. \strong{Tidy Data.} The Journal of Statistical Software, vol. 59, 2014. \url{http://vita.had.co.nz/papers/tidy-data.html}
#' @seealso \code{\link{portion}_*} to calculate microbial resistance and susceptibility. #' @seealso \code{\link{portion}_*} to calculate microbial resistance and susceptibility.
#' @keywords resistance susceptibility rsi antibiotics isolate isolates #' @keywords resistance susceptibility rsi antibiotics isolate isolates
@@ -61,8 +62,8 @@
#' # Since n_rsi counts available isolates, you can #' # Since n_rsi counts available isolates, you can
#' # calculate back to count e.g. non-susceptible isolates. #' # calculate back to count e.g. non-susceptible isolates.
#' # This results in the same: #' # This results in the same:
#' count_IR(septic_patients$AMX) #' count_SI(septic_patients$AMX)
#' portion_IR(septic_patients$AMX) * n_rsi(septic_patients$AMX) #' portion_SI(septic_patients$AMX) * n_rsi(septic_patients$AMX)
#' #'
#' library(dplyr) #' library(dplyr)
#' septic_patients %>% #' septic_patients %>%
@@ -76,17 +77,17 @@
#' #'
#' # 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.
#' # Please mind that `portion_S` calculates percentages right away instead. #' # Please mind that `portion_SI` calculates percentages right away instead.
#' count_S(septic_patients$AMC) # S = 1342 (71.4%) #' count_SI(septic_patients$AMC) # 1433
#' count_all(septic_patients$AMC) # n = 1879 #' count_all(septic_patients$AMC) # 1879
#' #'
#' count_S(septic_patients$GEN) # S = 1372 (74.0%) #' count_SI(septic_patients$GEN) # 1399
#' count_all(septic_patients$GEN) # n = 1855 #' count_all(septic_patients$GEN) # 1855
#' #'
#' with(septic_patients, #' with(septic_patients,
#' count_S(AMC, GEN)) # S = 1660 (92.3%) #' count_SI(AMC, GEN)) # 1764
#' with(septic_patients, # n = 1798 #' with(septic_patients,
#' n_rsi(AMC, GEN)) #' n_rsi(AMC, GEN)) # 1936
#' #'
#' # Get portions S/I/R immediately of all rsi columns #' # Get portions S/I/R immediately of all rsi columns
#' septic_patients %>% #' septic_patients %>%
@@ -99,71 +100,56 @@
#' group_by(hospital_id) %>% #' group_by(hospital_id) %>%
#' count_df(translate = FALSE) #' count_df(translate = FALSE)
#' #'
count_R <- function(..., also_single_tested = FALSE) { count_R <- function(..., only_all_tested = FALSE) {
rsi_calc(..., rsi_calc(...,
type = "R", ab_result = "R",
include_I = FALSE, only_all_tested = only_all_tested,
minimum = 0,
as_percent = FALSE,
also_single_tested = also_single_tested,
only_count = TRUE) only_count = TRUE)
} }
#' @rdname count #' @rdname count
#' @export #' @export
count_IR <- function(..., also_single_tested = FALSE) { count_IR <- function(..., only_all_tested = FALSE) {
rsi_calc(..., rsi_calc(...,
type = "R", ab_result = c("I", "R"),
include_I = TRUE, only_all_tested = only_all_tested,
minimum = 0,
as_percent = FALSE,
also_single_tested = also_single_tested,
only_count = TRUE) only_count = TRUE)
} }
#' @rdname count #' @rdname count
#' @export #' @export
count_I <- function(..., also_single_tested = FALSE) { count_I <- function(..., only_all_tested = FALSE) {
rsi_calc(..., rsi_calc(...,
type = "I", ab_result = "I",
include_I = FALSE, only_all_tested = only_all_tested,
minimum = 0,
as_percent = FALSE,
also_single_tested = also_single_tested,
only_count = TRUE) only_count = TRUE)
} }
#' @rdname count #' @rdname count
#' @export #' @export
count_SI <- function(..., also_single_tested = FALSE) { count_SI <- function(..., only_all_tested = FALSE) {
rsi_calc(..., rsi_calc(...,
type = "S", ab_result = c("S", "I"),
include_I = TRUE, only_all_tested = only_all_tested,
minimum = 0,
as_percent = FALSE,
also_single_tested = also_single_tested,
only_count = TRUE) only_count = TRUE)
} }
#' @rdname count #' @rdname count
#' @export #' @export
count_S <- function(..., also_single_tested = FALSE) { count_S <- function(..., only_all_tested = FALSE) {
rsi_calc(..., rsi_calc(...,
type = "S", ab_result = "S",
include_I = FALSE, only_all_tested = only_all_tested,
minimum = 0,
as_percent = FALSE,
also_single_tested = also_single_tested,
only_count = TRUE) only_count = TRUE)
} }
#' @rdname count #' @rdname count
#' @export #' @export
count_all <- function(..., also_single_tested = FALSE) { count_all <- function(..., only_all_tested = FALSE) {
res_SI <- count_SI(..., also_single_tested = also_single_tested) rsi_calc(...,
# only print warnings once, if needed ab_result = c("S", "I", "R"),
res_R <- suppressWarnings(count_R(..., also_single_tested = also_single_tested)) only_all_tested = only_all_tested,
res_SI + res_R only_count = TRUE)
} }
#' @rdname count #' @rdname count

110
R/mo.R
View File

@@ -87,12 +87,9 @@
#' \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 equal 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, previously accepted (but now invalid) taxonomic names and misspelled input}
#' \item{(uncertainty level 1): It tries to look for previously accepted (but now invalid) taxonomic names} #' \item{(uncertainty level 2): It removed parts between brackets, strips off words from the end one by one and re-evaluates the input with all previous rules}
#' \item{(uncertainty level 2): It strips off values between brackets and the brackets itself, and re-evaluates the input with all previous rules} #' \item{(uncertainty level 3): It strips off words from the start one by one and tries any part of the name}
#' \item{(uncertainty level 2): It strips off words from the end one by one and re-evaluates the input with all previous rules}
#' \item{(uncertainty level 3): It strips off words from the start one by one and re-evaluates the input with all previous rules}
#' \item{(uncertainty level 3): It tries any part of the name}
#' } #' }
#' #'
#' You can also use e.g. \code{as.mo(..., allow_uncertain = 1)} to only allow up to level 1 uncertainty. #' You can also use e.g. \code{as.mo(..., allow_uncertain = 1)} to only allow up to level 1 uncertainty.
@@ -281,7 +278,7 @@ is.mo <- function(x) {
#' @importFrom dplyr %>% pull left_join n_distinct progress_estimated filter distinct #' @importFrom dplyr %>% pull left_join n_distinct progress_estimated filter distinct
#' @importFrom data.table data.table as.data.table setkey #' @importFrom data.table data.table as.data.table setkey
#' @importFrom crayon magenta red blue silver italic has_color #' @importFrom crayon magenta red blue silver italic
# param property a column name of AMR::microorganisms # param property a column name of AMR::microorganisms
# param initial_search logical - is FALSE when coming from uncertain tries, which uses exec_as.mo internally too # param initial_search logical - is FALSE when coming from uncertain tries, which uses exec_as.mo internally too
# param force_mo_history logical - whether found result must be saved with set_mo_history (default FALSE on non-interactive sessions) # param force_mo_history logical - whether found result must be saved with set_mo_history (default FALSE on non-interactive sessions)
@@ -486,7 +483,7 @@ exec_as.mo <- function(x,
# remove genus as first word # remove genus as first word
x <- gsub("^Genus ", "", x) x <- gsub("^Genus ", "", x)
# allow characters that resemble others # allow characters that resemble others
if (uncertainty_level >= 2) { if (initial_search == FALSE) {
x <- tolower(x) x <- tolower(x)
x <- gsub("[iy]+", "[iy]+", x) x <- gsub("[iy]+", "[iy]+", x)
x <- gsub("(c|k|q|qu|s|z|x|ks)+", "(c|k|q|qu|s|z|x|ks)+", x) x <- gsub("(c|k|q|qu|s|z|x|ks)+", "(c|k|q|qu|s|z|x|ks)+", x)
@@ -768,31 +765,24 @@ exec_as.mo <- function(x,
} }
next next
} }
if (grepl("[sS]almonella [A-Z][a-z]+ ?.*", x_backup_without_spp[i], ignore.case = FALSE)) { if (x_backup_without_spp[i] %like% "salmonella [a-z]+ ?.*") {
if (x_backup_without_spp[i] %like% "Salmonella group") { if (x_backup_without_spp[i] %like% "Salmonella group") {
# 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), 0, 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"), } else if (grepl("[sS]almonella [A-Z][a-z]+ ?.*", x_backup_without_spp[i], ignore.case = FALSE)) {
magenta(paste0("NOTE: ",
italic("Salmonella"), " ", trimws(gsub("Salmonella", "", x_backup_without_spp[i])),
" was considered ",
italic("Salmonella species"),
" (B_SLMNL)"))))
} else {
# 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), 0, 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"), uncertainties <- rbind(uncertainties,
magenta(paste0("NOTE: ", data.frame(uncertainty = 1,
italic("Salmonella"), " ", trimws(gsub("Salmonella", "", x_backup_without_spp[i])), input = x_backup_without_spp[i],
" was considered a subspecies of ", fullname = microorganismsDT[mo == "B_SLMNL_ENT", fullname][[1]],
italic("Salmonella enterica"), mo = "B_SLMNL_ENT"))
" (B_SLMNL_ENT)"))))
} }
next next
} }
@@ -1041,9 +1031,27 @@ exec_as.mo <- function(x,
} }
return(x) return(x)
} }
# (2) Try with misspelled input ----
# just rerun with initial_search = FALSE will used the extensive regex part above
found <- suppressMessages(suppressWarnings(exec_as.mo(a.x_backup, initial_search = FALSE, allow_uncertain = FALSE)))
if (!empty_result(found)) {
found_result <- found
found <- microorganismsDT[mo == found, ..property][[1]]
uncertainties <<- rbind(uncertainties,
data.frame(uncertainty = 1,
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), 1, force = force_mo_history)
}
return(found[1L])
}
} }
if (uncertainty_level >= 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)) {
@@ -1286,10 +1294,11 @@ exec_as.mo <- function(x,
post_Becker <- c("argensis", "caeli", "cornubiensis", "edaphicus") post_Becker <- c("argensis", "caeli", "cornubiensis", "edaphicus")
if (any(x %in% MOs_staph[species %in% post_Becker, ..property][[1]])) { if (any(x %in% MOs_staph[species %in% post_Becker, ..property][[1]])) {
warning("Becker ", italic("et al."), " (2014, 2019) does not contain species named after their publication: ", warning("Becker ", italic("et al."), " (2014, 2019) does not contain these species named after their publication: ",
italic(paste("S.", italic(paste("S.",
sort(mo_species(unique(x[x %in% MOs_staph[species %in% post_Becker, ..property][[1]]]))), sort(mo_species(unique(x[x %in% MOs_staph[species %in% post_Becker, ..property][[1]]]))),
collapse = ", ")), collapse = ", ")),
".",
call. = FALSE, call. = FALSE,
immediate. = TRUE) immediate. = TRUE)
} }
@@ -1352,15 +1361,7 @@ exec_as.mo <- function(x,
} }
if (length(mo_renamed()) > 0) { if (length(mo_renamed()) > 0) {
if (has_color()) { print(mo_renamed())
notes <- getOption("mo_renamed")
} else {
notes <- mo_renamed()
}
notes <- sort(notes)
for (i in 1:length(notes)) {
base::message(blue(paste("NOTE:", notes[i])))
}
} }
x x
@@ -1387,9 +1388,14 @@ was_renamed <- function(name_old, name_new, ref_old = "", ref_new = "", mo = "")
} else { } else {
mo <- "" mo <- ""
} }
msg <- paste0(italic(name_old), ref_old, " was renamed ", italic(name_new), ref_new, mo) old_values <- paste0(italic(name_old), ref_old)
msg <- gsub("et al.", italic("et al."), msg) old_values <- gsub("et al.", italic("et al."), old_values)
options(mo_renamed = c(getOption("mo_renamed"), sort(msg))) new_values <- paste0(italic(name_new), ref_new, mo)
new_values <- gsub("et al.", italic("et al."), new_values)
names(new_values) <- old_values
total <- c(getOption("mo_renamed"), new_values)
options(mo_renamed = total[order(names(total))])
} }
#' @exportMethod print.mo #' @exportMethod print.mo
@@ -1451,6 +1457,9 @@ mo_failures <- function() {
#' @importFrom crayon italic #' @importFrom crayon italic
#' @export #' @export
mo_uncertainties <- function() { mo_uncertainties <- function() {
if (is.null(getOption("mo_uncertainties"))) {
return(NULL)
}
structure(.Data = as.data.frame(getOption("mo_uncertainties"), stringsAsFactors = FALSE), structure(.Data = as.data.frame(getOption("mo_uncertainties"), stringsAsFactors = FALSE),
class = c("mo_uncertainties", "data.frame")) class = c("mo_uncertainties", "data.frame"))
} }
@@ -1463,8 +1472,8 @@ print.mo_uncertainties <- function(x, ...) {
if (NROW(x) == 0) { if (NROW(x) == 0) {
return(NULL) return(NULL)
} }
cat(paste0(bold(nrow(x), "unique result(s) guessed with uncertainty:"), cat(paste0(bold(nr2char(nrow(x)), paste0("unique result", ifelse(nrow(x) > 1, "s", ""), " guessed with uncertainty:")),
"\n(1 = ", green("renamed"), "\n(1 = ", green("renamed/misspelled"),
", 2 = ", yellow("uncertain"), ", 2 = ", yellow("uncertain"),
", 3 = ", red("very uncertain"), ")\n")) ", 3 = ", red("very uncertain"), ")\n"))
@@ -1489,10 +1498,18 @@ print.mo_uncertainties <- function(x, ...) {
} }
#' @rdname as.mo #' @rdname as.mo
#' @importFrom crayon strip_style
#' @export #' @export
mo_renamed <- function() { mo_renamed <- function() {
structure(.Data = strip_style(gsub("was renamed", "->", getOption("mo_renamed"), fixed = TRUE)), items <- getOption("mo_renamed")
class = c("mo_renamed", "character")) if (is.null(items)) {
return(NULL)
}
items <- strip_style(items)
names(items) <- strip_style(names(items))
structure(.Data = items,
class = c("mo_renamed", "character"))
} }
#' @exportMethod print.mo_renamed #' @exportMethod print.mo_renamed
@@ -1500,7 +1517,8 @@ mo_renamed <- function() {
#' @export #' @export
#' @noRd #' @noRd
print.mo_renamed <- function(x, ...) { print.mo_renamed <- function(x, ...) {
cat(blue(paste(getOption("mo_renamed"), collapse = "\n"))) items <- getOption("mo_renamed")
base::message(blue(paste("NOTE:", names(items), "was renamed", items, collapse = "\n"), collapse = "\n"))
} }
nr2char <- function(x) { nr2char <- function(x) {
@@ -1540,3 +1558,15 @@ translate_allow_uncertain <- function(allow_uncertain) {
} }
allow_uncertain allow_uncertain
} }
get_mo_failures_uncertainties_renamed <- function() {
list(failures = getOption("mo_failures"),
uncertainties = getOption("mo_uncertainties"),
renamed = getOption("mo_renamed"))
}
load_mo_failures_uncertainties_renamed <- function(metadata) {
options("mo_failures" = metadata$failures)
options("mo_uncertainties" = metadata$uncertainties)
options("mo_renamed" = metadata$renamed)
}

View File

@@ -148,7 +148,9 @@ mo_fullname <- mo_name
#' @importFrom dplyr %>% mutate pull #' @importFrom dplyr %>% mutate pull
#' @export #' @export
mo_shortname <- function(x, language = get_locale(), ...) { mo_shortname <- function(x, language = get_locale(), ...) {
x.mo <- as.mo(x, ...) x.mo <- AMR::as.mo(x, ...)
metadata <- get_mo_failures_uncertainties_renamed()
# get first char of genus and complete species in English # get first char of genus and complete species in English
shortnames <- paste0(substr(mo_genus(x.mo, language = NULL), 1, 1), ". ", mo_species(x.mo, language = NULL)) shortnames <- paste0(substr(mo_genus(x.mo, language = NULL), 1, 1), ". ", mo_species(x.mo, language = NULL))
@@ -158,6 +160,7 @@ mo_shortname <- function(x, language = get_locale(), ...) {
# exceptions for Streptococci # exceptions for Streptococci
shortnames[shortnames %like% "S. group [ABCDFGHK]"] <- paste0("G", gsub("S. group ([ABCDFGHK])", "\\1", shortnames[shortnames %like% "S. group [ABCDFGHK]"]), "S") shortnames[shortnames %like% "S. group [ABCDFGHK]"] <- paste0("G", gsub("S. group ([ABCDFGHK])", "\\1", shortnames[shortnames %like% "S. group [ABCDFGHK]"]), "S")
load_mo_failures_uncertainties_renamed(metadata)
translate_AMR(shortnames, language = language, only_unknown = FALSE) translate_AMR(shortnames, language = language, only_unknown = FALSE)
} }
@@ -218,8 +221,10 @@ mo_type <- function(x, language = get_locale(), ...) {
#' @rdname mo_property #' @rdname mo_property
#' @export #' @export
mo_gramstain <- function(x, language = get_locale(), ...) { mo_gramstain <- function(x, language = get_locale(), ...) {
x.mo <- as.mo(x, ...) x.mo <- AMR::as.mo(x, ...)
x.phylum <- mo_phylum(x.mo, language = NULL) metadata <- get_mo_failures_uncertainties_renamed()
x.phylum <- mo_phylum(x.mo)
# DETERMINE GRAM STAIN FOR BACTERIA # DETERMINE GRAM STAIN FOR BACTERIA
# Source: https://itis.gov/servlet/SingleRpt/SingleRpt?search_topic=TSN&search_value=956097 # Source: https://itis.gov/servlet/SingleRpt/SingleRpt?search_topic=TSN&search_value=956097
# It says this: # It says this:
@@ -232,13 +237,15 @@ mo_gramstain <- function(x, language = get_locale(), ...) {
# Phylum Tenericutes (Murray, 1984) # Phylum Tenericutes (Murray, 1984)
x <- NA_character_ x <- NA_character_
# make all bacteria Gram negative # make all bacteria Gram negative
x[mo_kingdom(x.mo, language = NULL) == "Bacteria"] <- "Gram-negative" x[mo_kingdom(x.mo) == "Bacteria"] <- "Gram-negative"
# overwrite these phyla with Gram positive # overwrite these phyla with Gram positive
x[x.phylum %in% c("Actinobacteria", x[x.phylum %in% c("Actinobacteria",
"Chloroflexi", "Chloroflexi",
"Firmicutes", "Firmicutes",
"Tenericutes") "Tenericutes")
| x.mo == "B_GRAMP"] <- "Gram-positive" | x.mo == "B_GRAMP"] <- "Gram-positive"
load_mo_failures_uncertainties_renamed(metadata)
translate_AMR(x, language = language, only_unknown = FALSE) translate_AMR(x, language = language, only_unknown = FALSE)
} }
@@ -276,7 +283,9 @@ mo_rank <- function(x, ...) {
#' @export #' @export
mo_taxonomy <- function(x, language = get_locale(), ...) { mo_taxonomy <- function(x, language = get_locale(), ...) {
x <- AMR::as.mo(x, ...) x <- AMR::as.mo(x, ...)
base::list(kingdom = AMR::mo_kingdom(x, language = language), metadata <- get_mo_failures_uncertainties_renamed()
result <- base::list(kingdom = AMR::mo_kingdom(x, language = language),
phylum = AMR::mo_phylum(x, language = language), phylum = AMR::mo_phylum(x, language = language),
class = AMR::mo_class(x, language = language), class = AMR::mo_class(x, language = language),
order = AMR::mo_order(x, language = language), order = AMR::mo_order(x, language = language),
@@ -284,12 +293,17 @@ mo_taxonomy <- function(x, language = get_locale(), ...) {
genus = AMR::mo_genus(x, language = language), genus = AMR::mo_genus(x, language = language),
species = AMR::mo_species(x, language = language), species = AMR::mo_species(x, language = language),
subspecies = AMR::mo_subspecies(x, language = language)) subspecies = AMR::mo_subspecies(x, language = language))
load_mo_failures_uncertainties_renamed(metadata)
result
} }
#' @rdname mo_property #' @rdname mo_property
#' @export #' @export
mo_synonyms <- function(x, ...) { mo_synonyms <- function(x, ...) {
x <- as.mo(x, ...) x <- AMR::as.mo(x, ...)
metadata <- get_mo_failures_uncertainties_renamed()
IDs <- AMR::mo_property(x = x, property = "col_id", language = NULL) IDs <- AMR::mo_property(x = x, property = "col_id", language = NULL)
syns <- lapply(IDs, function(col_id) { syns <- lapply(IDs, function(col_id) {
res <- sort(AMR::microorganisms.old[which(AMR::microorganisms.old$col_id_new == col_id), "fullname"]) res <- sort(AMR::microorganisms.old[which(AMR::microorganisms.old$col_id_new == col_id), "fullname"])
@@ -301,16 +315,21 @@ mo_synonyms <- function(x, ...) {
}) })
if (length(syns) > 1) { if (length(syns) > 1) {
names(syns) <- mo_fullname(x) names(syns) <- mo_fullname(x)
syns result <- syns
} else { } else {
unlist(syns) result <- unlist(syns)
} }
load_mo_failures_uncertainties_renamed(metadata)
result
} }
#' @rdname mo_property #' @rdname mo_property
#' @export #' @export
mo_info <- function(x, language = get_locale(), ...) { mo_info <- function(x, language = get_locale(), ...) {
x <- AMR::as.mo(x, ...) x <- AMR::as.mo(x, ...)
metadata <- get_mo_failures_uncertainties_renamed()
info <- lapply(x, function(y) info <- lapply(x, function(y)
c(mo_taxonomy(y, language = language), c(mo_taxonomy(y, language = language),
list(synonyms = mo_synonyms(y), list(synonyms = mo_synonyms(y),
@@ -318,10 +337,13 @@ mo_info <- function(x, language = get_locale(), ...) {
ref = mo_ref(y)))) ref = mo_ref(y))))
if (length(info) > 1) { if (length(info) > 1) {
names(info) <- mo_fullname(x) names(info) <- mo_fullname(x)
info result <- info
} else { } else {
info[[1L]] result <- info[[1L]]
} }
load_mo_failures_uncertainties_renamed(metadata)
result
} }
#' @rdname mo_property #' @rdname mo_property
@@ -330,6 +352,8 @@ mo_info <- function(x, language = get_locale(), ...) {
#' @export #' @export
mo_url <- function(x, open = FALSE, ...) { mo_url <- function(x, open = FALSE, ...) {
mo <- AMR::as.mo(x = x, ... = ...) mo <- AMR::as.mo(x = x, ... = ...)
metadata <- get_mo_failures_uncertainties_renamed()
df <- data.frame(mo, stringsAsFactors = FALSE) %>% df <- data.frame(mo, stringsAsFactors = FALSE) %>%
left_join(select(AMR::microorganisms, mo, source, species_id), by = "mo") %>% left_join(select(AMR::microorganisms, mo, source, species_id), by = "mo") %>%
mutate(url = case_when(source == "CoL" ~ mutate(url = case_when(source == "CoL" ~
@@ -347,6 +371,8 @@ mo_url <- function(x, open = FALSE, ...) {
} }
browseURL(u[1L]) browseURL(u[1L])
} }
load_mo_failures_uncertainties_renamed(metadata)
u u
} }

View File

@@ -27,36 +27,61 @@
#' @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 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 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 for 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 could lead to selection bias.} #' @param only_all_tested (for combination therapies, i.e. using more than one variable for \code{...}) a logical to indicate that isolates must be tested for all antibiotics, see section \emph{Combination therapy} below
#' @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}})
#' @param translate_ab a column name of the \code{\link{antibiotics}} data set to translate the antibiotic abbreviations to, using \code{\link{ab_property}} #' @param translate_ab a column name of the \code{\link{antibiotics}} data set to translate the antibiotic abbreviations to, using \code{\link{ab_property}}
#' @inheritParams ab_property #' @inheritParams ab_property
#' @param combine_SI a logical to indicate whether all values of S and I must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter \code{combine_IR}, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see section 'Interpretation of S, I and R' below. Default is \code{TRUE}. #' @param combine_SI a logical to indicate whether all values of S and I must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter \code{combine_IR}, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see section 'Interpretation of S, I and R' below. Default is \code{TRUE}.
#' @param combine_IR a logical to indicate whether all values of I and R must be merged into one, so the output only consists of S vs. I+R (susceptible vs. non-susceptible). This is outdated, see parameter \code{combine_SI}. #' @param combine_IR a logical to indicate whether all values of I and R must be merged into one, so the output only consists of S vs. I+R (susceptible vs. non-susceptible). This is outdated, see parameter \code{combine_SI}.
#' @inheritSection as.rsi Interpretation of S, I and R #' @inheritSection as.rsi Interpretation of S, I and R
#' @details \strong{Remember that you should filter your table to let it contain only first isolates!} Use \code{\link{first_isolate}} to determine them in your data set. #' @details \strong{Remember that you should filter your table to let it contain only first isolates!} This is needed to exclude duplicates and to reduce selection bias. Use \code{\link{first_isolate}} to determine them in your data set.
#' #'
#' These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. \emph{Low counts can infuence the outcome - these \code{portion} functions may camouflage this, since they only return the portion albeit being dependent on the \code{minimum} parameter.} #' These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. \emph{Low counts can infuence the outcome - these \code{portion} functions may camouflage this, since they only return the portion albeit being dependent on the \code{minimum} parameter.}
#' #'
#' The function \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each group and each variable with class \code{"rsi"}. #' The function \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each group and each variable with class \code{"rsi"}.
#' #'
#' The function \code{rsi_df} works exactly like \code{portion_df}, but adds the number of isolates. #' The function \code{rsi_df} works exactly like \code{portion_df}, but adds the number of isolates.
#' \if{html}{ #' @section Combination therapy:
# (created with https://www.latex4technics.com/) #' When using more than one variable for \code{...} (= combination therapy)), use \code{only_all_tested} to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antibiotics, Antibiotic A and Antibiotic B, about how \code{portion_SI} works to calculate the \%SI:
#' \cr\cr #'
#' To calculate the probability (\emph{p}) of susceptibility of one antibiotic, we use this formula: #' \preformatted{
#' \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 #' only_all_tested = FALSE only_all_tested = TRUE
#' \cr #' Antibiotic Antibiotic ----------------------- -----------------------
#' For two antibiotics: #' A B include as include as include as include as
#' \out{<div style="text-align: center;">}\figure{combi_therapy_2.png}\out{</div>} #' numerator denominator numerator denominator
#' \cr #' ---------- ---------- ---------- ----------- ---------- -----------
#' For three antibiotics: #' S S X X X X
#' \out{<div style="text-align: center;">}\figure{combi_therapy_2.png}\out{</div>} #' I S X X X X
#' \cr #' R S X X X X
#' And so on. #' not tested S X X - -
#' S I X X X X
#' I I X X X X
#' R I X X X X
#' not tested I X X - -
#' S R X X X X
#' I R X X X X
#' R R - X - X
#' not tested R - - - -
#' S not tested X X - -
#' I not tested X X - -
#' R not tested - - - -
#' not tested not tested - - - -
#' -------------------------------------------------------------------------
#' } #' }
#' #'
#' Please note that for \code{only_all_tested = TRUE} applies that:
#' \preformatted{
#' count_S() + count_I() + count_R() == count_all()
#' portion_S() + portion_I() + portion_R() == 1
#' }
#' and that for \code{only_all_tested = FALSE} applies that:
#' \preformatted{
#' count_S() + count_I() + count_R() >= count_all()
#' portion_S() + portion_I() + portion_R() >= 1
#' }
#'
#' Using \code{only_all_tested} has no impact when only using one antibiotic as input.
#' @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}
@@ -89,7 +114,7 @@
#' #'
#' septic_patients %>% #' septic_patients %>%
#' group_by(hospital_id) %>% #' group_by(hospital_id) %>%
#' summarise(p = portion_S(CIP), #' summarise(p = portion_SI(CIP),
#' n = n_rsi(CIP)) # n_rsi works like n_distinct in dplyr #' n = n_rsi(CIP)) # n_rsi works like n_distinct in dplyr
#' #'
#' septic_patients %>% #' septic_patients %>%
@@ -103,32 +128,38 @@
#' #'
#' # 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:
#' septic_patients %>% portion_S(AMC) # S = 71.4% #' septic_patients %>% portion_SI(AMC) # %SI = 76.3%
#' septic_patients %>% count_all(AMC) # n = 1879 #' septic_patients %>% count_all(AMC) # n = 1879
#' #'
#' septic_patients %>% portion_S(GEN) # S = 74.0% #' septic_patients %>% portion_SI(GEN) # %SI = 75.4%
#' septic_patients %>% count_all(GEN) # n = 1855 #' septic_patients %>% count_all(GEN) # n = 1855
#' #'
#' septic_patients %>% portion_S(AMC, GEN) # S = 92.3% #' septic_patients %>% portion_SI(AMC, GEN) # %SI = 94.1%
#' septic_patients %>% count_all(AMC, GEN) # n = 1798 #' septic_patients %>% count_all(AMC, GEN) # n = 1939
#' #'
#' # Using `also_single_tested` can be useful ... #'
#' # See Details on how `only_all_tested` works. Example:
#' septic_patients %>% #' septic_patients %>%
#' portion_S(AMC, GEN, #' summarise(numerator = count_SI(AMC, GEN),
#' also_single_tested = TRUE) # S = 92.6% #' denominator = count_all(AMC, GEN),
#' # ... but can also lead to selection bias - the data only has 2,000 rows: #' portion = portion_SI(AMC, GEN))
#' # numerator denominator portion
#' # 1764 1936 0.9408
#' septic_patients %>% #' septic_patients %>%
#' count_all(AMC, GEN, #' summarise(numerator = count_SI(AMC, GEN, only_all_tested = TRUE),
#' also_single_tested = TRUE) # n = 2555 #' denominator = count_all(AMC, GEN, only_all_tested = TRUE),
#' portion = portion_SI(AMC, GEN, only_all_tested = TRUE))
#' # numerator denominator portion
#' # 1687 1798 0.9383
#' #'
#' #'
#' septic_patients %>% #' septic_patients %>%
#' group_by(hospital_id) %>% #' group_by(hospital_id) %>%
#' summarise(cipro_p = portion_S(CIP, as_percent = TRUE), #' summarise(cipro_p = portion_SI(CIP, as_percent = TRUE),
#' cipro_n = count_all(CIP), #' cipro_n = count_all(CIP),
#' genta_p = portion_S(GEN, as_percent = TRUE), #' genta_p = portion_SI(GEN, as_percent = TRUE),
#' genta_n = count_all(GEN), #' genta_n = count_all(GEN),
#' combination_p = portion_S(CIP, GEN, as_percent = TRUE), #' combination_p = portion_SI(CIP, GEN, as_percent = TRUE),
#' combination_n = count_all(CIP, GEN)) #' combination_n = count_all(CIP, GEN))
#' #'
#' # Get portions S/I/R immediately of all rsi columns #' # Get portions S/I/R immediately of all rsi columns
@@ -155,13 +186,12 @@
portion_R <- function(..., portion_R <- function(...,
minimum = 30, minimum = 30,
as_percent = FALSE, as_percent = FALSE,
also_single_tested = FALSE) { only_all_tested = FALSE) {
rsi_calc(..., rsi_calc(...,
type = "R", ab_result = "R",
include_I = FALSE,
minimum = minimum, minimum = minimum,
as_percent = as_percent, as_percent = as_percent,
also_single_tested = also_single_tested, only_all_tested = only_all_tested,
only_count = FALSE) only_count = FALSE)
} }
@@ -170,13 +200,12 @@ portion_R <- function(...,
portion_IR <- function(..., portion_IR <- function(...,
minimum = 30, minimum = 30,
as_percent = FALSE, as_percent = FALSE,
also_single_tested = FALSE) { only_all_tested = FALSE) {
rsi_calc(..., rsi_calc(...,
type = "R", ab_result = c("I", "R"),
include_I = TRUE,
minimum = minimum, minimum = minimum,
as_percent = as_percent, as_percent = as_percent,
also_single_tested = also_single_tested, only_all_tested = only_all_tested,
only_count = FALSE) only_count = FALSE)
} }
@@ -185,13 +214,12 @@ portion_IR <- function(...,
portion_I <- function(..., portion_I <- function(...,
minimum = 30, minimum = 30,
as_percent = FALSE, as_percent = FALSE,
also_single_tested = FALSE) { only_all_tested = FALSE) {
rsi_calc(..., rsi_calc(...,
type = "I", ab_result = "I",
include_I = FALSE,
minimum = minimum, minimum = minimum,
as_percent = as_percent, as_percent = as_percent,
also_single_tested = also_single_tested, only_all_tested = only_all_tested,
only_count = FALSE) only_count = FALSE)
} }
@@ -200,13 +228,12 @@ portion_I <- function(...,
portion_SI <- function(..., portion_SI <- function(...,
minimum = 30, minimum = 30,
as_percent = FALSE, as_percent = FALSE,
also_single_tested = FALSE) { only_all_tested = FALSE) {
rsi_calc(..., rsi_calc(...,
type = "S", ab_result = c("S", "I"),
include_I = TRUE,
minimum = minimum, minimum = minimum,
as_percent = as_percent, as_percent = as_percent,
also_single_tested = also_single_tested, only_all_tested = only_all_tested,
only_count = FALSE) only_count = FALSE)
} }
@@ -215,13 +242,12 @@ portion_SI <- function(...,
portion_S <- function(..., portion_S <- function(...,
minimum = 30, minimum = 30,
as_percent = FALSE, as_percent = FALSE,
also_single_tested = FALSE) { only_all_tested = FALSE) {
rsi_calc(..., rsi_calc(...,
type = "S", ab_result = "S",
include_I = FALSE,
minimum = minimum, minimum = minimum,
as_percent = as_percent, as_percent = as_percent,
also_single_tested = also_single_tested, only_all_tested = only_all_tested,
only_count = FALSE) only_count = FALSE)
} }

View File

@@ -36,7 +36,7 @@
#' #'
#' The function \code{is.rsi.eligible} returns \code{TRUE} when a columns contains at most 5\% invalid antimicrobial interpretations (not S and/or I and/or R), and \code{FALSE} otherwise. The threshold of 5\% can be set with the \code{threshold} parameter. #' The function \code{is.rsi.eligible} returns \code{TRUE} when a columns contains at most 5\% invalid antimicrobial interpretations (not S and/or I and/or R), and \code{FALSE} otherwise. The threshold of 5\% can be set with the \code{threshold} parameter.
#' @section Interpretation of S, I and R: #' @section Interpretation of S, I and R:
#' In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations". #' In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (\url{http://www.eucast.org/newsiandr/}). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".
#' #'
#' \itemize{ #' \itemize{
#' \item{\strong{S} - }{Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.} #' \item{\strong{S} - }{Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.}
@@ -46,9 +46,7 @@
#' #'
#' Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection. #' Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.
#' #'
#' Source: \url{http://www.eucast.org/newsiandr/}. #' This AMR package honours this new insight. Use \code{\link{portion_SI}} to determine antimicrobial susceptibility and \code{\link{count_SI}} to count susceptible isolates.
#'
#' \strong{This AMR package honours this new insight.}
#' @return Ordered factor with new class \code{rsi} #' @return Ordered factor with new class \code{rsi}
#' @keywords rsi #' @keywords rsi
#' @export #' @export

View File

@@ -38,30 +38,29 @@ dots2vars <- function(...) {
#' @importFrom dplyr %>% pull all_vars any_vars filter_all funs mutate_all #' @importFrom dplyr %>% pull all_vars any_vars filter_all funs mutate_all
rsi_calc <- function(..., rsi_calc <- function(...,
type, ab_result,
include_I, minimum = 0,
minimum, as_percent = FALSE,
as_percent, only_all_tested = FALSE,
also_single_tested, only_count = FALSE) {
only_count) {
data_vars <- dots2vars(...) data_vars <- dots2vars(...)
if (!is.logical(include_I)) {
stop('`include_I` must be logical', call. = FALSE)
}
if (!is.numeric(minimum)) { if (!is.numeric(minimum)) {
stop('`minimum` must be numeric', call. = FALSE) stop('`minimum` must be numeric', call. = FALSE)
} }
if (!is.logical(as_percent)) { if (!is.logical(as_percent)) {
stop('`as_percent` must be logical', call. = FALSE) stop('`as_percent` must be logical', call. = FALSE)
} }
if (!is.logical(also_single_tested)) { if (!is.logical(only_all_tested)) {
stop('`also_single_tested` must be logical', call. = FALSE) stop('`only_all_tested` must be logical', call. = FALSE)
} }
dots_df <- ...elt(1) # it needs this evaluation dots_df <- ...elt(1) # it needs this evaluation
dots <- base::eval(base::substitute(base::alist(...))) dots <- base::eval(base::substitute(base::alist(...)))
if ("also_single_tested" %in% names(dots)) {
stop("`also_single_tested` was replaced by `only_all_tested`. Please read Details in the help page (`?portion`) as this may have a considerable impact on your analysis.", call. = FALSE)
}
ndots <- length(dots) ndots <- length(dots)
if ("data.frame" %in% class(dots_df)) { if ("data.frame" %in% class(dots_df)) {
@@ -99,8 +98,7 @@ rsi_calc <- function(...,
print_warning <- FALSE print_warning <- FALSE
type_trans <- as.integer(as.rsi(type)) ab_result <- as.rsi(ab_result)
type_others <- base::setdiff(1:3, type_trans)
if (is.data.frame(x)) { if (is.data.frame(x)) {
rsi_integrity_check <- character(0) rsi_integrity_check <- character(0)
@@ -108,43 +106,38 @@ rsi_calc <- function(...,
# check integrity of columns: force rsi class # check integrity of columns: force rsi class
if (!is.rsi(x %>% pull(i))) { if (!is.rsi(x %>% pull(i))) {
rsi_integrity_check <- c(rsi_integrity_check, x %>% pull(i) %>% as.character()) rsi_integrity_check <- c(rsi_integrity_check, x %>% pull(i) %>% as.character())
x[, i] <- suppressWarnings(as.rsi(x[, i])) # warning will be given later x[, i] <- suppressWarnings(x %>% pull(i) %>% as.rsi()) # warning will be given later
print_warning <- TRUE print_warning <- TRUE
} }
x[, i] <- x %>% pull(i) %>% as.integer() #x[, i] <- x %>% pull(i)
} }
if (length(rsi_integrity_check) > 0) { if (length(rsi_integrity_check) > 0) {
# this will give a warning for invalid results, of all input columns (so only 1 warning) # this will give a warning for invalid results, of all input columns (so only 1 warning)
rsi_integrity_check <- as.rsi(rsi_integrity_check) rsi_integrity_check <- as.rsi(rsi_integrity_check)
} }
if (include_I == TRUE) { # THE CHANCE THAT AT LEAST ONE RESULT IS ab_result
x <- x %>% mutate_all(funs(ifelse(. == 2, type_trans, .))) #numerator <- x %>% filter_all(any_vars(. %in% ab_result)) %>% nrow()
} if (only_all_tested == TRUE) {
# THE NUMBER OF ISOLATES WHERE *ALL* ABx ARE S/I/R
if (also_single_tested == TRUE) { x_filtered <- x %>% filter_all(all_vars(!is.na(.)))
# THE CHANCE THAT AT LEAST ONE RESULT IS type numerator <- x_filtered %>% filter_all(any_vars(. %in% ab_result)) %>% nrow()
found <- x %>% filter_all(any_vars(. == type_trans)) %>% nrow() denominator <- x_filtered %>% nrow()
# THE CHANCE THAT AT LEAST ONE RESULT IS type OR ALL ARE TESTED
total <- found + x %>% filter_all(all_vars(. %in% type_others)) %>% nrow()
} else { } else {
x <- apply(X = x, # THE NUMBER OF ISOLATES WHERE *ANY* ABx IS S/I/R
MARGIN = 1, other_values <- base::setdiff(c(NA, levels(ab_result)), ab_result)
FUN = min) other_values_filter <- base::apply(x, 1, function(y) { base::all(y %in% other_values) & base::any(is.na(y)) })
found <- sum(as.integer(x) == type_trans, na.rm = TRUE) numerator <- x %>% filter_all(any_vars(. %in% ab_result)) %>% nrow()
total <- length(x) - sum(is.na(x)) denominator <- x %>% filter(!other_values_filter) %>% nrow()
} }
} else { } else {
# x is not a data.frame
if (!is.rsi(x)) { if (!is.rsi(x)) {
x <- as.rsi(x) x <- as.rsi(x)
print_warning <- TRUE print_warning <- TRUE
} }
x <- as.integer(x) numerator <- sum(x %in% ab_result, na.rm = TRUE)
if (include_I == TRUE) { denominator <- sum(x %in% levels(ab_result), na.rm = TRUE)
x[x == 2] <- type_trans
}
found <- sum(x == type_trans, na.rm = TRUE)
total <- length(x) - sum(is.na(x))
} }
if (print_warning == TRUE) { if (print_warning == TRUE) {
@@ -153,20 +146,23 @@ rsi_calc <- function(...,
} }
if (only_count == TRUE) { if (only_count == TRUE) {
return(found) return(numerator)
} }
if (total < minimum) { if (denominator < minimum) {
warning("Introducing NA: only ", total, " results available for ", data_vars, " (minimum set to ", minimum, ").", call. = FALSE) if (data_vars != "") {
result <- NA data_vars <- paste(" for", data_vars)
}
warning("Introducing NA: only ", denominator, " results available", data_vars, " (minimum set to ", minimum, ").", call. = FALSE)
fraction <- NA
} else { } else {
result <- found / total fraction <- numerator / denominator
} }
if (as_percent == TRUE) { if (as_percent == TRUE) {
percent(result, force_zero = TRUE) percent(fraction, force_zero = TRUE)
} else { } else {
result fraction
} }
} }

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="Latest development version">0.7.1.9004</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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">23 June 2019</h4> <h4 class="date">01 July 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/">R Markdown</a>. However, the methodology remains unchanged. This page was generated on 23 June 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/">R Markdown</a>. However, the methodology remains unchanged. This page was generated on 01 July 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-06-23</td> <td align="center">2019-07-01</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-06-23</td> <td align="center">2019-07-01</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-06-23</td> <td align="center">2019-07-01</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,69 +327,69 @@
</tr></thead> </tr></thead>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">2017-10-01</td> <td align="center">2011-09-06</td>
<td align="center">O3</td> <td align="center">Z5</td>
<td align="center">Hospital B</td> <td align="center">Hospital B</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">R</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">F</td> <td align="center">F</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2011-03-09</td> <td align="center">2015-03-21</td>
<td align="center">U5</td> <td align="center">E7</td>
<td align="center">Hospital B</td> <td align="center">Hospital C</td>
<td align="center">Staphylococcus aureus</td> <td align="center">Escherichia coli</td>
<td align="center">R</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">M</td>
</tr>
<tr class="odd">
<td align="center">2010-08-11</td>
<td align="center">X6</td>
<td align="center">Hospital C</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">R</td>
<td align="center">S</td>
<td align="center">F</td> <td align="center">F</td>
</tr> </tr>
<tr class="odd"> <tr class="even">
<td align="center">2011-03-26</td> <td align="center">2012-06-16</td>
<td align="center">N5</td> <td align="center">E10</td>
<td align="center">Hospital A</td> <td align="center">Hospital D</td>
<td align="center">Escherichia coli</td> <td align="center">Staphylococcus aureus</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">M</td>
</tr>
<tr class="odd">
<td align="center">2016-12-29</td>
<td align="center">J3</td>
<td align="center">Hospital C</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">S</td>
<td align="center">M</td> <td align="center">M</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2013-03-11</td> <td align="center">2010-04-09</td>
<td align="center">O1</td> <td align="center">Q3</td>
<td align="center">Hospital A</td> <td align="center">Hospital B</td>
<td align="center">Escherichia coli</td> <td align="center">Streptococcus pneumoniae</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">F</td>
</tr>
<tr class="odd">
<td align="center">2016-05-24</td>
<td align="center">V5</td>
<td align="center">Hospital D</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">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="even">
<td align="center">2016-09-21</td>
<td align="center">Z8</td>
<td align="center">Hospital A</td>
<td align="center">Klebsiella pneumoniae</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">F</td> <td align="center">F</td>
</tr> </tr>
</tbody> </tbody>
@@ -411,8 +411,8 @@
# #
# Item Count Percent Cum. Count Cum. Percent # Item Count Percent Cum. Count Cum. Percent
# --- ----- ------- -------- ----------- ------------- # --- ----- ------- -------- ----------- -------------
# 1 M 10,366 51.8% 10,366 51.8% # 1 M 10,408 52.0% 10,408 52.0%
# 2 F 9,634 48.2% 20,000 100.0%</code></pre> # 2 F 9,592 48.0% 20,000 100.0%</code></pre>
<p>So, we can draw at least two conclusions immediately. From a data scientists perspective, the data looks clean: only values <code>M</code> and <code>F</code>. From a researchers 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 scientists perspective, the data looks clean: only values <code>M</code> and <code>F</code>. From a researchers 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>
@@ -442,14 +442,14 @@
<a class="sourceLine" id="cb14-18" title="18"><span class="co"># Pasteurella multocida (no new changes)</span></a> <a class="sourceLine" id="cb14-18" title="18"><span class="co"># Pasteurella multocida (no new changes)</span></a>
<a class="sourceLine" id="cb14-19" title="19"><span class="co"># Staphylococcus (no new changes)</span></a> <a class="sourceLine" id="cb14-19" title="19"><span class="co"># Staphylococcus (no new changes)</span></a>
<a class="sourceLine" id="cb14-20" title="20"><span class="co"># Streptococcus groups A, B, C, G (no new changes)</span></a> <a class="sourceLine" id="cb14-20" title="20"><span class="co"># Streptococcus groups A, B, C, G (no new changes)</span></a>
<a class="sourceLine" id="cb14-21" title="21"><span class="co"># Streptococcus pneumoniae (1,453 new changes)</span></a> <a class="sourceLine" id="cb14-21" title="21"><span class="co"># Streptococcus pneumoniae (1,443 new changes)</span></a>
<a class="sourceLine" id="cb14-22" title="22"><span class="co"># Viridans group streptococci (no new changes)</span></a> <a class="sourceLine" id="cb14-22" title="22"><span class="co"># Viridans group streptococci (no new changes)</span></a>
<a class="sourceLine" id="cb14-23" title="23"><span class="co"># </span></a> <a class="sourceLine" id="cb14-23" title="23"><span class="co"># </span></a>
<a class="sourceLine" id="cb14-24" title="24"><span class="co"># EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)</span></a> <a class="sourceLine" id="cb14-24" title="24"><span class="co"># EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)</span></a>
<a class="sourceLine" id="cb14-25" title="25"><span class="co"># Table 01: Intrinsic resistance in Enterobacteriaceae (1,298 new changes)</span></a> <a class="sourceLine" id="cb14-25" title="25"><span class="co"># Table 01: Intrinsic resistance in Enterobacteriaceae (1,332 new changes)</span></a>
<a class="sourceLine" id="cb14-26" title="26"><span class="co"># Table 02: Intrinsic resistance in non-fermentative Gram-negative bacteria (no new changes)</span></a> <a class="sourceLine" id="cb14-26" title="26"><span class="co"># Table 02: Intrinsic resistance in non-fermentative Gram-negative bacteria (no new changes)</span></a>
<a class="sourceLine" id="cb14-27" title="27"><span class="co"># Table 03: Intrinsic resistance in other Gram-negative bacteria (no new changes)</span></a> <a class="sourceLine" id="cb14-27" title="27"><span class="co"># Table 03: Intrinsic resistance in other Gram-negative bacteria (no new changes)</span></a>
<a class="sourceLine" id="cb14-28" title="28"><span class="co"># Table 04: Intrinsic resistance in Gram-positive bacteria (2,747 new changes)</span></a> <a class="sourceLine" id="cb14-28" title="28"><span class="co"># Table 04: Intrinsic resistance in Gram-positive bacteria (2,723 new changes)</span></a>
<a class="sourceLine" id="cb14-29" title="29"><span class="co"># Table 08: Interpretive rules for B-lactam agents and Gram-positive cocci (no new changes)</span></a> <a class="sourceLine" id="cb14-29" title="29"><span class="co"># Table 08: Interpretive rules for B-lactam agents and Gram-positive cocci (no new changes)</span></a>
<a class="sourceLine" id="cb14-30" title="30"><span class="co"># Table 09: Interpretive rules for B-lactam agents and Gram-negative rods (no new changes)</span></a> <a class="sourceLine" id="cb14-30" title="30"><span class="co"># Table 09: Interpretive rules for B-lactam agents and Gram-negative rods (no new changes)</span></a>
<a class="sourceLine" id="cb14-31" title="31"><span class="co"># Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins (no new changes)</span></a> <a class="sourceLine" id="cb14-31" title="31"><span class="co"># Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins (no new changes)</span></a>
@@ -457,24 +457,24 @@
<a class="sourceLine" id="cb14-33" title="33"><span class="co"># Table 13: Interpretive rules for quinolones (no new changes)</span></a> <a class="sourceLine" id="cb14-33" title="33"><span class="co"># Table 13: Interpretive rules for quinolones (no new changes)</span></a>
<a class="sourceLine" id="cb14-34" title="34"><span class="co"># </span></a> <a class="sourceLine" id="cb14-34" title="34"><span class="co"># </span></a>
<a class="sourceLine" id="cb14-35" title="35"><span class="co"># Other rules</span></a> <a class="sourceLine" id="cb14-35" title="35"><span class="co"># Other rules</span></a>
<a class="sourceLine" id="cb14-36" title="36"><span class="co"># Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (2,176 new changes)</span></a> <a class="sourceLine" id="cb14-36" title="36"><span class="co"># Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (2,213 new changes)</span></a>
<a class="sourceLine" id="cb14-37" title="37"><span class="co"># Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (121 new changes)</span></a> <a class="sourceLine" id="cb14-37" title="37"><span class="co"># Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (127 new changes)</span></a>
<a class="sourceLine" id="cb14-38" title="38"><span class="co"># Non-EUCAST: piperacillin = R where piperacillin/tazobactam = R (no new changes)</span></a> <a class="sourceLine" id="cb14-38" title="38"><span class="co"># Non-EUCAST: piperacillin = R where piperacillin/tazobactam = R (no new changes)</span></a>
<a class="sourceLine" id="cb14-39" title="39"><span class="co"># Non-EUCAST: piperacillin/tazobactam = S where piperacillin = S (no new changes)</span></a> <a class="sourceLine" id="cb14-39" title="39"><span class="co"># Non-EUCAST: piperacillin/tazobactam = S where piperacillin = S (no new changes)</span></a>
<a class="sourceLine" id="cb14-40" title="40"><span class="co"># Non-EUCAST: trimethoprim = R where trimethoprim/sulfa = R (no new changes)</span></a> <a class="sourceLine" id="cb14-40" title="40"><span class="co"># Non-EUCAST: trimethoprim = R where trimethoprim/sulfa = R (no new changes)</span></a>
<a class="sourceLine" id="cb14-41" title="41"><span class="co"># Non-EUCAST: trimethoprim/sulfa = S where trimethoprim = S (no new changes)</span></a> <a class="sourceLine" id="cb14-41" title="41"><span class="co"># Non-EUCAST: trimethoprim/sulfa = S where trimethoprim = S (no new changes)</span></a>
<a class="sourceLine" id="cb14-42" title="42"><span class="co"># </span></a> <a class="sourceLine" id="cb14-42" title="42"><span class="co"># </span></a>
<a class="sourceLine" id="cb14-43" title="43"><span class="co"># --------------------------------------------------------------------------</span></a> <a class="sourceLine" id="cb14-43" title="43"><span class="co"># --------------------------------------------------------------------------</span></a>
<a class="sourceLine" id="cb14-44" title="44"><span class="co"># EUCAST rules affected 6,468 out of 20,000 rows, making a total of 7,795 edits</span></a> <a class="sourceLine" id="cb14-44" title="44"><span class="co"># EUCAST rules affected 6,513 out of 20,000 rows, making a total of 7,838 edits</span></a>
<a class="sourceLine" id="cb14-45" title="45"><span class="co"># =&gt; added 0 test results</span></a> <a class="sourceLine" id="cb14-45" title="45"><span class="co"># =&gt; added 0 test results</span></a>
<a class="sourceLine" id="cb14-46" title="46"><span class="co"># </span></a> <a class="sourceLine" id="cb14-46" title="46"><span class="co"># </span></a>
<a class="sourceLine" id="cb14-47" title="47"><span class="co"># =&gt; changed 7,795 test results</span></a> <a class="sourceLine" id="cb14-47" title="47"><span class="co"># =&gt; changed 7,838 test results</span></a>
<a class="sourceLine" id="cb14-48" title="48"><span class="co"># - 107 test results changed from S to I</span></a> <a class="sourceLine" id="cb14-48" title="48"><span class="co"># - 115 test results changed from S to I</span></a>
<a class="sourceLine" id="cb14-49" title="49"><span class="co"># - 4,725 test results changed from S to R</span></a> <a class="sourceLine" id="cb14-49" title="49"><span class="co"># - 4,719 test results changed from S to R</span></a>
<a class="sourceLine" id="cb14-50" title="50"><span class="co"># - 1,040 test results changed from I to S</span></a> <a class="sourceLine" id="cb14-50" title="50"><span class="co"># - 1,077 test results changed from I to S</span></a>
<a class="sourceLine" id="cb14-51" title="51"><span class="co"># - 329 test results changed from I to R</span></a> <a class="sourceLine" id="cb14-51" title="51"><span class="co"># - 335 test results changed from I to R</span></a>
<a class="sourceLine" id="cb14-52" title="52"><span class="co"># - 1,579 test results changed from R to S</span></a> <a class="sourceLine" id="cb14-52" title="52"><span class="co"># - 1,573 test results changed from R to S</span></a>
<a class="sourceLine" id="cb14-53" title="53"><span class="co"># - 15 test results changed from R to I</span></a> <a class="sourceLine" id="cb14-53" title="53"><span class="co"># - 19 test results changed from R to I</span></a>
<a class="sourceLine" id="cb14-54" title="54"><span class="co"># --------------------------------------------------------------------------</span></a> <a class="sourceLine" id="cb14-54" title="54"><span class="co"># --------------------------------------------------------------------------</span></a>
<a class="sourceLine" id="cb14-55" title="55"><span class="co"># </span></a> <a class="sourceLine" id="cb14-55" title="55"><span class="co"># </span></a>
<a class="sourceLine" id="cb14-56" title="56"><span class="co"># Use verbose = TRUE to get a data.frame with all specified edits instead.</span></a></code></pre></div> <a class="sourceLine" id="cb14-56" title="56"><span class="co"># Use verbose = TRUE to get a data.frame with all specified edits instead.</span></a></code></pre></div>
@@ -502,8 +502,8 @@
<a class="sourceLine" id="cb16-3" title="3"><span class="co"># </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"># </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"># </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"># </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"># </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"># </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; Found 5,644 first isolates (28.2% of total)</span></a></code></pre></div> <a class="sourceLine" id="cb16-6" title="6"><span class="co"># =&gt; Found 5,719 first isolates (28.6% of total)</span></a></code></pre></div>
<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> <p>So only 28.6% 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>
@@ -513,7 +513,7 @@
<div id="first-weighted-isolates" class="section level2"> <div id="first-weighted-isolates" class="section level2">
<h2 class="hasAnchor"> <h2 class="hasAnchor">
<a href="#first-weighted-isolates" class="anchor"></a>First <em>weighted</em> isolates</h2> <a href="#first-weighted-isolates" class="anchor"></a>First <em>weighted</em> isolates</h2>
<p>We made a slight twist to the CLSI algorithm, to take into account the antimicrobial susceptibility profile. Have a look at all isolates of patient M3, sorted on date:</p> <p>We made a slight twist to the CLSI algorithm, to take into account the antimicrobial susceptibility profile. Have a look at all isolates of patient S7, sorted on date:</p>
<table class="table"> <table class="table">
<thead><tr class="header"> <thead><tr class="header">
<th align="center">isolate</th> <th align="center">isolate</th>
@@ -529,74 +529,74 @@
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">1</td> <td align="center">1</td>
<td align="center">2010-01-24</td> <td align="center">2010-01-28</td>
<td align="center">M3</td> <td align="center">S7</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">TRUE</td>
</tr>
<tr class="even">
<td align="center">2</td>
<td align="center">2010-03-17</td>
<td align="center">M3</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>
</tr>
<tr class="odd">
<td align="center">3</td>
<td align="center">2010-04-12</td>
<td align="center">M3</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>
</tr>
<tr class="even">
<td align="center">4</td>
<td align="center">2010-05-20</td>
<td align="center">M3</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>
</tr>
<tr class="odd">
<td align="center">5</td>
<td align="center">2010-06-08</td>
<td align="center">M3</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>
</tr>
<tr class="even">
<td align="center">6</td>
<td align="center">2010-06-20</td>
<td align="center">M3</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">I</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">TRUE</td>
</tr>
<tr class="even">
<td align="center">2</td>
<td align="center">2010-02-07</td>
<td align="center">S7</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">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">3</td>
<td align="center">2010-03-16</td>
<td align="center">S7</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">FALSE</td>
</tr>
<tr class="even">
<td align="center">4</td>
<td align="center">2010-10-09</td>
<td align="center">S7</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>
</tr>
<tr class="odd">
<td align="center">5</td>
<td align="center">2011-01-25</td>
<td align="center">S7</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">FALSE</td>
</tr>
<tr class="even">
<td align="center">6</td>
<td align="center">2011-02-16</td>
<td align="center">S7</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>
</tr>
<tr class="odd">
<td align="center">7</td> <td align="center">7</td>
<td align="center">2010-09-18</td> <td align="center">2011-02-24</td>
<td align="center">M3</td> <td align="center">S7</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>
@@ -606,10 +606,10 @@
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">8</td> <td align="center">8</td>
<td align="center">2010-10-08</td> <td align="center">2011-03-30</td>
<td align="center">M3</td> <td align="center">S7</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">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>
@@ -617,19 +617,19 @@
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">9</td> <td align="center">9</td>
<td align="center">2010-11-05</td> <td align="center">2011-04-25</td>
<td align="center">M3</td> <td align="center">S7</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>
<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="even"> <tr class="even">
<td align="center">10</td> <td align="center">10</td>
<td align="center">2010-12-23</td> <td align="center">2011-05-06</td>
<td align="center">M3</td> <td align="center">S7</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>
@@ -639,7 +639,7 @@
</tr> </tr>
</tbody> </tbody>
</table> </table>
<p>Only 1 isolates are marked as first according to CLSI guideline. But when reviewing the antibiogram, it is obvious that some isolates are absolutely different strains and should be included too. This is why we weigh isolates, based on their antibiogram. The <code><a href="../reference/key_antibiotics.html">key_antibiotics()</a></code> function adds a vector with 18 key antibiotics: 6 broad spectrum ones, 6 small spectrum for Gram negatives and 6 small spectrum for Gram positives. These can be defined by the user.</p> <p>Only 2 isolates are marked as first according to CLSI guideline. But when reviewing the antibiogram, it is obvious that some isolates are absolutely different strains and should be included too. This is why we weigh isolates, based on their antibiogram. The <code><a href="../reference/key_antibiotics.html">key_antibiotics()</a></code> function adds a vector with 18 key antibiotics: 6 broad spectrum ones, 6 small spectrum for Gram negatives and 6 small spectrum for Gram positives. These can be defined by the user.</p>
<p>If a column exists with a name like key(…)ab the <code><a href="../reference/first_isolate.html">first_isolate()</a></code> function will automatically use it and determine the first weighted isolates. Mind the NOTEs in below output:</p> <p>If a column exists with a name like key(…)ab the <code><a href="../reference/first_isolate.html">first_isolate()</a></code> function will automatically use it and determine the first weighted isolates. Mind the NOTEs in below output:</p>
<div class="sourceCode" id="cb19"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb19-1" title="1">data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a> <div class="sourceCode" id="cb19"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb19-1" title="1">data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb19-2" title="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="dt">keyab =</span> <span class="kw"><a href="../reference/key_antibiotics.html">key_antibiotics</a></span>(.)) <span class="op">%&gt;%</span><span class="st"> </span></a> <a class="sourceLine" id="cb19-2" title="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="dt">keyab =</span> <span class="kw"><a href="../reference/key_antibiotics.html">key_antibiotics</a></span>(.)) <span class="op">%&gt;%</span><span class="st"> </span></a>
@@ -650,7 +650,7 @@
<a class="sourceLine" id="cb19-7" title="7"><span class="co"># </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"># </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"># </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"># </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"># [Criterion] Inclusion based on key antibiotics, ignoring I.</span></a> <a class="sourceLine" id="cb19-9" title="9"><span class="co"># [Criterion] Inclusion based on key antibiotics, ignoring I.</span></a>
<a class="sourceLine" id="cb19-10" title="10"><span class="co"># =&gt; Found 15,080 first weighted isolates (75.4% of total)</span></a></code></pre></div> <a class="sourceLine" id="cb19-10" title="10"><span class="co"># =&gt; Found 15,097 first weighted isolates (75.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>
@@ -667,94 +667,94 @@
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">1</td> <td align="center">1</td>
<td align="center">2010-01-24</td> <td align="center">2010-01-28</td>
<td align="center">M3</td> <td align="center">S7</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">I</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>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2</td> <td align="center">2</td>
<td align="center">2010-03-17</td> <td align="center">2010-02-07</td>
<td align="center">M3</td> <td align="center">S7</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>
<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">3</td> <td align="center">3</td>
<td align="center">2010-04-12</td> <td align="center">2010-03-16</td>
<td align="center">M3</td> <td align="center">S7</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">TRUE</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-05-20</td> <td align="center">2010-10-09</td>
<td align="center">M3</td> <td align="center">S7</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>
<td align="center">R</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">5</td> <td align="center">5</td>
<td align="center">2010-06-08</td> <td align="center">2011-01-25</td>
<td align="center">M3</td> <td align="center">S7</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> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">6</td> <td align="center">6</td>
<td align="center">2010-06-20</td> <td align="center">2011-02-16</td>
<td align="center">M3</td> <td align="center">S7</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">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">S</td>
<td align="center">S</td>
<td align="center">TRUE</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">7</td> <td align="center">7</td>
<td align="center">2010-09-18</td> <td align="center">2011-02-24</td>
<td align="center">M3</td> <td align="center">S7</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>
<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">TRUE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">8</td> <td align="center">8</td>
<td align="center">2010-10-08</td> <td align="center">2011-03-30</td>
<td align="center">M3</td> <td align="center">S7</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">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>
@@ -763,8 +763,20 @@
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">9</td> <td align="center">9</td>
<td align="center">2010-11-05</td> <td align="center">2011-04-25</td>
<td align="center">M3</td> <td align="center">S7</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">FALSE</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">10</td>
<td align="center">2011-05-06</td>
<td align="center">S7</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>
@@ -773,25 +785,13 @@
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even">
<td align="center">10</td>
<td align="center">2010-12-23</td>
<td align="center">M3</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>
</tbody> </tbody>
</table> </table>
<p>Instead of 1, now 7 isolates are flagged. In total, 75.4% of all isolates are marked first weighted - 47.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>Instead of 2, now 9 isolates are flagged. In total, 75.5% of all isolates are marked first weighted - 46.9% 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,080 isolates for analysis.</p> <p>So we end up with 15,097 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>
@@ -799,7 +799,6 @@
<div class="sourceCode" id="cb22"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb22-1" title="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/utils/topics/head">head</a></span>(data_1st)</a></code></pre></div> <div class="sourceCode" id="cb22"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb22-1" title="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/utils/topics/head">head</a></span>(data_1st)</a></code></pre></div>
<table class="table"> <table class="table">
<thead><tr class="header"> <thead><tr class="header">
<th></th>
<th align="center">date</th> <th align="center">date</th>
<th align="center">patient_id</th> <th align="center">patient_id</th>
<th align="center">hospital</th> <th align="center">hospital</th>
@@ -816,13 +815,12 @@
</tr></thead> </tr></thead>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td>1</td> <td align="center">2011-09-06</td>
<td align="center">2017-10-01</td> <td align="center">Z5</td>
<td align="center">O3</td>
<td align="center">Hospital B</td> <td align="center">Hospital B</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">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">F</td> <td align="center">F</td>
@@ -832,62 +830,58 @@
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td>4</td> <td align="center">2015-03-21</td>
<td align="center">2013-03-11</td> <td align="center">E7</td>
<td align="center">O1</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">I</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">M</td>
<td align="center">F</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>5</td> <td align="center">2010-08-11</td>
<td align="center">2016-05-24</td> <td align="center">X6</td>
<td align="center">V5</td> <td align="center">Hospital C</td>
<td align="center">Hospital D</td> <td align="center">B_ESCHR_COL</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">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">F</td> <td align="center">F</td>
<td align="center">Gram-negative</td>
<td align="center">Escherichia</td>
<td align="center">coli</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">2012-06-16</td>
<td align="center">E10</td>
<td align="center">Hospital D</td>
<td align="center">B_STPHY_AUR</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">Gram-positive</td> <td align="center">Gram-positive</td>
<td align="center">Staphylococcus</td> <td align="center">Staphylococcus</td>
<td align="center">aureus</td> <td align="center">aureus</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even">
<td>6</td>
<td align="center">2016-09-21</td>
<td align="center">Z8</td>
<td align="center">Hospital A</td>
<td align="center">B_KLBSL_PNE</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">F</td>
<td align="center">Gram-negative</td>
<td align="center">Klebsiella</td>
<td align="center">pneumoniae</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd"> <tr class="odd">
<td>7</td> <td align="center">2016-12-29</td>
<td align="center">2010-09-19</td> <td align="center">J3</td>
<td align="center">H3</td>
<td align="center">Hospital C</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">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">M</td> <td align="center">M</td>
<td align="center">Gram-negative</td> <td align="center">Gram-negative</td>
@@ -896,19 +890,18 @@
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td>8</td> <td align="center">2010-04-09</td>
<td align="center">2015-04-27</td> <td align="center">Q3</td>
<td align="center">C9</td> <td align="center">Hospital B</td>
<td align="center">Hospital C</td> <td align="center">B_STRPT_PNE</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">F</td>
<td align="center">S</td> <td align="center">Gram-positive</td>
<td align="center">M</td> <td align="center">Streptococcus</td>
<td align="center">Gram-negative</td> <td align="center">pneumoniae</td>
<td align="center">Escherichia</td>
<td align="center">coli</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
</tbody> </tbody>
@@ -928,9 +921,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 <code>data_1st</code> (15,080 x 13)</strong></p> <p><strong>Frequency table of <code>genus</code> and <code>species</code> from <code>data_1st</code> (15,097 x 13)</strong></p>
<p>Columns: 2<br> <p>Columns: 2<br>
Length: 15,080 (of which NA: 0 = 0.00%)<br> Length: 15,097 (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>
@@ -947,33 +940,33 @@ Longest: 24</p>
<tr class="odd"> <tr class="odd">
<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,414</td> <td align="right">7,483</td>
<td align="right">49.2%</td> <td align="right">49.6%</td>
<td align="right">7,414</td> <td align="right">7,483</td>
<td align="right">49.2%</td> <td align="right">49.6%</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,787</td> <td align="right">3,673</td>
<td align="right">25.1%</td> <td align="right">24.3%</td>
<td align="right">11,201</td> <td align="right">11,156</td>
<td align="right">74.3%</td> <td align="right">73.9%</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,319</td> <td align="right">2,306</td>
<td align="right">15.4%</td> <td align="right">15.3%</td>
<td align="right">13,520</td> <td align="right">13,462</td>
<td align="right">89.7%</td> <td align="right">89.2%</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,560</td> <td align="right">1,635</td>
<td align="right">10.3%</td> <td align="right">10.8%</td>
<td align="right">15,080</td> <td align="right">15,097</td>
<td align="right">100.0%</td> <td align="right">100.0%</td>
</tr> </tr>
</tbody> </tbody>
@@ -984,7 +977,7 @@ Longest: 24</p>
<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_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. As per the EUCAST guideline of 2019, we calculate resistance as the portion of R (<code><a href="../reference/portion.html">portion_R()</a></code>) and susceptibility as the portion of S and I (<code><a href="../reference/portion.html">portion_SI()</a></code>). These functions 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. As per the EUCAST guideline of 2019, we calculate resistance as the portion of R (<code><a href="../reference/portion.html">portion_R()</a></code>) and susceptibility as the portion of S and I (<code><a href="../reference/portion.html">portion_SI()</a></code>). These functions 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_R</a></span>(AMX)</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_R</a></span>(AMX)</a>
<a class="sourceLine" id="cb25-2" title="2"><span class="co"># [1] 0.4661804</span></a></code></pre></div> <a class="sourceLine" id="cb25-2" title="2"><span class="co"># [1] 0.4738027</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>
@@ -997,19 +990,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.4658016</td> <td align="center">0.4810406</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.4614653</td> <td align="center">0.4714259</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.4744526</td> <td align="center">0.4625113</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.4686334</td> <td align="center">0.4753247</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
@@ -1027,23 +1020,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.4658016</td> <td align="center">0.4810406</td>
<td align="center">4547</td> <td align="center">4536</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.4614653</td> <td align="center">0.4714259</td>
<td align="center">5255</td> <td align="center">5267</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.4744526</td> <td align="center">0.4625113</td>
<td align="center">2329</td> <td align="center">2214</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.4686334</td> <td align="center">0.4753247</td>
<td align="center">2949</td> <td align="center">3080</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
@@ -1063,27 +1056,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.9219045</td> <td align="center">0.9256982</td>
<td align="center">0.8950634</td> <td align="center">0.8929574</td>
<td align="center">0.9950094</td> <td align="center">0.9951891</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Klebsiella</td> <td align="center">Klebsiella</td>
<td align="center">0.8153846</td> <td align="center">0.8214067</td>
<td align="center">0.8935897</td> <td align="center">0.9033639</td>
<td align="center">0.9865385</td> <td align="center">0.9865443</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">Staphylococcus</td> <td align="center">Staphylococcus</td>
<td align="center">0.9176129</td> <td align="center">0.9229513</td>
<td align="center">0.9144442</td> <td align="center">0.9224068</td>
<td align="center">0.9949828</td> <td align="center">0.9937381</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Streptococcus</td> <td align="center">Streptococcus</td>
<td align="center">0.6196636</td> <td align="center">0.6153513</td>
<td align="center">0.0000000</td> <td align="center">0.0000000</td>
<td align="center">0.6196636</td> <td align="center">0.6153513</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>

Binary file not shown.

Before

Width:  |  Height:  |  Size: 35 KiB

After

Width:  |  Height:  |  Size: 35 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 18 KiB

After

Width:  |  Height:  |  Size: 18 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 68 KiB

After

Width:  |  Height:  |  Size: 68 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 42 KiB

After

Width:  |  Height:  |  Size: 42 KiB

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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>
@@ -192,7 +192,7 @@
<h1>How to apply EUCAST rules</h1> <h1>How to apply EUCAST rules</h1>
<h4 class="author">Matthijs S. Berends</h4> <h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">23 June 2019</h4> <h4 class="date">01 July 2019</h4>
<div class="hidden name"><code>EUCAST.Rmd</code></div> <div class="hidden name"><code>EUCAST.Rmd</code></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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>
@@ -192,7 +192,7 @@
<h1>How to determine multi-drug resistance (MDR)</h1> <h1>How to determine multi-drug resistance (MDR)</h1>
<h4 class="author">Matthijs S. Berends</h4> <h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">23 June 2019</h4> <h4 class="date">01 July 2019</h4>
<div class="hidden name"><code>MDR.Rmd</code></div> <div class="hidden name"><code>MDR.Rmd</code></div>
@@ -235,18 +235,18 @@
<p>The data set looks like this now:</p> <p>The data set looks like this now:</p>
<div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb3-1" title="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/utils/topics/head">head</a></span>(my_TB_data)</a> <div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb3-1" title="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/utils/topics/head">head</a></span>(my_TB_data)</a>
<a class="sourceLine" id="cb3-2" title="2"><span class="co"># rifampicin isoniazid gatifloxacin ethambutol pyrazinamide moxifloxacin</span></a> <a class="sourceLine" id="cb3-2" title="2"><span class="co"># rifampicin isoniazid gatifloxacin ethambutol pyrazinamide moxifloxacin</span></a>
<a class="sourceLine" id="cb3-3" title="3"><span class="co"># 1 R S R S S S</span></a> <a class="sourceLine" id="cb3-3" title="3"><span class="co"># 1 R R S S R I</span></a>
<a class="sourceLine" id="cb3-4" title="4"><span class="co"># 2 I R S S I S</span></a> <a class="sourceLine" id="cb3-4" title="4"><span class="co"># 2 R R S R S R</span></a>
<a class="sourceLine" id="cb3-5" title="5"><span class="co"># 3 S R R R S R</span></a> <a class="sourceLine" id="cb3-5" title="5"><span class="co"># 3 R S S R R R</span></a>
<a class="sourceLine" id="cb3-6" title="6"><span class="co"># 4 R S R R I S</span></a> <a class="sourceLine" id="cb3-6" title="6"><span class="co"># 4 R R S S S I</span></a>
<a class="sourceLine" id="cb3-7" title="7"><span class="co"># 5 I R R S R S</span></a> <a class="sourceLine" id="cb3-7" title="7"><span class="co"># 5 R R S S R I</span></a>
<a class="sourceLine" id="cb3-8" title="8"><span class="co"># 6 S S S S R R</span></a> <a class="sourceLine" id="cb3-8" title="8"><span class="co"># 6 R S R R S S</span></a>
<a class="sourceLine" id="cb3-9" title="9"><span class="co"># kanamycin</span></a> <a class="sourceLine" id="cb3-9" title="9"><span class="co"># kanamycin</span></a>
<a class="sourceLine" id="cb3-10" title="10"><span class="co"># 1 S</span></a> <a class="sourceLine" id="cb3-10" title="10"><span class="co"># 1 S</span></a>
<a class="sourceLine" id="cb3-11" title="11"><span class="co"># 2 I</span></a> <a class="sourceLine" id="cb3-11" title="11"><span class="co"># 2 S</span></a>
<a class="sourceLine" id="cb3-12" title="12"><span class="co"># 3 S</span></a> <a class="sourceLine" id="cb3-12" title="12"><span class="co"># 3 S</span></a>
<a class="sourceLine" id="cb3-13" title="13"><span class="co"># 4 S</span></a> <a class="sourceLine" id="cb3-13" title="13"><span class="co"># 4 R</span></a>
<a class="sourceLine" id="cb3-14" title="14"><span class="co"># 5 S</span></a> <a class="sourceLine" id="cb3-14" title="14"><span class="co"># 5 R</span></a>
<a class="sourceLine" id="cb3-15" title="15"><span class="co"># 6 S</span></a></code></pre></div> <a class="sourceLine" id="cb3-15" title="15"><span class="co"># 6 S</span></a></code></pre></div>
<p>We can now add the interpretation of MDR-TB to our data set:</p> <p>We can now add the interpretation of MDR-TB to our data set:</p>
<div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb4-1" title="1">my_TB_data<span class="op">$</span>mdr &lt;-<span class="st"> </span><span class="kw"><a href="../reference/mdro.html">mdr_tb</a></span>(my_TB_data)</a> <div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb4-1" title="1">my_TB_data<span class="op">$</span>mdr &lt;-<span class="st"> </span><span class="kw"><a href="../reference/mdro.html">mdr_tb</a></span>(my_TB_data)</a>
@@ -277,40 +277,40 @@ Unique: 5</p>
<tr class="odd"> <tr class="odd">
<td align="left">1</td> <td align="left">1</td>
<td align="left">Mono-resistance</td> <td align="left">Mono-resistance</td>
<td align="right">3,206</td> <td align="right">3,222</td>
<td align="right">64.1%</td> <td align="right">64.4%</td>
<td align="right">3,206</td> <td align="right">3,222</td>
<td align="right">64.1%</td> <td align="right">64.4%</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="left">2</td> <td align="left">2</td>
<td align="left">Negative</td> <td align="left">Negative</td>
<td align="right">689</td> <td align="right">659</td>
<td align="right">13.8%</td> <td align="right">13.2%</td>
<td align="right">3,895</td> <td align="right">3,881</td>
<td align="right">77.9%</td> <td align="right">77.6%</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="left">3</td> <td align="left">3</td>
<td align="left">Multidrug resistance</td> <td align="left">Multidrug resistance</td>
<td align="right">578</td> <td align="right">589</td>
<td align="right">11.6%</td> <td align="right">11.8%</td>
<td align="right">4,473</td> <td align="right">4,470</td>
<td align="right">89.5%</td> <td align="right">89.4%</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="left">4</td> <td align="left">4</td>
<td align="left">Poly-resistance</td> <td align="left">Poly-resistance</td>
<td align="right">299</td> <td align="right">313</td>
<td align="right">6.0%</td> <td align="right">6.3%</td>
<td align="right">4,772</td> <td align="right">4,783</td>
<td align="right">95.4%</td> <td align="right">95.7%</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="left">5</td> <td align="left">5</td>
<td align="left">Extensive drug resistance</td> <td align="left">Extensive drug resistance</td>
<td align="right">228</td> <td align="right">217</td>
<td align="right">4.6%</td> <td align="right">4.3%</td>
<td align="right">5,000</td> <td align="right">5,000</td>
<td align="right">100.0%</td> <td align="right">100.0%</td>
</tr> </tr>

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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>
@@ -192,7 +192,7 @@
<h1>How to import data from SPSS / SAS / Stata</h1> <h1>How to import data from SPSS / SAS / Stata</h1>
<h4 class="author">Matthijs S. Berends</h4> <h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">23 June 2019</h4> <h4 class="date">01 July 2019</h4>
<div class="hidden name"><code>SPSS.Rmd</code></div> <div class="hidden name"><code>SPSS.Rmd</code></div>
@@ -274,8 +274,7 @@
<a class="sourceLine" id="cb1-30" title="30"><span class="co"># [7] "Flucloxacillin" "Flucloxacilline" "Flucloxacillinum" </span></a> <a class="sourceLine" id="cb1-30" title="30"><span class="co"># [7] "Flucloxacillin" "Flucloxacilline" "Flucloxacillinum" </span></a>
<a class="sourceLine" id="cb1-31" title="31"><span class="co"># [10] "Fluorochloroxacillin"</span></a> <a class="sourceLine" id="cb1-31" title="31"><span class="co"># [10] "Fluorochloroxacillin"</span></a>
<a class="sourceLine" id="cb1-32" title="32"><span class="kw"><a href="../reference/ab_property.html">ab_atc</a></span>(<span class="st">"floxapen"</span>)</a> <a class="sourceLine" id="cb1-32" title="32"><span class="kw"><a href="../reference/ab_property.html">ab_atc</a></span>(<span class="st">"floxapen"</span>)</a>
<a class="sourceLine" id="cb1-33" title="33"><span class="co"># Class 'atc'</span></a> <a class="sourceLine" id="cb1-33" title="33"><span class="co"># [1] "J01CF05"</span></a></code></pre></div>
<a class="sourceLine" id="cb1-34" title="34"><span class="co"># [1] J01CF05</span></a></code></pre></div>
</div> </div>
<div id="import-data-from-spsssasstata" class="section level2"> <div id="import-data-from-spsssasstata" class="section level2">
<h2 class="hasAnchor"> <h2 class="hasAnchor">

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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>
@@ -192,7 +192,7 @@
<h1>How to work with WHONET data</h1> <h1>How to work with WHONET data</h1>
<h4 class="author">Matthijs S. Berends</h4> <h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">23 June 2019</h4> <h4 class="date">01 July 2019</h4>
<div class="hidden name"><code>WHONET.Rmd</code></div> <div class="hidden name"><code>WHONET.Rmd</code></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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>
@@ -192,7 +192,7 @@
<h1>Benchmarks</h1> <h1>Benchmarks</h1>
<h4 class="author">Matthijs S. Berends</h4> <h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">23 June 2019</h4> <h4 class="date">01 July 2019</h4>
<div class="hidden name"><code>benchmarks.Rmd</code></div> <div class="hidden name"><code>benchmarks.Rmd</code></div>
@@ -217,14 +217,14 @@
<a class="sourceLine" id="cb2-8" title="8"> <span class="dt">times =</span> <span class="dv">10</span>)</a> <a class="sourceLine" id="cb2-8" title="8"> <span class="dt">times =</span> <span class="dv">10</span>)</a>
<a class="sourceLine" id="cb2-9" title="9"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(S.aureus, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">2</span>)</a> <a class="sourceLine" id="cb2-9" title="9"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(S.aureus, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">2</span>)</a>
<a class="sourceLine" id="cb2-10" title="10"><span class="co"># Unit: milliseconds</span></a> <a class="sourceLine" id="cb2-10" title="10"><span class="co"># Unit: milliseconds</span></a>
<a class="sourceLine" id="cb2-11" title="11"><span class="co"># expr min lq mean median uq max neval</span></a> <a class="sourceLine" id="cb2-11" title="11"><span class="co"># expr min lq mean median uq max neval</span></a>
<a class="sourceLine" id="cb2-12" title="12"><span class="co"># as.mo("sau") 17.0 18.0 22.0 18.0 18.0 61.0 10</span></a> <a class="sourceLine" id="cb2-12" title="12"><span class="co"># as.mo("sau") 18.0 18.0 22 18.0 18.0 61 10</span></a>
<a class="sourceLine" id="cb2-13" title="13"><span class="co"># as.mo("stau") 66.0 66.0 75.0 66.0 68.0 110.0 10</span></a> <a class="sourceLine" id="cb2-13" title="13"><span class="co"># as.mo("stau") 65.0 65.0 70 66.0 66.0 110 10</span></a>
<a class="sourceLine" id="cb2-14" title="14"><span class="co"># as.mo("staaur") 17.0 18.0 18.0 18.0 18.0 18.0 10</span></a> <a class="sourceLine" id="cb2-14" title="14"><span class="co"># as.mo("staaur") 18.0 18.0 33 18.0 62.0 81 10</span></a>
<a class="sourceLine" id="cb2-15" title="15"><span class="co"># as.mo("STAAUR") 18.0 18.0 32.0 18.0 54.0 80.0 10</span></a> <a class="sourceLine" id="cb2-15" title="15"><span class="co"># as.mo("STAAUR") 18.0 18.0 18 18.0 18.0 19 10</span></a>
<a class="sourceLine" id="cb2-16" title="16"><span class="co"># as.mo("S. aureus") 52.0 53.0 57.0 53.0 53.0 96.0 10</span></a> <a class="sourceLine" id="cb2-16" title="16"><span class="co"># as.mo("S. aureus") 52.0 52.0 61 52.0 53.0 97 10</span></a>
<a class="sourceLine" id="cb2-17" title="17"><span class="co"># as.mo("S. aureus") 52.0 53.0 78.0 53.0 110.0 150.0 10</span></a> <a class="sourceLine" id="cb2-17" title="17"><span class="co"># as.mo("S. aureus") 52.0 52.0 71 53.0 97.0 150 10</span></a>
<a class="sourceLine" id="cb2-18" title="18"><span class="co"># as.mo("Staphylococcus aureus") 8.1 8.1 8.2 8.2 8.2 8.3 10</span></a></code></pre></div> <a class="sourceLine" id="cb2-18" title="18"><span class="co"># as.mo("Staphylococcus aureus") 8.1 8.1 14 8.1 8.2 63 10</span></a></code></pre></div>
<p>In the table above, all measurements are shown in milliseconds (thousands of seconds). A value of 5 milliseconds means it can determine 200 input values per second. It case of 100 milliseconds, this is only 10 input values per second. The second input is the only one that has to be looked up thoroughly. All the others are known codes (the first one is a WHONET code) or common laboratory codes, or common full organism names like the last one. Full organism names are always preferred.</p> <p>In the table above, all measurements are shown in milliseconds (thousands of seconds). A value of 5 milliseconds means it can determine 200 input values per second. It case of 100 milliseconds, this is only 10 input values per second. The second input is the only one that has to be looked up thoroughly. All the others are known codes (the first one is a WHONET code) or common laboratory codes, or common full organism names like the last one. Full organism names are always preferred.</p>
<p>To achieve this speed, the <code>as.mo</code> function also takes into account the prevalence of human pathogenic microorganisms. The downside is of course that less prevalent microorganisms will be determined less fast. See this example for the ID of <em>Thermus islandicus</em> (<code>B_THERMS_ISL</code>), a bug probably never found before in humans:</p> <p>To achieve this speed, the <code>as.mo</code> function also takes into account the prevalence of human pathogenic microorganisms. The downside is of course that less prevalent microorganisms will be determined less fast. See this example for the ID of <em>Thermus islandicus</em> (<code>B_THERMS_ISL</code>), a bug probably never found before in humans:</p>
<div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb3-1" title="1">T.islandicus &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/microbenchmark/topics/microbenchmark">microbenchmark</a></span>(<span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"theisl"</span>),</a> <div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb3-1" title="1">T.islandicus &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/microbenchmark/topics/microbenchmark">microbenchmark</a></span>(<span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"theisl"</span>),</a>
@@ -237,10 +237,10 @@
<a class="sourceLine" id="cb3-8" title="8"><span class="co"># Unit: milliseconds</span></a> <a class="sourceLine" id="cb3-8" title="8"><span class="co"># Unit: milliseconds</span></a>
<a class="sourceLine" id="cb3-9" title="9"><span class="co"># expr min lq mean median uq max neval</span></a> <a class="sourceLine" id="cb3-9" title="9"><span class="co"># expr min lq mean median uq max neval</span></a>
<a class="sourceLine" id="cb3-10" title="10"><span class="co"># as.mo("theisl") 390 390 420 440 440 440 10</span></a> <a class="sourceLine" id="cb3-10" title="10"><span class="co"># as.mo("theisl") 390 390 420 440 440 440 10</span></a>
<a class="sourceLine" id="cb3-11" title="11"><span class="co"># as.mo("THEISL") 390 390 420 440 440 450 10</span></a> <a class="sourceLine" id="cb3-11" title="11"><span class="co"># as.mo("THEISL") 390 390 410 400 440 440 10</span></a>
<a class="sourceLine" id="cb3-12" title="12"><span class="co"># as.mo("T. islandicus") 210 250 250 250 260 270 10</span></a> <a class="sourceLine" id="cb3-12" title="12"><span class="co"># as.mo("T. islandicus") 210 210 230 220 250 270 10</span></a>
<a class="sourceLine" id="cb3-13" title="13"><span class="co"># as.mo("T. islandicus") 210 210 240 220 250 410 10</span></a> <a class="sourceLine" id="cb3-13" title="13"><span class="co"># as.mo("T. islandicus") 210 210 240 260 260 280 10</span></a>
<a class="sourceLine" id="cb3-14" title="14"><span class="co"># as.mo("Thermus islandicus") 72 72 82 72 73 120 10</span></a></code></pre></div> <a class="sourceLine" id="cb3-14" title="14"><span class="co"># as.mo("Thermus islandicus") 72 72 92 73 120 130 10</span></a></code></pre></div>
<p>That takes 6.8 times as much time on average. A value of 100 milliseconds means it can only determine ~10 different input values per second. We can conclude that looking up arbitrary codes of less prevalent microorganisms is the worst way to go, in terms of calculation performance. Full names (like <em>Thermus islandicus</em>) are almost fast - these are the most probable input from most data sets.</p> <p>That takes 6.8 times as much time on average. A value of 100 milliseconds means it can only determine ~10 different input values per second. We can conclude that looking up arbitrary codes of less prevalent microorganisms is the worst way to go, in terms of calculation performance. Full names (like <em>Thermus islandicus</em>) are almost fast - these are the most probable input from most data sets.</p>
<p>In the figure below, we compare <em>Escherichia coli</em> (which is very common) with <em>Prevotella brevis</em> (which is moderately common) and with <em>Thermus islandicus</em> (which is very uncommon):</p> <p>In the figure below, we compare <em>Escherichia coli</em> (which is very common) with <em>Prevotella brevis</em> (which is moderately common) and with <em>Thermus islandicus</em> (which is very uncommon):</p>
<div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb4-1" title="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/par">par</a></span>(<span class="dt">mar =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="dv">5</span>, <span class="dv">16</span>, <span class="dv">4</span>, <span class="dv">2</span>)) <span class="co"># set more space for left margin text (16)</span></a> <div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb4-1" title="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/par">par</a></span>(<span class="dt">mar =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="dv">5</span>, <span class="dv">16</span>, <span class="dv">4</span>, <span class="dv">2</span>)) <span class="co"># set more space for left margin text (16)</span></a>
@@ -287,8 +287,8 @@
<a class="sourceLine" id="cb5-24" title="24"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(run_it, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">3</span>)</a> <a class="sourceLine" id="cb5-24" title="24"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(run_it, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">3</span>)</a>
<a class="sourceLine" id="cb5-25" title="25"><span class="co"># Unit: milliseconds</span></a> <a class="sourceLine" id="cb5-25" title="25"><span class="co"># Unit: milliseconds</span></a>
<a class="sourceLine" id="cb5-26" title="26"><span class="co"># expr min lq mean median uq max neval</span></a> <a class="sourceLine" id="cb5-26" title="26"><span class="co"># expr min lq mean median uq max neval</span></a>
<a class="sourceLine" id="cb5-27" title="27"><span class="co"># mo_fullname(x) 1120 1140 1190 1180 1210 1260 10</span></a></code></pre></div> <a class="sourceLine" id="cb5-27" title="27"><span class="co"># mo_fullname(x) 1050 1050 1100 1090 1120 1230 10</span></a></code></pre></div>
<p>So transforming 500,000 values (!!) of 50 unique values only takes 1.18 seconds (1182 ms). You only lose time on your unique input values.</p> <p>So transforming 500,000 values (!!) of 50 unique values only takes 1.09 seconds (1092 ms). You only lose time on your unique input values.</p>
</div> </div>
<div id="precalculated-results" class="section level3"> <div id="precalculated-results" class="section level3">
<h3 class="hasAnchor"> <h3 class="hasAnchor">
@@ -300,11 +300,11 @@
<a class="sourceLine" id="cb6-4" title="4"> <span class="dt">times =</span> <span class="dv">10</span>)</a> <a class="sourceLine" id="cb6-4" title="4"> <span class="dt">times =</span> <span class="dv">10</span>)</a>
<a class="sourceLine" id="cb6-5" title="5"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(run_it, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">3</span>)</a> <a class="sourceLine" id="cb6-5" title="5"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(run_it, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">3</span>)</a>
<a class="sourceLine" id="cb6-6" title="6"><span class="co"># Unit: milliseconds</span></a> <a class="sourceLine" id="cb6-6" title="6"><span class="co"># Unit: milliseconds</span></a>
<a class="sourceLine" id="cb6-7" title="7"><span class="co"># expr min lq mean median uq max neval</span></a> <a class="sourceLine" id="cb6-7" title="7"><span class="co"># expr min lq mean median uq max neval</span></a>
<a class="sourceLine" id="cb6-8" title="8"><span class="co"># A 12.90 13.1 18.50 13.60 13.90 63.60 10</span></a> <a class="sourceLine" id="cb6-8" title="8"><span class="co"># A 13.00 13.20 13.60 13.60 14.00 14.40 10</span></a>
<a class="sourceLine" id="cb6-9" title="9"><span class="co"># B 49.90 50.1 52.20 51.10 52.20 62.60 10</span></a> <a class="sourceLine" id="cb6-9" title="9"><span class="co"># B 49.40 50.00 57.50 51.90 52.40 103.00 10</span></a>
<a class="sourceLine" id="cb6-10" title="10"><span class="co"># C 1.49 1.7 1.76 1.73 1.96 1.98 10</span></a></code></pre></div> <a class="sourceLine" id="cb6-10" title="10"><span class="co"># C 1.52 1.72 1.81 1.78 1.98 1.99 10</span></a></code></pre></div>
<p>So going from <code><a href="../reference/mo_property.html">mo_fullname("Staphylococcus aureus")</a></code> to <code>"Staphylococcus aureus"</code> takes 0.0017 seconds - it doesnt even start calculating <em>if the result would be the same as the expected resulting value</em>. That goes for all helper functions:</p> <p>So going from <code><a href="../reference/mo_property.html">mo_fullname("Staphylococcus aureus")</a></code> to <code>"Staphylococcus aureus"</code> takes 0.0018 seconds - it doesnt even start calculating <em>if the result would be the same as the expected resulting value</em>. That goes for all helper functions:</p>
<div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb7-1" title="1">run_it &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/microbenchmark/topics/microbenchmark">microbenchmark</a></span>(<span class="dt">A =</span> <span class="kw"><a href="../reference/mo_property.html">mo_species</a></span>(<span class="st">"aureus"</span>),</a> <div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb7-1" title="1">run_it &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/microbenchmark/topics/microbenchmark">microbenchmark</a></span>(<span class="dt">A =</span> <span class="kw"><a href="../reference/mo_property.html">mo_species</a></span>(<span class="st">"aureus"</span>),</a>
<a class="sourceLine" id="cb7-2" title="2"> <span class="dt">B =</span> <span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(<span class="st">"Staphylococcus"</span>),</a> <a class="sourceLine" id="cb7-2" title="2"> <span class="dt">B =</span> <span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(<span class="st">"Staphylococcus"</span>),</a>
<a class="sourceLine" id="cb7-3" title="3"> <span class="dt">C =</span> <span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"Staphylococcus aureus"</span>),</a> <a class="sourceLine" id="cb7-3" title="3"> <span class="dt">C =</span> <span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"Staphylococcus aureus"</span>),</a>
@@ -317,14 +317,14 @@
<a class="sourceLine" id="cb7-10" title="10"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(run_it, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">3</span>)</a> <a class="sourceLine" id="cb7-10" title="10"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(run_it, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">3</span>)</a>
<a class="sourceLine" id="cb7-11" title="11"><span class="co"># Unit: milliseconds</span></a> <a class="sourceLine" id="cb7-11" title="11"><span class="co"># Unit: milliseconds</span></a>
<a class="sourceLine" id="cb7-12" title="12"><span class="co"># expr min lq mean median uq max neval</span></a> <a class="sourceLine" id="cb7-12" title="12"><span class="co"># expr min lq mean median uq max neval</span></a>
<a class="sourceLine" id="cb7-13" title="13"><span class="co"># A 0.518 0.544 0.630 0.620 0.683 0.752 10</span></a> <a class="sourceLine" id="cb7-13" title="13"><span class="co"># A 0.612 0.623 0.685 0.653 0.789 0.814 10</span></a>
<a class="sourceLine" id="cb7-14" title="14"><span class="co"># B 0.548 0.650 0.695 0.703 0.728 0.855 10</span></a> <a class="sourceLine" id="cb7-14" title="14"><span class="co"># B 0.556 0.575 0.680 0.671 0.689 0.958 10</span></a>
<a class="sourceLine" id="cb7-15" title="15"><span class="co"># C 1.530 1.600 1.750 1.780 1.880 1.950 10</span></a> <a class="sourceLine" id="cb7-15" title="15"><span class="co"># C 1.520 1.710 1.800 1.820 1.950 1.970 10</span></a>
<a class="sourceLine" id="cb7-16" title="16"><span class="co"># D 0.541 0.640 0.690 0.665 0.728 0.857 10</span></a> <a class="sourceLine" id="cb7-16" title="16"><span class="co"># D 0.547 0.665 0.723 0.688 0.811 0.997 10</span></a>
<a class="sourceLine" id="cb7-17" title="17"><span class="co"># E 0.496 0.545 0.610 0.612 0.680 0.754 10</span></a> <a class="sourceLine" id="cb7-17" title="17"><span class="co"># E 0.490 0.541 0.633 0.629 0.748 0.756 10</span></a>
<a class="sourceLine" id="cb7-18" title="18"><span class="co"># F 0.523 0.547 0.613 0.580 0.701 0.756 10</span></a> <a class="sourceLine" id="cb7-18" title="18"><span class="co"># F 0.482 0.569 0.612 0.590 0.663 0.756 10</span></a>
<a class="sourceLine" id="cb7-19" title="19"><span class="co"># G 0.528 0.547 0.586 0.568 0.600 0.743 10</span></a> <a class="sourceLine" id="cb7-19" title="19"><span class="co"># G 0.551 0.558 0.601 0.586 0.632 0.735 10</span></a>
<a class="sourceLine" id="cb7-20" title="20"><span class="co"># H 0.547 0.553 0.634 0.609 0.670 0.864 10</span></a></code></pre></div> <a class="sourceLine" id="cb7-20" title="20"><span class="co"># H 0.494 0.564 0.595 0.575 0.608 0.757 10</span></a></code></pre></div>
<p>Of course, when running <code><a href="../reference/mo_property.html">mo_phylum("Firmicutes")</a></code> the function has zero knowledge about the actual microorganism, namely <em>S. aureus</em>. But since the result would be <code>"Firmicutes"</code> too, there is no point in calculating the result. And because this package knows all phyla of all known bacteria (according to the Catalogue of Life), it can just return the initial value immediately.</p> <p>Of course, when running <code><a href="../reference/mo_property.html">mo_phylum("Firmicutes")</a></code> the function has zero knowledge about the actual microorganism, namely <em>S. aureus</em>. But since the result would be <code>"Firmicutes"</code> too, there is no point in calculating the result. And because this package knows all phyla of all known bacteria (according to the Catalogue of Life), it can just return the initial value immediately.</p>
</div> </div>
<div id="results-in-other-languages" class="section level3"> <div id="results-in-other-languages" class="section level3">
@@ -351,13 +351,13 @@
<a class="sourceLine" id="cb8-18" title="18"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(run_it, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">4</span>)</a> <a class="sourceLine" id="cb8-18" title="18"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(run_it, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">4</span>)</a>
<a class="sourceLine" id="cb8-19" title="19"><span class="co"># Unit: milliseconds</span></a> <a class="sourceLine" id="cb8-19" title="19"><span class="co"># Unit: milliseconds</span></a>
<a class="sourceLine" id="cb8-20" title="20"><span class="co"># expr min lq mean median uq max neval</span></a> <a class="sourceLine" id="cb8-20" title="20"><span class="co"># expr min lq mean median uq max neval</span></a>
<a class="sourceLine" id="cb8-21" title="21"><span class="co"># en 43.34 43.72 43.76 43.82 43.93 43.98 10</span></a> <a class="sourceLine" id="cb8-21" title="21"><span class="co"># en 43.00 43.12 45.51 44.82 44.89 56.61 10</span></a>
<a class="sourceLine" id="cb8-22" title="22"><span class="co"># de 45.77 45.82 46.40 45.90 46.21 50.16 10</span></a> <a class="sourceLine" id="cb8-22" title="22"><span class="co"># de 46.47 46.99 52.11 47.57 48.11 93.77 10</span></a>
<a class="sourceLine" id="cb8-23" title="23"><span class="co"># nl 59.12 59.39 60.61 59.81 60.97 65.36 10</span></a> <a class="sourceLine" id="cb8-23" title="23"><span class="co"># nl 60.86 62.72 67.57 63.69 63.99 108.20 10</span></a>
<a class="sourceLine" id="cb8-24" title="24"><span class="co"># es 45.35 45.70 55.58 46.30 50.91 90.30 10</span></a> <a class="sourceLine" id="cb8-24" title="24"><span class="co"># es 45.74 46.05 52.37 46.42 47.98 103.00 10</span></a>
<a class="sourceLine" id="cb8-25" title="25"><span class="co"># it 45.54 45.72 47.36 46.02 46.23 57.97 10</span></a> <a class="sourceLine" id="cb8-25" title="25"><span class="co"># it 45.84 45.89 51.90 47.66 47.73 94.83 10</span></a>
<a class="sourceLine" id="cb8-26" title="26"><span class="co"># fr 45.44 45.68 55.49 45.91 46.30 97.86 10</span></a> <a class="sourceLine" id="cb8-26" title="26"><span class="co"># fr 45.97 46.92 47.44 47.76 47.86 48.49 10</span></a>
<a class="sourceLine" id="cb8-27" title="27"><span class="co"># pt 45.60 45.68 52.57 45.79 46.17 110.10 10</span></a></code></pre></div> <a class="sourceLine" id="cb8-27" title="27"><span class="co"># pt 45.93 46.77 47.36 47.77 47.93 48.12 10</span></a></code></pre></div>
<p>Currently supported are German, Dutch, Spanish, Italian, French and Portuguese.</p> <p>Currently supported are German, Dutch, Spanish, Italian, French and Portuguese.</p>
</div> </div>
</div> </div>

Binary file not shown.

Before

Width:  |  Height:  |  Size: 26 KiB

After

Width:  |  Height:  |  Size: 26 KiB

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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>
@@ -192,7 +192,7 @@
<h1>How to create frequency tables</h1> <h1>How to create frequency tables</h1>
<h4 class="author">Matthijs S. Berends</h4> <h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">23 June 2019</h4> <h4 class="date">01 July 2019</h4>
<div class="hidden name"><code>freq.Rmd</code></div> <div class="hidden name"><code>freq.Rmd</code></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="Latest development version">0.7.1.9004</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>
@@ -192,7 +192,7 @@
<h1>How to predict antimicrobial resistance</h1> <h1>How to predict antimicrobial resistance</h1>
<h4 class="author">Matthijs S. Berends</h4> <h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">23 June 2019</h4> <h4 class="date">01 July 2019</h4>
<div class="hidden name"><code>resistance_predict.Rmd</code></div> <div class="hidden name"><code>resistance_predict.Rmd</code></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="Latest development version">0.7.1.9004</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9004</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9004</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>
@@ -232,10 +232,43 @@
</div> </div>
<div id="amr-0719004" class="section level1"> <div id="amr-0719005" class="section level1">
<h1 class="page-header"> <h1 class="page-header">
<a href="#amr-0719004" class="anchor"></a>AMR 0.7.1.9004<small> Unreleased </small> <a href="#amr-0719005" class="anchor"></a>AMR 0.7.1.9005<small> Unreleased </small>
</h1> </h1>
<div id="new" class="section level3">
<h3 class="hasAnchor">
<a href="#new" class="anchor"></a>New</h3>
<ul>
<li>
<p>Additional way to calculate co-resistance, i.e. when using multiple antibiotics as input for <code>portion_*</code> functions or <code>count_*</code> functions. This can be used to determine the empiric susceptibily of a combination therapy. A new parameter <code>only_all_tested</code> replaces the old <code>also_single_tested</code> and can be used to select one of the two methods to count isolates and calculate portions. The difference can be seen in this example table (which is also on the <code>portion</code> and <code>count</code> help pages), where the %SI is being determined:</p>
<div class="sourceCode" id="cb1"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb1-1" title="1"><span class="co"># -------------------------------------------------------------------------</span></a>
<a class="sourceLine" id="cb1-2" title="2"><span class="co"># only_all_tested = FALSE only_all_tested = TRUE</span></a>
<a class="sourceLine" id="cb1-3" title="3"><span class="co"># Antibiotic Antibiotic ----------------------- -----------------------</span></a>
<a class="sourceLine" id="cb1-4" title="4"><span class="co"># A B include as include as include as include as</span></a>
<a class="sourceLine" id="cb1-5" title="5"><span class="co"># numerator denominator numerator denominator</span></a>
<a class="sourceLine" id="cb1-6" title="6"><span class="co"># ---------- ---------- ---------- ----------- ---------- -----------</span></a>
<a class="sourceLine" id="cb1-7" title="7"><span class="co"># S S X X X X</span></a>
<a class="sourceLine" id="cb1-8" title="8"><span class="co"># I S X X X X</span></a>
<a class="sourceLine" id="cb1-9" title="9"><span class="co"># R S X X X X</span></a>
<a class="sourceLine" id="cb1-10" title="10"><span class="co"># not tested S X X - -</span></a>
<a class="sourceLine" id="cb1-11" title="11"><span class="co"># S I X X X X</span></a>
<a class="sourceLine" id="cb1-12" title="12"><span class="co"># I I X X X X</span></a>
<a class="sourceLine" id="cb1-13" title="13"><span class="co"># R I X X X X</span></a>
<a class="sourceLine" id="cb1-14" title="14"><span class="co"># not tested I X X - -</span></a>
<a class="sourceLine" id="cb1-15" title="15"><span class="co"># S R X X X X</span></a>
<a class="sourceLine" id="cb1-16" title="16"><span class="co"># I R X X X X</span></a>
<a class="sourceLine" id="cb1-17" title="17"><span class="co"># R R - X - X</span></a>
<a class="sourceLine" id="cb1-18" title="18"><span class="co"># not tested R - - - -</span></a>
<a class="sourceLine" id="cb1-19" title="19"><span class="co"># S not tested X X - -</span></a>
<a class="sourceLine" id="cb1-20" title="20"><span class="co"># I not tested X X - -</span></a>
<a class="sourceLine" id="cb1-21" title="21"><span class="co"># R not tested - - - -</span></a>
<a class="sourceLine" id="cb1-22" title="22"><span class="co"># not tested not tested - - - -</span></a>
<a class="sourceLine" id="cb1-23" title="23"><span class="co"># -------------------------------------------------------------------------</span></a></code></pre></div>
<p>Since this is a major change, usage of the old <code>also_single_tested</code> will throw an informative error that it has been replaced by <code>only_all_tested</code>.</p>
</li>
</ul>
</div>
<div id="changed" class="section level3"> <div id="changed" class="section level3">
<h3 class="hasAnchor"> <h3 class="hasAnchor">
<a href="#changed" class="anchor"></a>Changed</h3> <a href="#changed" class="anchor"></a>Changed</h3>
@@ -246,7 +279,7 @@
<li>Fix and speed improvement for <code><a href="../reference/mo_property.html">mo_shortname()</a></code> <li>Fix and speed improvement for <code><a href="../reference/mo_property.html">mo_shortname()</a></code>
</li> </li>
<li>Fix for <code><a href="../reference/as.mo.html">as.mo()</a></code> where misspelled input would not be understood</li> <li>Fix for <code><a href="../reference/as.mo.html">as.mo()</a></code> where misspelled input would not be understood</li>
<li>Fix for <code>also_single_tested</code> parameter in <code>count_*</code> functions</li> <li>Fix for using <code>mo_*</code> functions where the coercion uncertainties and failures would not be available through <code><a href="../reference/as.mo.html">mo_uncertainties()</a></code> and <code><a href="../reference/as.mo.html">mo_failures()</a></code> anymore</li>
</ul> </ul>
</div> </div>
</div> </div>
@@ -254,20 +287,20 @@
<h1 class="page-header"> <h1 class="page-header">
<a href="#amr-071" class="anchor"></a>AMR 0.7.1<small> 2019-06-23 </small> <a href="#amr-071" class="anchor"></a>AMR 0.7.1<small> 2019-06-23 </small>
</h1> </h1>
<div id="new" class="section level4"> <div id="new-1" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#new" class="anchor"></a>New</h4> <a href="#new-1" class="anchor"></a>New</h4>
<ul> <ul>
<li> <li>
<p>Function <code><a href="../reference/portion.html">rsi_df()</a></code> to transform a <code>data.frame</code> to a data set containing only the microbial interpretation (S, I, R), the antibiotic, the percentage of S/I/R and the number of available isolates. This is a convenient combination of the existing functions <code><a href="../reference/count.html">count_df()</a></code> and <code><a href="../reference/portion.html">portion_df()</a></code> to immediately show resistance percentages and number of available isolates:</p> <p>Function <code><a href="../reference/portion.html">rsi_df()</a></code> to transform a <code>data.frame</code> to a data set containing only the microbial interpretation (S, I, R), the antibiotic, the percentage of S/I/R and the number of available isolates. This is a convenient combination of the existing functions <code><a href="../reference/count.html">count_df()</a></code> and <code><a href="../reference/portion.html">portion_df()</a></code> to immediately show resistance percentages and number of available isolates:</p>
<div class="sourceCode" id="cb1"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb1-1" title="1">septic_patients <span class="op">%&gt;%</span></a> <div class="sourceCode" id="cb2"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb2-1" title="1">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb1-2" title="2"><span class="st"> </span><span class="kw">select</span>(AMX, CIP) <span class="op">%&gt;%</span></a> <a class="sourceLine" id="cb2-2" title="2"><span class="st"> </span><span class="kw">select</span>(AMX, CIP) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb1-3" title="3"><span class="st"> </span><span class="kw"><a href="../reference/portion.html">rsi_df</a></span>()</a> <a class="sourceLine" id="cb2-3" title="3"><span class="st"> </span><span class="kw"><a href="../reference/portion.html">rsi_df</a></span>()</a>
<a class="sourceLine" id="cb1-4" title="4"><span class="co"># antibiotic interpretation value isolates</span></a> <a class="sourceLine" id="cb2-4" title="4"><span class="co"># antibiotic interpretation value isolates</span></a>
<a class="sourceLine" id="cb1-5" title="5"><span class="co"># 1 Amoxicillin SI 0.4442636 546</span></a> <a class="sourceLine" id="cb2-5" title="5"><span class="co"># 1 Amoxicillin SI 0.4442636 546</span></a>
<a class="sourceLine" id="cb1-6" title="6"><span class="co"># 2 Amoxicillin R 0.5557364 683</span></a> <a class="sourceLine" id="cb2-6" title="6"><span class="co"># 2 Amoxicillin R 0.5557364 683</span></a>
<a class="sourceLine" id="cb1-7" title="7"><span class="co"># 3 Ciprofloxacin SI 0.8381831 1181</span></a> <a class="sourceLine" id="cb2-7" title="7"><span class="co"># 3 Ciprofloxacin SI 0.8381831 1181</span></a>
<a class="sourceLine" id="cb1-8" title="8"><span class="co"># 4 Ciprofloxacin R 0.1618169 228</span></a></code></pre></div> <a class="sourceLine" id="cb2-8" title="8"><span class="co"># 4 Ciprofloxacin R 0.1618169 228</span></a></code></pre></div>
</li> </li>
<li> <li>
<p>Support for all scientifically published pathotypes of <em>E. coli</em> to date (that we could find). Supported are:</p> <p>Support for all scientifically published pathotypes of <em>E. coli</em> to date (that we could find). Supported are:</p>
@@ -285,12 +318,12 @@
<li>UPEC (Uropathogenic <em>E. coli</em>)</li> <li>UPEC (Uropathogenic <em>E. coli</em>)</li>
</ul> </ul>
<p>All these lead to the microbial ID of <em>E. coli</em>:</p> <p>All these lead to the microbial ID of <em>E. coli</em>:</p>
<div class="sourceCode" id="cb2"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb2-1" title="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"UPEC"</span>)</a> <div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb3-1" title="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"UPEC"</span>)</a>
<a class="sourceLine" id="cb2-2" title="2"><span class="co"># B_ESCHR_COL</span></a> <a class="sourceLine" id="cb3-2" title="2"><span class="co"># B_ESCHR_COL</span></a>
<a class="sourceLine" id="cb2-3" title="3"><span class="kw"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="st">"UPEC"</span>)</a> <a class="sourceLine" id="cb3-3" title="3"><span class="kw"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="st">"UPEC"</span>)</a>
<a class="sourceLine" id="cb2-4" title="4"><span class="co"># "Escherichia coli"</span></a> <a class="sourceLine" id="cb3-4" title="4"><span class="co"># "Escherichia coli"</span></a>
<a class="sourceLine" id="cb2-5" title="5"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"EHEC"</span>)</a> <a class="sourceLine" id="cb3-5" title="5"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"EHEC"</span>)</a>
<a class="sourceLine" id="cb2-6" title="6"><span class="co"># "Gram-negative"</span></a></code></pre></div> <a class="sourceLine" id="cb3-6" title="6"><span class="co"># "Gram-negative"</span></a></code></pre></div>
</li> </li>
<li>Function <code><a href="../reference/mo_property.html">mo_info()</a></code> as an analogy to <code><a href="../reference/ab_property.html">ab_info()</a></code>. The <code><a href="../reference/mo_property.html">mo_info()</a></code> prints a list with the full taxonomy, authors, and the URL to the online database of a microorganism</li> <li>Function <code><a href="../reference/mo_property.html">mo_info()</a></code> as an analogy to <code><a href="../reference/ab_property.html">ab_info()</a></code>. The <code><a href="../reference/mo_property.html">mo_info()</a></code> prints a list with the full taxonomy, authors, and the URL to the online database of a microorganism</li>
<li><p>Function <code><a href="../reference/mo_property.html">mo_synonyms()</a></code> to get all previously accepted taxonomic names of a microorganism</p></li> <li><p>Function <code><a href="../reference/mo_property.html">mo_synonyms()</a></code> to get all previously accepted taxonomic names of a microorganism</p></li>
@@ -335,9 +368,9 @@
<h1 class="page-header"> <h1 class="page-header">
<a href="#amr-070" class="anchor"></a>AMR 0.7.0<small> 2019-06-03 </small> <a href="#amr-070" class="anchor"></a>AMR 0.7.0<small> 2019-06-03 </small>
</h1> </h1>
<div id="new-1" class="section level4"> <div id="new-2" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#new-1" class="anchor"></a>New</h4> <a href="#new-2" class="anchor"></a>New</h4>
<ul> <ul>
<li>Support for translation of disk diffusion and MIC values to RSI values (i.e. antimicrobial interpretations). Supported guidelines are EUCAST (2011 to 2019) and CLSI (2011 to 2019). Use <code><a href="../reference/as.rsi.html">as.rsi()</a></code> on an MIC value (created with <code><a href="../reference/as.mic.html">as.mic()</a></code>), a disk diffusion value (created with the new <code><a href="../reference/as.disk.html">as.disk()</a></code>) or on a complete date set containing columns with MIC or disk diffusion values.</li> <li>Support for translation of disk diffusion and MIC values to RSI values (i.e. antimicrobial interpretations). Supported guidelines are EUCAST (2011 to 2019) and CLSI (2011 to 2019). Use <code><a href="../reference/as.rsi.html">as.rsi()</a></code> on an MIC value (created with <code><a href="../reference/as.mic.html">as.mic()</a></code>), a disk diffusion value (created with the new <code><a href="../reference/as.disk.html">as.disk()</a></code>) or on a complete date set containing columns with MIC or disk diffusion values.</li>
<li>Function <code><a href="../reference/mo_property.html">mo_name()</a></code> as alias of <code><a href="../reference/mo_property.html">mo_fullname()</a></code> <li>Function <code><a href="../reference/mo_property.html">mo_name()</a></code> as alias of <code><a href="../reference/mo_property.html">mo_fullname()</a></code>
@@ -389,14 +422,14 @@ Please <a href="https://gitlab.com/msberends/AMR/issues/new?issue%5Btitle%5D=Tra
<li>when all values are unique it now shows a message instead of a warning</li> <li>when all values are unique it now shows a message instead of a warning</li>
<li> <li>
<p>support for boxplots:</p> <p>support for boxplots:</p>
<div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb3-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a> <div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb4-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb3-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age) <span class="op">%&gt;%</span><span class="st"> </span></a> <a class="sourceLine" id="cb4-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb3-3" title="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/boxplot">boxplot</a></span>()</a> <a class="sourceLine" id="cb4-3" title="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/boxplot">boxplot</a></span>()</a>
<a class="sourceLine" id="cb3-4" title="4"><span class="co"># grouped boxplots:</span></a> <a class="sourceLine" id="cb4-4" title="4"><span class="co"># grouped boxplots:</span></a>
<a class="sourceLine" id="cb3-5" title="5">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a> <a class="sourceLine" id="cb4-5" title="5">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb3-6" title="6"><span class="st"> </span><span class="kw">group_by</span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a> <a class="sourceLine" id="cb4-6" title="6"><span class="st"> </span><span class="kw">group_by</span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb3-7" title="7"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age) <span class="op">%&gt;%</span></a> <a class="sourceLine" id="cb4-7" title="7"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb3-8" title="8"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/boxplot">boxplot</a></span>()</a></code></pre></div> <a class="sourceLine" id="cb4-8" title="8"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/boxplot">boxplot</a></span>()</a></code></pre></div>
</li> </li>
</ul> </ul>
</li> </li>
@@ -452,9 +485,9 @@ Please <a href="https://gitlab.com/msberends/AMR/issues/new?issue%5Btitle%5D=EUC
<li>Contains the complete manual of this package and all of its functions with an explanation of their parameters</li> <li>Contains the complete manual of this package and all of its functions with an explanation of their parameters</li>
<li>Contains a comprehensive tutorial about how to conduct antimicrobial resistance analysis, import data from WHONET or SPSS and many more.</li> <li>Contains a comprehensive tutorial about how to conduct antimicrobial resistance analysis, import data from WHONET or SPSS and many more.</li>
</ul> </ul>
<div id="new-2" class="section level4"> <div id="new-3" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#new-2" class="anchor"></a>New</h4> <a href="#new-3" class="anchor"></a>New</h4>
<ul> <ul>
<li> <li>
<strong>BREAKING</strong>: removed deprecated functions, parameters and references to bactid. Use <code><a href="../reference/as.mo.html">as.mo()</a></code> to identify an MO code.</li> <strong>BREAKING</strong>: removed deprecated functions, parameters and references to bactid. Use <code><a href="../reference/as.mo.html">as.mo()</a></code> to identify an MO code.</li>
@@ -481,32 +514,32 @@ This data is updated annually - check the included version with the new function
</li> </li>
<li> <li>
<p>New filters for antimicrobial classes. Use these functions to filter isolates on results in one of more antibiotics from a specific class:</p> <p>New filters for antimicrobial classes. Use these functions to filter isolates on results in one of more antibiotics from a specific class:</p>
<div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb4-1" title="1"><span class="kw"><a href="../reference/filter_ab_class.html">filter_aminoglycosides</a></span>()</a> <div class="sourceCode" id="cb5"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb5-1" title="1"><span class="kw"><a href="../reference/filter_ab_class.html">filter_aminoglycosides</a></span>()</a>
<a class="sourceLine" id="cb4-2" title="2"><span class="kw"><a href="../reference/filter_ab_class.html">filter_carbapenems</a></span>()</a> <a class="sourceLine" id="cb5-2" title="2"><span class="kw"><a href="../reference/filter_ab_class.html">filter_carbapenems</a></span>()</a>
<a class="sourceLine" id="cb4-3" title="3"><span class="kw"><a href="../reference/filter_ab_class.html">filter_cephalosporins</a></span>()</a> <a class="sourceLine" id="cb5-3" title="3"><span class="kw"><a href="../reference/filter_ab_class.html">filter_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb4-4" title="4"><span class="kw"><a href="../reference/filter_ab_class.html">filter_1st_cephalosporins</a></span>()</a> <a class="sourceLine" id="cb5-4" title="4"><span class="kw"><a href="../reference/filter_ab_class.html">filter_1st_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb4-5" title="5"><span class="kw"><a href="../reference/filter_ab_class.html">filter_2nd_cephalosporins</a></span>()</a> <a class="sourceLine" id="cb5-5" title="5"><span class="kw"><a href="../reference/filter_ab_class.html">filter_2nd_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb4-6" title="6"><span class="kw"><a href="../reference/filter_ab_class.html">filter_3rd_cephalosporins</a></span>()</a> <a class="sourceLine" id="cb5-6" title="6"><span class="kw"><a href="../reference/filter_ab_class.html">filter_3rd_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb4-7" title="7"><span class="kw"><a href="../reference/filter_ab_class.html">filter_4th_cephalosporins</a></span>()</a> <a class="sourceLine" id="cb5-7" title="7"><span class="kw"><a href="../reference/filter_ab_class.html">filter_4th_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb4-8" title="8"><span class="kw"><a href="../reference/filter_ab_class.html">filter_fluoroquinolones</a></span>()</a> <a class="sourceLine" id="cb5-8" title="8"><span class="kw"><a href="../reference/filter_ab_class.html">filter_fluoroquinolones</a></span>()</a>
<a class="sourceLine" id="cb4-9" title="9"><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>()</a> <a class="sourceLine" id="cb5-9" title="9"><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>()</a>
<a class="sourceLine" id="cb4-10" title="10"><span class="kw"><a href="../reference/filter_ab_class.html">filter_macrolides</a></span>()</a> <a class="sourceLine" id="cb5-10" title="10"><span class="kw"><a href="../reference/filter_ab_class.html">filter_macrolides</a></span>()</a>
<a class="sourceLine" id="cb4-11" title="11"><span class="kw"><a href="../reference/filter_ab_class.html">filter_tetracyclines</a></span>()</a></code></pre></div> <a class="sourceLine" id="cb5-11" title="11"><span class="kw"><a href="../reference/filter_ab_class.html">filter_tetracyclines</a></span>()</a></code></pre></div>
<p>The <code>antibiotics</code> data set will be searched, after which the input data will be checked for column names with a value in any abbreviations, codes or official names found in the <code>antibiotics</code> data set. For example:</p> <p>The <code>antibiotics</code> data set will be searched, after which the input data will be checked for column names with a value in any abbreviations, codes or official names found in the <code>antibiotics</code> data set. For example:</p>
<div class="sourceCode" id="cb5"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb5-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>(<span class="dt">result =</span> <span class="st">"R"</span>)</a> <div class="sourceCode" id="cb6"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb6-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>(<span class="dt">result =</span> <span class="st">"R"</span>)</a>
<a class="sourceLine" id="cb5-2" title="2"><span class="co"># Filtering on glycopeptide antibacterials: any of `vanc` or `teic` is R</span></a> <a class="sourceLine" id="cb6-2" title="2"><span class="co"># Filtering on glycopeptide antibacterials: any of `vanc` or `teic` is R</span></a>
<a class="sourceLine" id="cb5-3" title="3">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>(<span class="dt">result =</span> <span class="st">"R"</span>, <span class="dt">scope =</span> <span class="st">"all"</span>)</a> <a class="sourceLine" id="cb6-3" title="3">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>(<span class="dt">result =</span> <span class="st">"R"</span>, <span class="dt">scope =</span> <span class="st">"all"</span>)</a>
<a class="sourceLine" id="cb5-4" title="4"><span class="co"># Filtering on glycopeptide antibacterials: all of `vanc` and `teic` is R</span></a></code></pre></div> <a class="sourceLine" id="cb6-4" title="4"><span class="co"># Filtering on glycopeptide antibacterials: all of `vanc` and `teic` is R</span></a></code></pre></div>
</li> </li>
<li> <li>
<p>All <code>ab_*</code> functions are deprecated and replaced by <code>atc_*</code> functions:</p> <p>All <code>ab_*</code> functions are deprecated and replaced by <code>atc_*</code> functions:</p>
<div class="sourceCode" id="cb6"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb6-1" title="1">ab_property -&gt;<span class="st"> </span><span class="kw">atc_property</span>()</a> <div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb7-1" title="1">ab_property -&gt;<span class="st"> </span><span class="kw">atc_property</span>()</a>
<a class="sourceLine" id="cb6-2" title="2">ab_name -&gt;<span class="st"> </span><span class="kw">atc_name</span>()</a> <a class="sourceLine" id="cb7-2" title="2">ab_name -&gt;<span class="st"> </span><span class="kw">atc_name</span>()</a>
<a class="sourceLine" id="cb6-3" title="3">ab_official -&gt;<span class="st"> </span><span class="kw">atc_official</span>()</a> <a class="sourceLine" id="cb7-3" title="3">ab_official -&gt;<span class="st"> </span><span class="kw">atc_official</span>()</a>
<a class="sourceLine" id="cb6-4" title="4">ab_trivial_nl -&gt;<span class="st"> </span><span class="kw">atc_trivial_nl</span>()</a> <a class="sourceLine" id="cb7-4" title="4">ab_trivial_nl -&gt;<span class="st"> </span><span class="kw">atc_trivial_nl</span>()</a>
<a class="sourceLine" id="cb6-5" title="5">ab_certe -&gt;<span class="st"> </span><span class="kw">atc_certe</span>()</a> <a class="sourceLine" id="cb7-5" title="5">ab_certe -&gt;<span class="st"> </span><span class="kw">atc_certe</span>()</a>
<a class="sourceLine" id="cb6-6" title="6">ab_umcg -&gt;<span class="st"> </span><span class="kw">atc_umcg</span>()</a> <a class="sourceLine" id="cb7-6" title="6">ab_umcg -&gt;<span class="st"> </span><span class="kw">atc_umcg</span>()</a>
<a class="sourceLine" id="cb6-7" title="7">ab_tradenames -&gt;<span class="st"> </span><span class="kw">atc_tradenames</span>()</a></code></pre></div> <a class="sourceLine" id="cb7-7" title="7">ab_tradenames -&gt;<span class="st"> </span><span class="kw">atc_tradenames</span>()</a></code></pre></div>
These functions use <code><a href="../reference/AMR-deprecated.html">as.atc()</a></code> internally. The old <code>atc_property</code> has been renamed <code><a href="../reference/atc_online.html">atc_online_property()</a></code>. This is done for two reasons: firstly, not all ATC codes are of antibiotics (ab) but can also be of antivirals or antifungals. Secondly, the input must have class <code>atc</code> or must be coerable to this class. Properties of these classes should start with the same class name, analogous to <code><a href="../reference/as.mo.html">as.mo()</a></code> and e.g. <code>mo_genus</code>.</li> These functions use <code><a href="../reference/AMR-deprecated.html">as.atc()</a></code> internally. The old <code>atc_property</code> has been renamed <code><a href="../reference/atc_online.html">atc_online_property()</a></code>. This is done for two reasons: firstly, not all ATC codes are of antibiotics (ab) but can also be of antivirals or antifungals. Secondly, the input must have class <code>atc</code> or must be coerable to this class. Properties of these classes should start with the same class name, analogous to <code><a href="../reference/as.mo.html">as.mo()</a></code> and e.g. <code>mo_genus</code>.</li>
<li>New functions <code><a href="../reference/mo_source.html">set_mo_source()</a></code> and <code><a href="../reference/mo_source.html">get_mo_source()</a></code> to use your own predefined MO codes as input for <code><a href="../reference/as.mo.html">as.mo()</a></code> and consequently all <code>mo_*</code> functions</li> <li>New functions <code><a href="../reference/mo_source.html">set_mo_source()</a></code> and <code><a href="../reference/mo_source.html">get_mo_source()</a></code> to use your own predefined MO codes as input for <code><a href="../reference/as.mo.html">as.mo()</a></code> and consequently all <code>mo_*</code> functions</li>
<li>Support for the upcoming <a href="https://dplyr.tidyverse.org"><code>dplyr</code></a> version 0.8.0</li> <li>Support for the upcoming <a href="https://dplyr.tidyverse.org"><code>dplyr</code></a> version 0.8.0</li>
@@ -518,20 +551,20 @@ These functions use <code><a href="../reference/AMR-deprecated.html">as.atc()</a
<li>New function <code><a href="../reference/age_groups.html">age_groups()</a></code> to split ages into custom or predefined groups (like children or elderly). This allows for easier demographic antimicrobial resistance analysis per age group.</li> <li>New function <code><a href="../reference/age_groups.html">age_groups()</a></code> to split ages into custom or predefined groups (like children or elderly). This allows for easier demographic antimicrobial resistance analysis per age group.</li>
<li> <li>
<p>New function <code><a href="../reference/resistance_predict.html">ggplot_rsi_predict()</a></code> as well as the base R <code><a href="https://www.rdocumentation.org/packages/graphics/topics/plot">plot()</a></code> function can now be used for resistance prediction calculated with <code><a href="../reference/resistance_predict.html">resistance_predict()</a></code>:</p> <p>New function <code><a href="../reference/resistance_predict.html">ggplot_rsi_predict()</a></code> as well as the base R <code><a href="https://www.rdocumentation.org/packages/graphics/topics/plot">plot()</a></code> function can now be used for resistance prediction calculated with <code><a href="../reference/resistance_predict.html">resistance_predict()</a></code>:</p>
<div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb7-1" title="1">x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/resistance_predict.html">resistance_predict</a></span>(septic_patients, <span class="dt">col_ab =</span> <span class="st">"amox"</span>)</a> <div class="sourceCode" id="cb8"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb8-1" title="1">x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/resistance_predict.html">resistance_predict</a></span>(septic_patients, <span class="dt">col_ab =</span> <span class="st">"amox"</span>)</a>
<a class="sourceLine" id="cb7-2" title="2"><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/plot">plot</a></span>(x)</a> <a class="sourceLine" id="cb8-2" title="2"><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/plot">plot</a></span>(x)</a>
<a class="sourceLine" id="cb7-3" title="3"><span class="kw"><a href="../reference/resistance_predict.html">ggplot_rsi_predict</a></span>(x)</a></code></pre></div> <a class="sourceLine" id="cb8-3" title="3"><span class="kw"><a href="../reference/resistance_predict.html">ggplot_rsi_predict</a></span>(x)</a></code></pre></div>
</li> </li>
<li> <li>
<p>Functions <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> and <code><a href="../reference/first_isolate.html">filter_first_weighted_isolate()</a></code> to shorten and fasten filtering on data sets with antimicrobial results, e.g.:</p> <p>Functions <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> and <code><a href="../reference/first_isolate.html">filter_first_weighted_isolate()</a></code> to shorten and fasten filtering on data sets with antimicrobial results, e.g.:</p>
<div class="sourceCode" id="cb8"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb8-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(...)</a> <div class="sourceCode" id="cb9"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb9-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(...)</a>
<a class="sourceLine" id="cb8-2" title="2"><span class="co"># or</span></a> <a class="sourceLine" id="cb9-2" title="2"><span class="co"># or</span></a>
<a class="sourceLine" id="cb8-3" title="3"><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(septic_patients, ...)</a></code></pre></div> <a class="sourceLine" id="cb9-3" title="3"><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(septic_patients, ...)</a></code></pre></div>
<p>is equal to:</p> <p>is equal to:</p>
<div class="sourceCode" id="cb9"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb9-1" title="1">septic_patients <span class="op">%&gt;%</span></a> <div class="sourceCode" id="cb10"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb10-1" title="1">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb9-2" title="2"><span class="st"> </span><span class="kw">mutate</span>(<span class="dt">only_firsts =</span> <span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(septic_patients, ...)) <span class="op">%&gt;%</span></a> <a class="sourceLine" id="cb10-2" title="2"><span class="st"> </span><span class="kw">mutate</span>(<span class="dt">only_firsts =</span> <span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(septic_patients, ...)) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb9-3" title="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/stats/topics/filter">filter</a></span>(only_firsts <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>) <span class="op">%&gt;%</span></a> <a class="sourceLine" id="cb10-3" title="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/stats/topics/filter">filter</a></span>(only_firsts <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb9-4" title="4"><span class="st"> </span><span class="kw">select</span>(<span class="op">-</span>only_firsts)</a></code></pre></div> <a class="sourceLine" id="cb10-4" title="4"><span class="st"> </span><span class="kw">select</span>(<span class="op">-</span>only_firsts)</a></code></pre></div>
</li> </li>
<li>New function <code><a href="../reference/availability.html">availability()</a></code> to check the number of available (non-empty) results in a <code>data.frame</code> <li>New function <code><a href="../reference/availability.html">availability()</a></code> to check the number of available (non-empty) results in a <code>data.frame</code>
</li> </li>
@@ -560,33 +593,33 @@ These functions use <code><a href="../reference/AMR-deprecated.html">as.atc()</a
<ul> <ul>
<li> <li>
<p>Now handles incorrect spelling, like <code>i</code> instead of <code>y</code> and <code>f</code> instead of <code>ph</code>:</p> <p>Now handles incorrect spelling, like <code>i</code> instead of <code>y</code> and <code>f</code> instead of <code>ph</code>:</p>
<div class="sourceCode" id="cb10"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb10-1" title="1"><span class="co"># mo_fullname() uses as.mo() internally</span></a> <div class="sourceCode" id="cb11"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb11-1" title="1"><span class="co"># mo_fullname() uses as.mo() internally</span></a>
<a class="sourceLine" id="cb10-2" title="2"></a> <a class="sourceLine" id="cb11-2" title="2"></a>
<a class="sourceLine" id="cb10-3" title="3"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"Sthafilokockus aaureuz"</span>)</a> <a class="sourceLine" id="cb11-3" title="3"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"Sthafilokockus aaureuz"</span>)</a>
<a class="sourceLine" id="cb10-4" title="4"><span class="co">#&gt; [1] "Staphylococcus aureus"</span></a> <a class="sourceLine" id="cb11-4" title="4"><span class="co">#&gt; [1] "Staphylococcus aureus"</span></a>
<a class="sourceLine" id="cb10-5" title="5"></a> <a class="sourceLine" id="cb11-5" title="5"></a>
<a class="sourceLine" id="cb10-6" title="6"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. klossi"</span>)</a> <a class="sourceLine" id="cb11-6" title="6"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. klossi"</span>)</a>
<a class="sourceLine" id="cb10-7" title="7"><span class="co">#&gt; [1] "Staphylococcus kloosii"</span></a></code></pre></div> <a class="sourceLine" id="cb11-7" title="7"><span class="co">#&gt; [1] "Staphylococcus kloosii"</span></a></code></pre></div>
</li> </li>
<li> <li>
<p>Uncertainty of the algorithm is now divided into four levels, 0 to 3, where the default <code>allow_uncertain = TRUE</code> is equal to uncertainty level 2. Run <code><a href="../reference/as.mo.html">?as.mo</a></code> for more info about these levels.</p> <p>Uncertainty of the algorithm is now divided into four levels, 0 to 3, where the default <code>allow_uncertain = TRUE</code> is equal to uncertainty level 2. Run <code><a href="../reference/as.mo.html">?as.mo</a></code> for more info about these levels.</p>
<div class="sourceCode" id="cb11"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb11-1" title="1"><span class="co"># equal:</span></a> <div class="sourceCode" id="cb12"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb12-1" title="1"><span class="co"># equal:</span></a>
<a class="sourceLine" id="cb11-2" title="2"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="ot">TRUE</span>)</a> <a class="sourceLine" id="cb12-2" title="2"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="ot">TRUE</span>)</a>
<a class="sourceLine" id="cb11-3" title="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="dv">2</span>)</a> <a class="sourceLine" id="cb12-3" title="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="dv">2</span>)</a>
<a class="sourceLine" id="cb11-4" title="4"></a> <a class="sourceLine" id="cb12-4" title="4"></a>
<a class="sourceLine" id="cb11-5" title="5"><span class="co"># also equal:</span></a> <a class="sourceLine" id="cb12-5" title="5"><span class="co"># also equal:</span></a>
<a class="sourceLine" id="cb11-6" title="6"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="ot">FALSE</span>)</a> <a class="sourceLine" id="cb12-6" title="6"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="ot">FALSE</span>)</a>
<a class="sourceLine" id="cb11-7" title="7"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="dv">0</span>)</a></code></pre></div> <a class="sourceLine" id="cb12-7" title="7"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="dv">0</span>)</a></code></pre></div>
Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a></code> could lead to very unreliable results.</li> Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a></code> could lead to very unreliable results.</li>
<li>Implemented the latest publication of Becker <em>et al.</em> (2019), for categorising coagulase-negative <em>Staphylococci</em> <li>Implemented the latest publication of Becker <em>et al.</em> (2019), for categorising coagulase-negative <em>Staphylococci</em>
</li> </li>
<li>All microbial IDs that found are now saved to a local file <code>~/.Rhistory_mo</code>. Use the new function <code>clean_mo_history()</code> to delete this file, which resets the algorithms.</li> <li>All microbial IDs that found are now saved to a local file <code>~/.Rhistory_mo</code>. Use the new function <code>clean_mo_history()</code> to delete this file, which resets the algorithms.</li>
<li> <li>
<p>Incoercible results will now be considered unknown, MO code <code>UNKNOWN</code>. On foreign systems, properties of these will be translated to all languages already previously supported: German, Dutch, French, Italian, Spanish and Portuguese:</p> <p>Incoercible results will now be considered unknown, MO code <code>UNKNOWN</code>. On foreign systems, properties of these will be translated to all languages already previously supported: German, Dutch, French, Italian, Spanish and Portuguese:</p>
<div class="sourceCode" id="cb12"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb12-1" title="1"><span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(<span class="st">"qwerty"</span>, <span class="dt">language =</span> <span class="st">"es"</span>)</a> <div class="sourceCode" id="cb13"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb13-1" title="1"><span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(<span class="st">"qwerty"</span>, <span class="dt">language =</span> <span class="st">"es"</span>)</a>
<a class="sourceLine" id="cb12-2" title="2"><span class="co"># Warning: </span></a> <a class="sourceLine" id="cb13-2" title="2"><span class="co"># Warning: </span></a>
<a class="sourceLine" id="cb12-3" title="3"><span class="co"># one unique value (^= 100.0%) could not be coerced and is considered 'unknown': "qwerty". Use mo_failures() to review it.</span></a> <a class="sourceLine" id="cb13-3" title="3"><span class="co"># one unique value (^= 100.0%) could not be coerced and is considered 'unknown': "qwerty". Use mo_failures() to review it.</span></a>
<a class="sourceLine" id="cb12-4" title="4"><span class="co">#&gt; [1] "(género desconocido)"</span></a></code></pre></div> <a class="sourceLine" id="cb13-4" title="4"><span class="co">#&gt; [1] "(género desconocido)"</span></a></code></pre></div>
</li> </li>
<li>Fix for vector containing only empty values</li> <li>Fix for vector containing only empty values</li>
<li>Finds better results when input is in other languages</li> <li>Finds better results when input is in other languages</li>
@@ -632,19 +665,19 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<ul> <ul>
<li> <li>
<p>Support for tidyverse quasiquotation! Now you can create frequency tables of function outcomes:</p> <p>Support for tidyverse quasiquotation! Now you can create frequency tables of function outcomes:</p>
<div class="sourceCode" id="cb13"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb13-1" title="1"><span class="co"># Determine genus of microorganisms (mo) in `septic_patients` data set:</span></a> <div class="sourceCode" id="cb14"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb14-1" title="1"><span class="co"># Determine genus of microorganisms (mo) in `septic_patients` data set:</span></a>
<a class="sourceLine" id="cb13-2" title="2"><span class="co"># OLD WAY</span></a> <a class="sourceLine" id="cb14-2" title="2"><span class="co"># OLD WAY</span></a>
<a class="sourceLine" id="cb13-3" title="3">septic_patients <span class="op">%&gt;%</span></a> <a class="sourceLine" id="cb14-3" title="3">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb13-4" title="4"><span class="st"> </span><span class="kw">mutate</span>(<span class="dt">genus =</span> <span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo)) <span class="op">%&gt;%</span></a> <a class="sourceLine" id="cb14-4" title="4"><span class="st"> </span><span class="kw">mutate</span>(<span class="dt">genus =</span> <span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo)) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb13-5" title="5"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(genus)</a> <a class="sourceLine" id="cb14-5" title="5"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(genus)</a>
<a class="sourceLine" id="cb13-6" title="6"><span class="co"># NEW WAY</span></a> <a class="sourceLine" id="cb14-6" title="6"><span class="co"># NEW WAY</span></a>
<a class="sourceLine" id="cb13-7" title="7">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a> <a class="sourceLine" id="cb14-7" title="7">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb13-8" title="8"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(<span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo))</a> <a class="sourceLine" id="cb14-8" title="8"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(<span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo))</a>
<a class="sourceLine" id="cb13-9" title="9"></a> <a class="sourceLine" id="cb14-9" title="9"></a>
<a class="sourceLine" id="cb13-10" title="10"><span class="co"># Even supports grouping variables:</span></a> <a class="sourceLine" id="cb14-10" title="10"><span class="co"># Even supports grouping variables:</span></a>
<a class="sourceLine" id="cb13-11" title="11">septic_patients <span class="op">%&gt;%</span></a> <a class="sourceLine" id="cb14-11" title="11">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb13-12" title="12"><span class="st"> </span><span class="kw">group_by</span>(gender) <span class="op">%&gt;%</span><span class="st"> </span></a> <a class="sourceLine" id="cb14-12" title="12"><span class="st"> </span><span class="kw">group_by</span>(gender) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb13-13" title="13"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(<span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo))</a></code></pre></div> <a class="sourceLine" id="cb14-13" title="13"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(<span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo))</a></code></pre></div>
</li> </li>
<li>Header info is now available as a list, with the <code>header</code> function</li> <li>Header info is now available as a list, with the <code>header</code> function</li>
<li>The parameter <code>header</code> is now set to <code>TRUE</code> at default, even for markdown</li> <li>The parameter <code>header</code> is now set to <code>TRUE</code> at default, even for markdown</li>
@@ -679,9 +712,9 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<h1 class="page-header"> <h1 class="page-header">
<a href="#amr-050" class="anchor"></a>AMR 0.5.0<small> 2018-11-30 </small> <a href="#amr-050" class="anchor"></a>AMR 0.5.0<small> 2018-11-30 </small>
</h1> </h1>
<div id="new-3" class="section level4"> <div id="new-4" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#new-3" class="anchor"></a>New</h4> <a href="#new-4" class="anchor"></a>New</h4>
<ul> <ul>
<li>Repository moved to GitLab: <a href="https://gitlab.com/msberends/AMR" class="uri">https://gitlab.com/msberends/AMR</a> <li>Repository moved to GitLab: <a href="https://gitlab.com/msberends/AMR" class="uri">https://gitlab.com/msberends/AMR</a>
</li> </li>
@@ -719,10 +752,10 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<li>Fewer than 3 characters as input for <code>as.mo</code> will return NA</li> <li>Fewer than 3 characters as input for <code>as.mo</code> will return NA</li>
<li> <li>
<p>Function <code>as.mo</code> (and all <code>mo_*</code> wrappers) now supports genus abbreviations with “species” attached</p> <p>Function <code>as.mo</code> (and all <code>mo_*</code> wrappers) now supports genus abbreviations with “species” attached</p>
<div class="sourceCode" id="cb14"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb14-1" title="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. species"</span>) <span class="co"># B_ESCHR</span></a> <div class="sourceCode" id="cb15"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb15-1" title="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. species"</span>) <span class="co"># B_ESCHR</span></a>
<a class="sourceLine" id="cb14-2" title="2"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"E. spp."</span>) <span class="co"># "Escherichia species"</span></a> <a class="sourceLine" id="cb15-2" title="2"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"E. spp."</span>) <span class="co"># "Escherichia species"</span></a>
<a class="sourceLine" id="cb14-3" title="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S. spp"</span>) <span class="co"># B_STPHY</span></a> <a class="sourceLine" id="cb15-3" title="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S. spp"</span>) <span class="co"># B_STPHY</span></a>
<a class="sourceLine" id="cb14-4" title="4"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. species"</span>) <span class="co"># "Staphylococcus species"</span></a></code></pre></div> <a class="sourceLine" id="cb15-4" title="4"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. species"</span>) <span class="co"># "Staphylococcus species"</span></a></code></pre></div>
</li> </li>
<li>Added parameter <code>combine_IR</code> (TRUE/FALSE) to functions <code>portion_df</code> and <code>count_df</code>, to indicate that all values of I and R must be merged into one, so the output only consists of S vs. IR (susceptible vs. non-susceptible)</li> <li>Added parameter <code>combine_IR</code> (TRUE/FALSE) to functions <code>portion_df</code> and <code>count_df</code>, to indicate that all values of I and R must be merged into one, so the output only consists of S vs. IR (susceptible vs. non-susceptible)</li>
<li>Fix for <code>portion_*(..., as_percent = TRUE)</code> when minimal number of isolates would not be met</li> <li>Fix for <code>portion_*(..., as_percent = TRUE)</code> when minimal number of isolates would not be met</li>
@@ -735,15 +768,15 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<ul> <ul>
<li> <li>
<p>Support for grouping variables, test with:</p> <p>Support for grouping variables, test with:</p>
<div class="sourceCode" id="cb15"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb15-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a> <div class="sourceCode" id="cb16"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb16-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb15-2" title="2"><span class="st"> </span><span class="kw">group_by</span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a> <a class="sourceLine" id="cb16-2" title="2"><span class="st"> </span><span class="kw">group_by</span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb15-3" title="3"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(gender)</a></code></pre></div> <a class="sourceLine" id="cb16-3" title="3"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(gender)</a></code></pre></div>
</li> </li>
<li> <li>
<p>Support for (un)selecting columns:</p> <p>Support for (un)selecting columns:</p>
<div class="sourceCode" id="cb16"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb16-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a> <div class="sourceCode" id="cb17"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb17-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb16-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a> <a class="sourceLine" id="cb17-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb16-3" title="3"><span class="st"> </span><span class="kw">select</span>(<span class="op">-</span>count, <span class="op">-</span>cum_count) <span class="co"># only get item, percent, cum_percent</span></a></code></pre></div> <a class="sourceLine" id="cb17-3" title="3"><span class="st"> </span><span class="kw">select</span>(<span class="op">-</span>count, <span class="op">-</span>cum_count) <span class="co"># only get item, percent, cum_percent</span></a></code></pre></div>
</li> </li>
<li>Check for <code><a href="https://www.rdocumentation.org/packages/hms/topics/hms">hms::is.hms</a></code> <li>Check for <code><a href="https://www.rdocumentation.org/packages/hms/topics/hms">hms::is.hms</a></code>
</li> </li>
@@ -806,9 +839,9 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<h1 class="page-header"> <h1 class="page-header">
<a href="#amr-040" class="anchor"></a>AMR 0.4.0<small> 2018-10-01 </small> <a href="#amr-040" class="anchor"></a>AMR 0.4.0<small> 2018-10-01 </small>
</h1> </h1>
<div id="new-4" class="section level4"> <div id="new-5" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#new-4" class="anchor"></a>New</h4> <a href="#new-5" class="anchor"></a>New</h4>
<ul> <ul>
<li>The data set <code>microorganisms</code> now contains <strong>all microbial taxonomic data from ITIS</strong> (kingdoms Bacteria, Fungi and Protozoa), the Integrated Taxonomy Information System, available via <a href="https://itis.gov" class="uri">https://itis.gov</a>. The data set now contains more than 18,000 microorganisms with all known bacteria, fungi and protozoa according ITIS with genus, species, subspecies, family, order, class, phylum and subkingdom. The new data set <code>microorganisms.old</code> contains all previously known taxonomic names from those kingdoms.</li> <li>The data set <code>microorganisms</code> now contains <strong>all microbial taxonomic data from ITIS</strong> (kingdoms Bacteria, Fungi and Protozoa), the Integrated Taxonomy Information System, available via <a href="https://itis.gov" class="uri">https://itis.gov</a>. The data set now contains more than 18,000 microorganisms with all known bacteria, fungi and protozoa according ITIS with genus, species, subspecies, family, order, class, phylum and subkingdom. The new data set <code>microorganisms.old</code> contains all previously known taxonomic names from those kingdoms.</li>
<li>New functions based on the existing function <code>mo_property</code>: <li>New functions based on the existing function <code>mo_property</code>:
@@ -823,18 +856,18 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
</li> </li>
</ul> </ul>
<p>They also come with support for German, Dutch, French, Italian, Spanish and Portuguese:</p> <p>They also come with support for German, Dutch, French, Italian, Spanish and Portuguese:</p>
<div class="sourceCode" id="cb17"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb17-1" title="1"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>)</a> <div class="sourceCode" id="cb18"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb18-1" title="1"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>)</a>
<a class="sourceLine" id="cb17-2" title="2"><span class="co"># [1] "Gram negative"</span></a> <a class="sourceLine" id="cb18-2" title="2"><span class="co"># [1] "Gram negative"</span></a>
<a class="sourceLine" id="cb17-3" title="3"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"de"</span>) <span class="co"># German</span></a> <a class="sourceLine" id="cb18-3" title="3"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"de"</span>) <span class="co"># German</span></a>
<a class="sourceLine" id="cb17-4" title="4"><span class="co"># [1] "Gramnegativ"</span></a> <a class="sourceLine" id="cb18-4" title="4"><span class="co"># [1] "Gramnegativ"</span></a>
<a class="sourceLine" id="cb17-5" title="5"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"es"</span>) <span class="co"># Spanish</span></a> <a class="sourceLine" id="cb18-5" title="5"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"es"</span>) <span class="co"># Spanish</span></a>
<a class="sourceLine" id="cb17-6" title="6"><span class="co"># [1] "Gram negativo"</span></a> <a class="sourceLine" id="cb18-6" title="6"><span class="co"># [1] "Gram negativo"</span></a>
<a class="sourceLine" id="cb17-7" title="7"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. group A"</span>, <span class="dt">language =</span> <span class="st">"pt"</span>) <span class="co"># Portuguese</span></a> <a class="sourceLine" id="cb18-7" title="7"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. group A"</span>, <span class="dt">language =</span> <span class="st">"pt"</span>) <span class="co"># Portuguese</span></a>
<a class="sourceLine" id="cb17-8" title="8"><span class="co"># [1] "Streptococcus grupo A"</span></a></code></pre></div> <a class="sourceLine" id="cb18-8" title="8"><span class="co"># [1] "Streptococcus grupo A"</span></a></code></pre></div>
<p>Furthermore, former taxonomic names will give a note about the current taxonomic name:</p> <p>Furthermore, former taxonomic names will give a note about the current taxonomic name:</p>
<div class="sourceCode" id="cb18"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb18-1" title="1"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"Esc blattae"</span>)</a> <div class="sourceCode" id="cb19"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb19-1" title="1"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"Esc blattae"</span>)</a>
<a class="sourceLine" id="cb18-2" title="2"><span class="co"># Note: 'Escherichia blattae' (Burgess et al., 1973) was renamed 'Shimwellia blattae' (Priest and Barker, 2010)</span></a> <a class="sourceLine" id="cb19-2" title="2"><span class="co"># Note: 'Escherichia blattae' (Burgess et al., 1973) was renamed 'Shimwellia blattae' (Priest and Barker, 2010)</span></a>
<a class="sourceLine" id="cb18-3" title="3"><span class="co"># [1] "Gram negative"</span></a></code></pre></div> <a class="sourceLine" id="cb19-3" title="3"><span class="co"># [1] "Gram negative"</span></a></code></pre></div>
</li> </li>
<li>Functions <code>count_R</code>, <code>count_IR</code>, <code>count_I</code>, <code>count_SI</code> and <code>count_S</code> to selectively count resistant or susceptible isolates <li>Functions <code>count_R</code>, <code>count_IR</code>, <code>count_I</code>, <code>count_SI</code> and <code>count_S</code> to selectively count resistant or susceptible isolates
<ul> <ul>
@@ -845,18 +878,18 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
</li> </li>
<li> <li>
<p>Functions <code>as.mo</code> and <code>is.mo</code> as replacements for <code>as.bactid</code> and <code>is.bactid</code> (since the <code>microoganisms</code> data set not only contains bacteria). These last two functions are deprecated and will be removed in a future release. The <code>as.mo</code> function determines microbial IDs using intelligent rules:</p> <p>Functions <code>as.mo</code> and <code>is.mo</code> as replacements for <code>as.bactid</code> and <code>is.bactid</code> (since the <code>microoganisms</code> data set not only contains bacteria). These last two functions are deprecated and will be removed in a future release. The <code>as.mo</code> function determines microbial IDs using intelligent rules:</p>
<div class="sourceCode" id="cb19"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb19-1" title="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. coli"</span>)</a> <div class="sourceCode" id="cb20"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb20-1" title="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. coli"</span>)</a>
<a class="sourceLine" id="cb19-2" title="2"><span class="co"># [1] B_ESCHR_COL</span></a> <a class="sourceLine" id="cb20-2" title="2"><span class="co"># [1] B_ESCHR_COL</span></a>
<a class="sourceLine" id="cb19-3" title="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"MRSA"</span>)</a> <a class="sourceLine" id="cb20-3" title="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"MRSA"</span>)</a>
<a class="sourceLine" id="cb19-4" title="4"><span class="co"># [1] B_STPHY_AUR</span></a> <a class="sourceLine" id="cb20-4" title="4"><span class="co"># [1] B_STPHY_AUR</span></a>
<a class="sourceLine" id="cb19-5" title="5"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S group A"</span>)</a> <a class="sourceLine" id="cb20-5" title="5"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S group A"</span>)</a>
<a class="sourceLine" id="cb19-6" title="6"><span class="co"># [1] B_STRPTC_GRA</span></a></code></pre></div> <a class="sourceLine" id="cb20-6" title="6"><span class="co"># [1] B_STRPTC_GRA</span></a></code></pre></div>
<p>And with great speed too - on a quite regular Linux server from 2007 it takes us less than 0.02 seconds to transform 25,000 items:</p> <p>And with great speed too - on a quite regular Linux server from 2007 it takes us less than 0.02 seconds to transform 25,000 items:</p>
<div class="sourceCode" id="cb20"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb20-1" title="1">thousands_of_E_colis &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/rep">rep</a></span>(<span class="st">"E. coli"</span>, <span class="dv">25000</span>)</a> <div class="sourceCode" id="cb21"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb21-1" title="1">thousands_of_E_colis &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/rep">rep</a></span>(<span class="st">"E. coli"</span>, <span class="dv">25000</span>)</a>
<a class="sourceLine" id="cb20-2" title="2">microbenchmark<span class="op">::</span><span class="kw"><a href="https://www.rdocumentation.org/packages/microbenchmark/topics/microbenchmark">microbenchmark</a></span>(<span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(thousands_of_E_colis), <span class="dt">unit =</span> <span class="st">"s"</span>)</a> <a class="sourceLine" id="cb21-2" title="2">microbenchmark<span class="op">::</span><span class="kw"><a href="https://www.rdocumentation.org/packages/microbenchmark/topics/microbenchmark">microbenchmark</a></span>(<span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(thousands_of_E_colis), <span class="dt">unit =</span> <span class="st">"s"</span>)</a>
<a class="sourceLine" id="cb20-3" title="3"><span class="co"># Unit: seconds</span></a> <a class="sourceLine" id="cb21-3" title="3"><span class="co"># Unit: seconds</span></a>
<a class="sourceLine" id="cb20-4" title="4"><span class="co"># min median max neval</span></a> <a class="sourceLine" id="cb21-4" title="4"><span class="co"># min median max neval</span></a>
<a class="sourceLine" id="cb20-5" title="5"><span class="co"># 0.01817717 0.01843957 0.03878077 100</span></a></code></pre></div> <a class="sourceLine" id="cb21-5" title="5"><span class="co"># 0.01817717 0.01843957 0.03878077 100</span></a></code></pre></div>
</li> </li>
<li>Added parameter <code>reference_df</code> for <code>as.mo</code>, so users can supply their own microbial IDs, name or codes as a reference table</li> <li>Added parameter <code>reference_df</code> for <code>as.mo</code>, so users can supply their own microbial IDs, name or codes as a reference table</li>
<li>Renamed all previous references to <code>bactid</code> to <code>mo</code>, like: <li>Renamed all previous references to <code>bactid</code> to <code>mo</code>, like:
@@ -884,12 +917,12 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<li>Added three antimicrobial agents to the <code>antibiotics</code> data set: Terbinafine (D01BA02), Rifaximin (A07AA11) and Isoconazole (D01AC05)</li> <li>Added three antimicrobial agents to the <code>antibiotics</code> data set: Terbinafine (D01BA02), Rifaximin (A07AA11) and Isoconazole (D01AC05)</li>
<li> <li>
<p>Added 163 trade names to the <code>antibiotics</code> data set, it now contains 298 different trade names in total, e.g.:</p> <p>Added 163 trade names to the <code>antibiotics</code> data set, it now contains 298 different trade names in total, e.g.:</p>
<div class="sourceCode" id="cb21"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb21-1" title="1"><span class="kw">ab_official</span>(<span class="st">"Bactroban"</span>)</a> <div class="sourceCode" id="cb22"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb22-1" title="1"><span class="kw">ab_official</span>(<span class="st">"Bactroban"</span>)</a>
<a class="sourceLine" id="cb21-2" title="2"><span class="co"># [1] "Mupirocin"</span></a> <a class="sourceLine" id="cb22-2" title="2"><span class="co"># [1] "Mupirocin"</span></a>
<a class="sourceLine" id="cb21-3" title="3"><span class="kw"><a href="../reference/ab_property.html">ab_name</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="st">"Bactroban"</span>, <span class="st">"Amoxil"</span>, <span class="st">"Zithromax"</span>, <span class="st">"Floxapen"</span>))</a> <a class="sourceLine" id="cb22-3" title="3"><span class="kw"><a href="../reference/ab_property.html">ab_name</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="st">"Bactroban"</span>, <span class="st">"Amoxil"</span>, <span class="st">"Zithromax"</span>, <span class="st">"Floxapen"</span>))</a>
<a class="sourceLine" id="cb21-4" title="4"><span class="co"># [1] "Mupirocin" "Amoxicillin" "Azithromycin" "Flucloxacillin"</span></a> <a class="sourceLine" id="cb22-4" title="4"><span class="co"># [1] "Mupirocin" "Amoxicillin" "Azithromycin" "Flucloxacillin"</span></a>
<a class="sourceLine" id="cb21-5" title="5"><span class="kw"><a href="../reference/ab_property.html">ab_atc</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="st">"Bactroban"</span>, <span class="st">"Amoxil"</span>, <span class="st">"Zithromax"</span>, <span class="st">"Floxapen"</span>))</a> <a class="sourceLine" id="cb22-5" title="5"><span class="kw"><a href="../reference/ab_property.html">ab_atc</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="st">"Bactroban"</span>, <span class="st">"Amoxil"</span>, <span class="st">"Zithromax"</span>, <span class="st">"Floxapen"</span>))</a>
<a class="sourceLine" id="cb21-6" title="6"><span class="co"># [1] "R01AX06" "J01CA04" "J01FA10" "J01CF05"</span></a></code></pre></div> <a class="sourceLine" id="cb22-6" title="6"><span class="co"># [1] "R01AX06" "J01CA04" "J01FA10" "J01CF05"</span></a></code></pre></div>
</li> </li>
<li>For <code>first_isolate</code>, rows will be ignored when theres no species available</li> <li>For <code>first_isolate</code>, rows will be ignored when theres no species available</li>
<li>Function <code>ratio</code> is now deprecated and will be removed in a future release, as it is not really the scope of this package</li> <li>Function <code>ratio</code> is now deprecated and will be removed in a future release, as it is not really the scope of this package</li>
@@ -900,13 +933,13 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
</li> </li>
<li> <li>
<p>Support for quasiquotation in the functions series <code>count_*</code> and <code>portions_*</code>, and <code>n_rsi</code>. This allows to check for more than 2 vectors or columns.</p> <p>Support for quasiquotation in the functions series <code>count_*</code> and <code>portions_*</code>, and <code>n_rsi</code>. This allows to check for more than 2 vectors or columns.</p>
<div class="sourceCode" id="cb22"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb22-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw">select</span>(amox, cipr) <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>()</a> <div class="sourceCode" id="cb23"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb23-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw">select</span>(amox, cipr) <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>()</a>
<a class="sourceLine" id="cb22-2" title="2"><span class="co"># which is the same as:</span></a> <a class="sourceLine" id="cb23-2" title="2"><span class="co"># which is the same as:</span></a>
<a class="sourceLine" id="cb22-3" title="3">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>(amox, cipr)</a> <a class="sourceLine" id="cb23-3" title="3">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>(amox, cipr)</a>
<a class="sourceLine" id="cb22-4" title="4"></a> <a class="sourceLine" id="cb23-4" title="4"></a>
<a class="sourceLine" id="cb22-5" title="5">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl)</a> <a class="sourceLine" id="cb23-5" title="5">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl)</a>
<a class="sourceLine" id="cb22-6" title="6">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent)</a> <a class="sourceLine" id="cb23-6" title="6">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent)</a>
<a class="sourceLine" id="cb22-7" title="7">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent, pita)</a></code></pre></div> <a class="sourceLine" id="cb23-7" title="7">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent, pita)</a></code></pre></div>
</li> </li>
<li>Edited <code>ggplot_rsi</code> and <code>geom_rsi</code> so they can cope with <code>count_df</code>. The new <code>fun</code> parameter has value <code>portion_df</code> at default, but can be set to <code>count_df</code>.</li> <li>Edited <code>ggplot_rsi</code> and <code>geom_rsi</code> so they can cope with <code>count_df</code>. The new <code>fun</code> parameter has value <code>portion_df</code> at default, but can be set to <code>count_df</code>.</li>
<li>Fix for <code>ggplot_rsi</code> when the <code>ggplot2</code> package was not loaded</li> <li>Fix for <code>ggplot_rsi</code> when the <code>ggplot2</code> package was not loaded</li>
@@ -920,12 +953,12 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
</li> </li>
<li> <li>
<p>Support for types (classes) list and matrix for <code>freq</code></p> <p>Support for types (classes) list and matrix for <code>freq</code></p>
<div class="sourceCode" id="cb23"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb23-1" title="1">my_matrix =<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/with">with</a></span>(septic_patients, <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/matrix">matrix</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(age, gender), <span class="dt">ncol =</span> <span class="dv">2</span>))</a> <div class="sourceCode" id="cb24"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb24-1" title="1">my_matrix =<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/with">with</a></span>(septic_patients, <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/matrix">matrix</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(age, gender), <span class="dt">ncol =</span> <span class="dv">2</span>))</a>
<a class="sourceLine" id="cb23-2" title="2"><span class="kw"><a href="../reference/freq.html">freq</a></span>(my_matrix)</a></code></pre></div> <a class="sourceLine" id="cb24-2" title="2"><span class="kw"><a href="../reference/freq.html">freq</a></span>(my_matrix)</a></code></pre></div>
<p>For lists, subsetting is possible:</p> <p>For lists, subsetting is possible:</p>
<div class="sourceCode" id="cb24"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb24-1" title="1">my_list =<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/list">list</a></span>(<span class="dt">age =</span> septic_patients<span class="op">$</span>age, <span class="dt">gender =</span> septic_patients<span class="op">$</span>gender)</a> <div class="sourceCode" id="cb25"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb25-1" title="1">my_list =<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/list">list</a></span>(<span class="dt">age =</span> septic_patients<span class="op">$</span>age, <span class="dt">gender =</span> septic_patients<span class="op">$</span>gender)</a>
<a class="sourceLine" id="cb24-2" title="2">my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age)</a> <a class="sourceLine" id="cb25-2" title="2">my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age)</a>
<a class="sourceLine" id="cb24-3" title="3">my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(gender)</a></code></pre></div> <a class="sourceLine" id="cb25-3" title="3">my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(gender)</a></code></pre></div>
</li> </li>
</ul> </ul>
</div> </div>
@@ -941,9 +974,9 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<h1 class="page-header"> <h1 class="page-header">
<a href="#amr-030" class="anchor"></a>AMR 0.3.0<small> 2018-08-14 </small> <a href="#amr-030" class="anchor"></a>AMR 0.3.0<small> 2018-08-14 </small>
</h1> </h1>
<div id="new-5" class="section level4"> <div id="new-6" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#new-5" class="anchor"></a>New</h4> <a href="#new-6" class="anchor"></a>New</h4>
<ul> <ul>
<li> <li>
<strong>BREAKING</strong>: <code>rsi_df</code> was removed in favour of new functions <code>portion_R</code>, <code>portion_IR</code>, <code>portion_I</code>, <code>portion_SI</code> and <code>portion_S</code> to selectively calculate resistance or susceptibility. These functions are 20 to 30 times faster than the old <code>rsi</code> function. The old function still works, but is deprecated. <strong>BREAKING</strong>: <code>rsi_df</code> was removed in favour of new functions <code>portion_R</code>, <code>portion_IR</code>, <code>portion_I</code>, <code>portion_SI</code> and <code>portion_S</code> to selectively calculate resistance or susceptibility. These functions are 20 to 30 times faster than the old <code>rsi</code> function. The old function still works, but is deprecated.
@@ -1078,9 +1111,9 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<h1 class="page-header"> <h1 class="page-header">
<a href="#amr-020" class="anchor"></a>AMR 0.2.0<small> 2018-05-03 </small> <a href="#amr-020" class="anchor"></a>AMR 0.2.0<small> 2018-05-03 </small>
</h1> </h1>
<div id="new-6" class="section level4"> <div id="new-7" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#new-6" class="anchor"></a>New</h4> <a href="#new-7" class="anchor"></a>New</h4>
<ul> <ul>
<li>Full support for Windows, Linux and macOS</li> <li>Full support for Windows, Linux and macOS</li>
<li>Full support for old R versions, only R-3.0.0 (April 2013) or later is needed (needed packages may have other dependencies)</li> <li>Full support for old R versions, only R-3.0.0 (April 2013) or later is needed (needed packages may have other dependencies)</li>
@@ -1159,7 +1192,7 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<div id="tocnav"> <div id="tocnav">
<h2>Contents</h2> <h2>Contents</h2>
<ul class="nav nav-pills nav-stacked"> <ul class="nav nav-pills nav-stacked">
<li><a href="#amr-0719004">0.7.1.9004</a></li> <li><a href="#amr-0719005">0.7.1.9005</a></li>
<li><a href="#amr-071">0.7.1</a></li> <li><a href="#amr-071">0.7.1</a></li>
<li><a href="#amr-070">0.7.0</a></li> <li><a href="#amr-070">0.7.0</a></li>
<li><a href="#amr-061">0.6.1</a></li> <li><a href="#amr-061">0.6.1</a></li>

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="Latest development version">0.7.1.9004</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9004</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>
@@ -322,12 +322,9 @@ This function uses intelligent rules to help getting fast and logical results. I
</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 equal 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, previously accepted (but now invalid) taxonomic names and misspelled input</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 removed parts between brackets, strips off words from the end one by one 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> <li><p>(uncertainty level 3): It strips off words from the start one by one and tries any part of the name</p></li>
<li><p>(uncertainty level 2): It strips off words from the end one by one and re-evaluates the input with all previous rules</p></li>
<li><p>(uncertainty level 3): It strips off words from the start one by one and re-evaluates the input with all previous rules</p></li>
<li><p>(uncertainty level 3): It tries any part of the name</p></li>
</ul> </ul>
<p>You can also use e.g. <code>as.mo(..., allow_uncertain = 1)</code> to only allow up to level 1 uncertainty.</p> <p>You can also use e.g. <code>as.mo(..., allow_uncertain = 1)</code> to only allow up to level 1 uncertainty.</p>
<p>Examples:</p><ul> <p>Examples:</p><ul>

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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>
@@ -303,15 +303,14 @@
<h2 class="hasAnchor" id="interpretation-of-s-i-and-r"><a class="anchor" href="#interpretation-of-s-i-and-r"></a>Interpretation of S, I and R</h2> <h2 class="hasAnchor" id="interpretation-of-s-i-and-r"><a class="anchor" href="#interpretation-of-s-i-and-r"></a>Interpretation of S, I and R</h2>
<p>In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".</p> <p>In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (<a href='http://www.eucast.org/newsiandr/'>http://www.eucast.org/newsiandr/</a>). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".</p>
<ul> <ul>
<li><p><strong>S</strong> - Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.</p></li> <li><p><strong>S</strong> - Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.</p></li>
<li><p><strong>I</strong> - Susceptible, increased exposure: A microorganism is categorised as "Susceptible, Increased exposure" when there is a high likelihood of therapeutic success because exposure to the agent is increased by adjusting the dosing regimen or by its concentration at the site of infection.</p></li> <li><p><strong>I</strong> - Susceptible, increased exposure: A microorganism is categorised as "Susceptible, Increased exposure" when there is a high likelihood of therapeutic success because exposure to the agent is increased by adjusting the dosing regimen or by its concentration at the site of infection.</p></li>
<li><p><strong>R</strong> - Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.</p></li> <li><p><strong>R</strong> - Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.</p></li>
</ul> </ul>
<p>Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.</p> <p>Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.</p>
<p>Source: <a href='http://www.eucast.org/newsiandr/'>http://www.eucast.org/newsiandr/</a>.</p> <p>This AMR package honours this new insight. Use <code><a href='portion.html'>portion_SI</a></code> to determine antimicrobial susceptibility and <code><a href='count.html'>count_SI</a></code> to count susceptible isolates.</p>
<p><strong>This AMR package honours this new insight.</strong></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

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

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="Latest development version">0.7.1.9004</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>
@@ -243,19 +243,19 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
</div> </div>
<pre class="usage"><span class='fu'>count_R</span>(<span class='no'>...</span>, <span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>) <pre class="usage"><span class='fu'>count_R</span>(<span class='no'>...</span>, <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>count_IR</span>(<span class='no'>...</span>, <span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>) <span class='fu'>count_IR</span>(<span class='no'>...</span>, <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>count_I</span>(<span class='no'>...</span>, <span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>) <span class='fu'>count_I</span>(<span class='no'>...</span>, <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>count_SI</span>(<span class='no'>...</span>, <span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>) <span class='fu'>count_SI</span>(<span class='no'>...</span>, <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>count_S</span>(<span class='no'>...</span>, <span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>) <span class='fu'>count_S</span>(<span class='no'>...</span>, <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>count_all</span>(<span class='no'>...</span>, <span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>) <span class='fu'>count_all</span>(<span class='no'>...</span>, <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>n_rsi</span>(<span class='no'>...</span>, <span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>) <span class='fu'>n_rsi</span>(<span class='no'>...</span>, <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>count_df</span>(<span class='no'>data</span>, <span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='st'>"name"</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='fu'>count_df</span>(<span class='no'>data</span>, <span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='st'>"name"</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(),
<span class='kw'>combine_SI</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='kw'>combine_IR</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)</pre> <span class='kw'>combine_SI</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='kw'>combine_IR</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)</pre>
@@ -268,8 +268,8 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
<td><p>one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with <code><a href='as.rsi.html'>as.rsi</a></code> if needed.</p></td> <td><p>one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with <code><a href='as.rsi.html'>as.rsi</a></code> if needed.</p></td>
</tr> </tr>
<tr> <tr>
<th>also_single_tested</th> <th>only_all_tested</th>
<td><p>a logical to indicate whether for 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</code> and R in case of <code>portion_R</code>). <strong>This could lead to selection bias.</strong></p></td> <td><p>(for combination therapies, i.e. using more than one variable for <code>...</code>) a logical to indicate that isolates must be tested for all antibiotics, see section <em>Combination therapy</em> below</p></td>
</tr> </tr>
<tr> <tr>
<th>data</th> <th>data</th>
@@ -311,15 +311,52 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
<h2 class="hasAnchor" id="interpretation-of-s-i-and-r"><a class="anchor" href="#interpretation-of-s-i-and-r"></a>Interpretation of S, I and R</h2> <h2 class="hasAnchor" id="interpretation-of-s-i-and-r"><a class="anchor" href="#interpretation-of-s-i-and-r"></a>Interpretation of S, I and R</h2>
<p>In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".</p> <p>In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (<a href='http://www.eucast.org/newsiandr/'>http://www.eucast.org/newsiandr/</a>). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".</p>
<ul> <ul>
<li><p><strong>S</strong> - Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.</p></li> <li><p><strong>S</strong> - Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.</p></li>
<li><p><strong>I</strong> - Susceptible, increased exposure: A microorganism is categorised as "Susceptible, Increased exposure" when there is a high likelihood of therapeutic success because exposure to the agent is increased by adjusting the dosing regimen or by its concentration at the site of infection.</p></li> <li><p><strong>I</strong> - Susceptible, increased exposure: A microorganism is categorised as "Susceptible, Increased exposure" when there is a high likelihood of therapeutic success because exposure to the agent is increased by adjusting the dosing regimen or by its concentration at the site of infection.</p></li>
<li><p><strong>R</strong> - Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.</p></li> <li><p><strong>R</strong> - Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.</p></li>
</ul> </ul>
<p>Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.</p> <p>Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.</p>
<p>Source: <a href='http://www.eucast.org/newsiandr/'>http://www.eucast.org/newsiandr/</a>.</p> <p>This AMR package honours this new insight. Use <code><a href='portion.html'>portion_SI</a></code> to determine antimicrobial susceptibility and <code>count_SI</code> to count susceptible isolates.</p>
<p><strong>This AMR package honours this new insight.</strong></p>
<h2 class="hasAnchor" id="combination-therapy"><a class="anchor" href="#combination-therapy"></a>Combination therapy</h2>
<p>When using more than one variable for <code>...</code> (= combination therapy)), use <code>only_all_tested</code> to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antibiotics, Antibiotic A and Antibiotic B, about how <code>portion_SI</code> works to calculate the %SI:</p>
<pre>
-------------------------------------------------------------------------
only_all_tested = FALSE only_all_tested = TRUE
Antibiotic Antibiotic ----------------------- -----------------------
A B include as include as include as include as
numerator denominator numerator denominator
---------- ---------- ---------- ----------- ---------- -----------
S S X X X X
I S X X X X
R S X X X X
not tested S X X - -
S I X X X X
I I X X X X
R I X X X X
not tested I X X - -
S R X X X X
I R X X X X
R R - X - X
not tested R - - - -
S not tested X X - -
I not tested X X - -
R not tested - - - -
not tested not tested - - - -
-------------------------------------------------------------------------
</pre>
<p>Please note that for <code>only_all_tested = TRUE</code> applies that:</p><pre>
count_S() + count_I() + count_R() == count_all()
portion_S() + portion_I() + portion_R() == 1
</pre><p>and that for <code>only_all_tested = FALSE</code> applies that:</p><pre>
count_S() + count_I() + count_R() &gt;= count_all()
portion_S() + portion_I() + portion_R() &gt;= 1
</pre>
<p>Using <code>only_all_tested</code> has no impact when only using one antibiotic as input.</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>
@@ -351,8 +388,8 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
<span class='co'># Since n_rsi counts available isolates, you can</span> <span class='co'># Since n_rsi counts available isolates, you can</span>
<span class='co'># calculate back to count e.g. non-susceptible isolates.</span> <span class='co'># calculate back to count e.g. non-susceptible isolates.</span>
<span class='co'># This results in the same:</span> <span class='co'># This results in the same:</span>
<span class='fu'>count_IR</span>(<span class='no'>septic_patients</span>$<span class='no'>AMX</span>) <span class='fu'>count_SI</span>(<span class='no'>septic_patients</span>$<span class='no'>AMX</span>)
<span class='fu'><a href='portion.html'>portion_IR</a></span>(<span class='no'>septic_patients</span>$<span class='no'>AMX</span>) * <span class='fu'>n_rsi</span>(<span class='no'>septic_patients</span>$<span class='no'>AMX</span>) <span class='fu'><a href='portion.html'>portion_SI</a></span>(<span class='no'>septic_patients</span>$<span class='no'>AMX</span>) * <span class='fu'>n_rsi</span>(<span class='no'>septic_patients</span>$<span class='no'>AMX</span>)
<span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/library'>library</a></span>(<span class='no'>dplyr</span>) <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/library'>library</a></span>(<span class='no'>dplyr</span>)
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
@@ -366,17 +403,17 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
<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>
<span class='co'># Please mind that `portion_S` calculates percentages right away instead.</span> <span class='co'># Please mind that `portion_SI` calculates percentages right away instead.</span>
<span class='fu'>count_S</span>(<span class='no'>septic_patients</span>$<span class='no'>AMC</span>) <span class='co'># S = 1342 (71.4%)</span> <span class='fu'>count_SI</span>(<span class='no'>septic_patients</span>$<span class='no'>AMC</span>) <span class='co'># 1433</span>
<span class='fu'>count_all</span>(<span class='no'>septic_patients</span>$<span class='no'>AMC</span>) <span class='co'># n = 1879</span> <span class='fu'>count_all</span>(<span class='no'>septic_patients</span>$<span class='no'>AMC</span>) <span class='co'># 1879</span>
<span class='fu'>count_S</span>(<span class='no'>septic_patients</span>$<span class='no'>GEN</span>) <span class='co'># S = 1372 (74.0%)</span> <span class='fu'>count_SI</span>(<span class='no'>septic_patients</span>$<span class='no'>GEN</span>) <span class='co'># 1399</span>
<span class='fu'>count_all</span>(<span class='no'>septic_patients</span>$<span class='no'>GEN</span>) <span class='co'># n = 1855</span> <span class='fu'>count_all</span>(<span class='no'>septic_patients</span>$<span class='no'>GEN</span>) <span class='co'># 1855</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/with'>with</a></span>(<span class='no'>septic_patients</span>, <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/with'>with</a></span>(<span class='no'>septic_patients</span>,
<span class='fu'>count_S</span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>)) <span class='co'># S = 1660 (92.3%)</span> <span class='fu'>count_SI</span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>)) <span class='co'># 1764</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/with'>with</a></span>(<span class='no'>septic_patients</span>, <span class='co'># n = 1798</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/with'>with</a></span>(<span class='no'>septic_patients</span>,
<span class='fu'>n_rsi</span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>)) <span class='fu'>n_rsi</span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>)) <span class='co'># 1936</span>
<span class='co'># Get portions S/I/R immediately of all rsi columns</span> <span class='co'># Get portions S/I/R immediately of all rsi columns</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
@@ -404,6 +441,8 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
<li><a href="#interpretation-of-s-i-and-r">Interpretation of S, I and R</a></li> <li><a href="#interpretation-of-s-i-and-r">Interpretation of S, I and R</a></li>
<li><a href="#combination-therapy">Combination therapy</a></li>
<li><a href="#read-more-on-our-website-">Read more on our website!</a></li> <li><a href="#read-more-on-our-website-">Read more on our website!</a></li>
<li><a href="#see-also">See also</a></li> <li><a href="#see-also">See also</a></li>

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

View File

@@ -81,7 +81,7 @@ top_freq can be used to get the top/bottom n items of a frequency table, with co
</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9004</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9004</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9004</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>

View File

@@ -81,7 +81,7 @@ This is the fastest way to have your organisation (or analysis) specific codes p
</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>

View File

@@ -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="Latest development version">0.7.1.9004</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>
@@ -244,19 +244,19 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
</div> </div>
<pre class="usage"><span class='fu'>portion_R</span>(<span class='no'>...</span>, <span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <pre class="usage"><span class='fu'>portion_R</span>(<span class='no'>...</span>, <span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>,
<span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>) <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>portion_IR</span>(<span class='no'>...</span>, <span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <span class='fu'>portion_IR</span>(<span class='no'>...</span>, <span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>,
<span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>) <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>portion_I</span>(<span class='no'>...</span>, <span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <span class='fu'>portion_I</span>(<span class='no'>...</span>, <span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>,
<span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>) <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>portion_SI</span>(<span class='no'>...</span>, <span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <span class='fu'>portion_SI</span>(<span class='no'>...</span>, <span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>,
<span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>) <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>portion_S</span>(<span class='no'>...</span>, <span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <span class='fu'>portion_S</span>(<span class='no'>...</span>, <span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>,
<span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>) <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>portion_df</span>(<span class='no'>data</span>, <span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='st'>"name"</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='fu'>portion_df</span>(<span class='no'>data</span>, <span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='st'>"name"</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(),
<span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <span class='kw'>combine_SI</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <span class='kw'>combine_SI</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>,
@@ -282,8 +282,8 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
<td><p>a logical to indicate whether the output must be returned as a hundred fold with % sign (a character). A value of <code>0.123456</code> will then be returned as <code>"12.3%"</code>.</p></td> <td><p>a logical to indicate whether the output must be returned as a hundred fold with % sign (a character). A value of <code>0.123456</code> will then be returned as <code>"12.3%"</code>.</p></td>
</tr> </tr>
<tr> <tr>
<th>also_single_tested</th> <th>only_all_tested</th>
<td><p>a logical to indicate whether for 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</code> and R in case of <code>portion_R</code>). <strong>This could lead to selection bias.</strong></p></td> <td><p>(for combination therapies, i.e. using more than one variable for <code>...</code>) a logical to indicate that isolates must be tested for all antibiotics, see section <em>Combination therapy</em> below</p></td>
</tr> </tr>
<tr> <tr>
<th>data</th> <th>data</th>
@@ -318,35 +318,60 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
<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><strong>Remember that you should filter your table to let it contain only first isolates!</strong> Use <code><a href='first_isolate.html'>first_isolate</a></code> to determine them in your data set.</p> <p><strong>Remember that you should filter your table to let it contain only first isolates!</strong> This is needed to exclude duplicates and to reduce selection bias. Use <code><a href='first_isolate.html'>first_isolate</a></code> to determine them in your data set.</p>
<p>These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the <code><a href='count.html'>count</a></code> functions to count isolates. <em>Low counts can infuence the outcome - these <code>portion</code> functions may camouflage this, since they only return the portion albeit being dependent on the <code>minimum</code> parameter.</em></p> <p>These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the <code><a href='count.html'>count</a></code> functions to count isolates. <em>Low counts can infuence the outcome - these <code>portion</code> functions may camouflage this, since they only return the portion albeit being dependent on the <code>minimum</code> parameter.</em></p>
<p>The function <code>portion_df</code> takes any variable from <code>data</code> that has an <code>"rsi"</code> class (created with <code><a href='as.rsi.html'>as.rsi</a></code>) and calculates the portions R, I and S. The resulting <em>tidy data</em> (see Source) <code>data.frame</code> will have three rows (S/I/R) and a column for each group and each variable with class <code>"rsi"</code>.</p> <p>The function <code>portion_df</code> takes any variable from <code>data</code> that has an <code>"rsi"</code> class (created with <code><a href='as.rsi.html'>as.rsi</a></code>) and calculates the portions R, I and S. The resulting <em>tidy data</em> (see Source) <code>data.frame</code> will have three rows (S/I/R) and a column for each group and each variable with class <code>"rsi"</code>.</p>
<p>The function <code>rsi_df</code> works exactly like <code>portion_df</code>, but adds the number of isolates. <p>The function <code>rsi_df</code> works exactly like <code>portion_df</code>, but adds the number of isolates.</p>
<br /><br />
To calculate the probability (<em>p</em>) of susceptibility of one antibiotic, we use this formula: <h2 class="hasAnchor" id="combination-therapy"><a class="anchor" href="#combination-therapy"></a>Combination therapy</h2>
<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 />
<br /> <p>When using more than one variable for <code>...</code> (= combination therapy)), use <code>only_all_tested</code> to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antibiotics, Antibiotic A and Antibiotic B, about how <code>portion_SI</code> works to calculate the %SI:</p>
For two antibiotics: <pre>
<div style="text-align: center;"><img src='figures/combi_therapy_2.png' alt='' /></div> -------------------------------------------------------------------------
<br /> only_all_tested = FALSE only_all_tested = TRUE
For three antibiotics: Antibiotic Antibiotic ----------------------- -----------------------
<div style="text-align: center;"><img src='figures/combi_therapy_2.png' alt='' /></div> A B include as include as include as include as
<br /> numerator denominator numerator denominator
And so on.</p> ---------- ---------- ---------- ----------- ---------- -----------
S S X X X X
I S X X X X
R S X X X X
not tested S X X - -
S I X X X X
I I X X X X
R I X X X X
not tested I X X - -
S R X X X X
I R X X X X
R R - X - X
not tested R - - - -
S not tested X X - -
I not tested X X - -
R not tested - - - -
not tested not tested - - - -
-------------------------------------------------------------------------
</pre>
<p>Please note that for <code>only_all_tested = TRUE</code> applies that:</p><pre>
count_S() + count_I() + count_R() == count_all()
portion_S() + portion_I() + portion_R() == 1
</pre><p>and that for <code>only_all_tested = FALSE</code> applies that:</p><pre>
count_S() + count_I() + count_R() &gt;= count_all()
portion_S() + portion_I() + portion_R() &gt;= 1
</pre>
<p>Using <code>only_all_tested</code> has no impact when only using one antibiotic as input.</p>
<h2 class="hasAnchor" id="interpretation-of-s-i-and-r"><a class="anchor" href="#interpretation-of-s-i-and-r"></a>Interpretation of S, I and R</h2> <h2 class="hasAnchor" id="interpretation-of-s-i-and-r"><a class="anchor" href="#interpretation-of-s-i-and-r"></a>Interpretation of S, I and R</h2>
<p>In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".</p> <p>In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (<a href='http://www.eucast.org/newsiandr/'>http://www.eucast.org/newsiandr/</a>). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".</p>
<ul> <ul>
<li><p><strong>S</strong> - Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.</p></li> <li><p><strong>S</strong> - Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.</p></li>
<li><p><strong>I</strong> - Susceptible, increased exposure: A microorganism is categorised as "Susceptible, Increased exposure" when there is a high likelihood of therapeutic success because exposure to the agent is increased by adjusting the dosing regimen or by its concentration at the site of infection.</p></li> <li><p><strong>I</strong> - Susceptible, increased exposure: A microorganism is categorised as "Susceptible, Increased exposure" when there is a high likelihood of therapeutic success because exposure to the agent is increased by adjusting the dosing regimen or by its concentration at the site of infection.</p></li>
<li><p><strong>R</strong> - Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.</p></li> <li><p><strong>R</strong> - Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.</p></li>
</ul> </ul>
<p>Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.</p> <p>Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.</p>
<p>Source: <a href='http://www.eucast.org/newsiandr/'>http://www.eucast.org/newsiandr/</a>.</p> <p>This AMR package honours this new insight. Use <code>portion_SI</code> to determine antimicrobial susceptibility and <code><a href='count.html'>count_SI</a></code> to count susceptible isolates.</p>
<p><strong>This AMR package honours this new insight.</strong></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>
@@ -380,7 +405,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
<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'><a href='https://dplyr.tidyverse.org/reference/group_by.html'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/group_by.html'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>p</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>CIP</span>), <span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>p</span> <span class='kw'>=</span> <span class='fu'>portion_SI</span>(<span class='no'>CIP</span>),
<span class='kw'>n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>n_rsi</a></span>(<span class='no'>CIP</span>)) <span class='co'># n_rsi works like n_distinct in dplyr</span> <span class='kw'>n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>n_rsi</a></span>(<span class='no'>CIP</span>)) <span class='co'># n_rsi works like n_distinct in dplyr</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
@@ -394,32 +419,38 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
<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>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'>portion_S</span>(<span class='no'>AMC</span>) <span class='co'># S = 71.4%</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'>portion_SI</span>(<span class='no'>AMC</span>) <span class='co'># %SI = 76.3%</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>AMC</span>) <span class='co'># n = 1879</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>AMC</span>) <span class='co'># n = 1879</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'>portion_S</span>(<span class='no'>GEN</span>) <span class='co'># S = 74.0%</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'>portion_SI</span>(<span class='no'>GEN</span>) <span class='co'># %SI = 75.4%</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>GEN</span>) <span class='co'># n = 1855</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>GEN</span>) <span class='co'># n = 1855</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'>portion_S</span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>) <span class='co'># S = 92.3%</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'>portion_SI</span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>) <span class='co'># %SI = 94.1%</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>) <span class='co'># n = 1798</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>) <span class='co'># n = 1939</span>
<span class='co'># Using `also_single_tested` can be useful ...</span>
<span class='co'># See Details on how `only_all_tested` works. Example:</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'>portion_S</span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>, <span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>numerator</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_SI</a></span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>),
<span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) <span class='co'># S = 92.6%</span> <span class='kw'>denominator</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>),
<span class='co'># ... but can also lead to selection bias - the data only has 2,000 rows:</span> <span class='kw'>portion</span> <span class='kw'>=</span> <span class='fu'>portion_SI</span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>))
<span class='co'># numerator denominator portion</span>
<span class='co'># 1764 1936 0.9408</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'><a href='count.html'>count_all</a></span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>, <span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>numerator</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_SI</a></span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>, <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>),
<span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) <span class='co'># n = 2555</span> <span class='kw'>denominator</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>, <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>),
<span class='kw'>portion</span> <span class='kw'>=</span> <span class='fu'>portion_SI</span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>, <span class='kw'>only_all_tested</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>))
<span class='co'># numerator denominator portion</span>
<span class='co'># 1687 1798 0.9383</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'><a href='https://dplyr.tidyverse.org/reference/group_by.html'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/group_by.html'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>cipro_p</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>CIP</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'>cipro_p</span> <span class='kw'>=</span> <span class='fu'>portion_SI</span>(<span class='no'>CIP</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>),
<span class='kw'>cipro_n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>CIP</span>), <span class='kw'>cipro_n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>CIP</span>),
<span class='kw'>genta_p</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>GEN</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>), <span class='kw'>genta_p</span> <span class='kw'>=</span> <span class='fu'>portion_SI</span>(<span class='no'>GEN</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>),
<span class='kw'>genta_n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>GEN</span>), <span class='kw'>genta_n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>GEN</span>),
<span class='kw'>combination_p</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>CIP</span>, <span class='no'>GEN</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>), <span class='kw'>combination_p</span> <span class='kw'>=</span> <span class='fu'>portion_SI</span>(<span class='no'>CIP</span>, <span class='no'>GEN</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>),
<span class='kw'>combination_n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>CIP</span>, <span class='no'>GEN</span>)) <span class='kw'>combination_n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>CIP</span>, <span class='no'>GEN</span>))
<span class='co'># Get portions S/I/R immediately of all rsi columns</span> <span class='co'># Get portions S/I/R immediately of all rsi columns</span>
@@ -454,6 +485,8 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
<li><a href="#details">Details</a></li> <li><a href="#details">Details</a></li>
<li><a href="#combination-therapy">Combination therapy</a></li>
<li><a href="#interpretation-of-s-i-and-r">Interpretation of S, I and R</a></li> <li><a href="#interpretation-of-s-i-and-r">Interpretation of S, I and R</a></li>
<li><a href="#read-more-on-our-website-">Read more on our website!</a></li> <li><a href="#read-more-on-our-website-">Read more on our website!</a></li>

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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9004</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>

View File

@@ -81,7 +81,7 @@ When negative: the left tail is longer; the mass of the distribution is concentr
</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</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="Latest development version">0.7.1.9003</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9005</span>
</span> </span>
</div> </div>

View File

@@ -88,12 +88,9 @@ This means that looking up human pathogenic microorganisms takes less time than
\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 equal 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, previously accepted (but now invalid) taxonomic names and misspelled input}
\item{(uncertainty level 1): It tries to look for previously accepted (but now invalid) taxonomic names} \item{(uncertainty level 2): It removed parts between brackets, strips off words from the end one by one and re-evaluates the input with all previous rules}
\item{(uncertainty level 2): It strips off values between brackets and the brackets itself, and re-evaluates the input with all previous rules} \item{(uncertainty level 3): It strips off words from the start one by one and tries any part of the name}
\item{(uncertainty level 2): It strips off words from the end one by one and re-evaluates the input with all previous rules}
\item{(uncertainty level 3): It strips off words from the start one by one and re-evaluates the input with all previous rules}
\item{(uncertainty level 3): It tries any part of the name}
} }
You can also use e.g. \code{as.mo(..., allow_uncertain = 1)} to only allow up to level 1 uncertainty. You can also use e.g. \code{as.mo(..., allow_uncertain = 1)} to only allow up to level 1 uncertainty.

View File

@@ -52,7 +52,7 @@ The function \code{is.rsi.eligible} returns \code{TRUE} when a columns contains
} }
\section{Interpretation of S, I and R}{ \section{Interpretation of S, I and R}{
In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations". In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (\url{http://www.eucast.org/newsiandr/}). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".
\itemize{ \itemize{
\item{\strong{S} - }{Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.} \item{\strong{S} - }{Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.}
@@ -62,9 +62,7 @@ In 2019, EUCAST has decided to change the definitions of susceptibility testing
Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection. Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.
Source: \url{http://www.eucast.org/newsiandr/}. This AMR package honours this new insight. Use \code{\link{portion_SI}} to determine antimicrobial susceptibility and \code{\link{count_SI}} to count susceptible isolates.
\strong{This AMR package honours this new insight.}
} }
\section{Read more on our website!}{ \section{Read more on our website!}{

View File

@@ -15,19 +15,19 @@
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}
} }
\usage{ \usage{
count_R(..., also_single_tested = FALSE) count_R(..., only_all_tested = FALSE)
count_IR(..., also_single_tested = FALSE) count_IR(..., only_all_tested = FALSE)
count_I(..., also_single_tested = FALSE) count_I(..., only_all_tested = FALSE)
count_SI(..., also_single_tested = FALSE) count_SI(..., only_all_tested = FALSE)
count_S(..., also_single_tested = FALSE) count_S(..., only_all_tested = FALSE)
count_all(..., also_single_tested = FALSE) count_all(..., only_all_tested = FALSE)
n_rsi(..., also_single_tested = FALSE) n_rsi(..., only_all_tested = FALSE)
count_df(data, translate_ab = "name", language = get_locale(), count_df(data, translate_ab = "name", language = get_locale(),
combine_SI = TRUE, combine_IR = FALSE) combine_SI = TRUE, combine_IR = FALSE)
@@ -35,7 +35,7 @@ count_df(data, translate_ab = "name", language = get_locale(),
\arguments{ \arguments{
\item{...}{one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with \code{\link{as.rsi}} if needed.} \item{...}{one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with \code{\link{as.rsi}} if needed.}
\item{also_single_tested}{a logical to indicate whether for 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 could lead to selection bias.}} \item{only_all_tested}{(for combination therapies, i.e. using more than one variable for \code{...}) a logical to indicate that isolates must be tested for all antibiotics, see section \emph{Combination therapy} below}
\item{data}{a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}})} \item{data}{a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}})}
@@ -66,7 +66,7 @@ The function \code{rsi_df} works exactly like \code{count_df}, but adds the perc
} }
\section{Interpretation of S, I and R}{ \section{Interpretation of S, I and R}{
In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations". In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (\url{http://www.eucast.org/newsiandr/}). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".
\itemize{ \itemize{
\item{\strong{S} - }{Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.} \item{\strong{S} - }{Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.}
@@ -76,9 +76,51 @@ In 2019, EUCAST has decided to change the definitions of susceptibility testing
Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection. Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.
Source: \url{http://www.eucast.org/newsiandr/}. This AMR package honours this new insight. Use \code{\link{portion_SI}} to determine antimicrobial susceptibility and \code{\link{count_SI}} to count susceptible isolates.
}
\strong{This AMR package honours this new insight.} \section{Combination therapy}{
When using more than one variable for \code{...} (= combination therapy)), use \code{only_all_tested} to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antibiotics, Antibiotic A and Antibiotic B, about how \code{portion_SI} works to calculate the \%SI:
\preformatted{
-------------------------------------------------------------------------
only_all_tested = FALSE only_all_tested = TRUE
Antibiotic Antibiotic ----------------------- -----------------------
A B include as include as include as include as
numerator denominator numerator denominator
---------- ---------- ---------- ----------- ---------- -----------
S S X X X X
I S X X X X
R S X X X X
not tested S X X - -
S I X X X X
I I X X X X
R I X X X X
not tested I X X - -
S R X X X X
I R X X X X
R R - X - X
not tested R - - - -
S not tested X X - -
I not tested X X - -
R not tested - - - -
not tested not tested - - - -
-------------------------------------------------------------------------
}
Please note that for \code{only_all_tested = TRUE} applies that:
\preformatted{
count_S() + count_I() + count_R() == count_all()
portion_S() + portion_I() + portion_R() == 1
}
and that for \code{only_all_tested = FALSE} applies that:
\preformatted{
count_S() + count_I() + count_R() >= count_all()
portion_S() + portion_I() + portion_R() >= 1
}
Using \code{only_all_tested} has no impact when only using one antibiotic as input.
} }
\section{Read more on our website!}{ \section{Read more on our website!}{
@@ -105,8 +147,8 @@ n_rsi(septic_patients$AMX)
# Since n_rsi counts available isolates, you can # Since n_rsi counts available isolates, you can
# calculate back to count e.g. non-susceptible isolates. # calculate back to count e.g. non-susceptible isolates.
# This results in the same: # This results in the same:
count_IR(septic_patients$AMX) count_SI(septic_patients$AMX)
portion_IR(septic_patients$AMX) * n_rsi(septic_patients$AMX) portion_SI(septic_patients$AMX) * n_rsi(septic_patients$AMX)
library(dplyr) library(dplyr)
septic_patients \%>\% septic_patients \%>\%
@@ -120,17 +162,17 @@ septic_patients \%>\%
# 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.
# Please mind that `portion_S` calculates percentages right away instead. # Please mind that `portion_SI` calculates percentages right away instead.
count_S(septic_patients$AMC) # S = 1342 (71.4\%) count_SI(septic_patients$AMC) # 1433
count_all(septic_patients$AMC) # n = 1879 count_all(septic_patients$AMC) # 1879
count_S(septic_patients$GEN) # S = 1372 (74.0\%) count_SI(septic_patients$GEN) # 1399
count_all(septic_patients$GEN) # n = 1855 count_all(septic_patients$GEN) # 1855
with(septic_patients, with(septic_patients,
count_S(AMC, GEN)) # S = 1660 (92.3\%) count_SI(AMC, GEN)) # 1764
with(septic_patients, # n = 1798 with(septic_patients,
n_rsi(AMC, GEN)) n_rsi(AMC, GEN)) # 1936
# Get portions S/I/R immediately of all rsi columns # Get portions S/I/R immediately of all rsi columns
septic_patients \%>\% septic_patients \%>\%

View File

@@ -17,19 +17,19 @@ Wickham H. \strong{Tidy Data.} The Journal of Statistical Software, vol. 59, 201
} }
\usage{ \usage{
portion_R(..., minimum = 30, as_percent = FALSE, portion_R(..., minimum = 30, as_percent = FALSE,
also_single_tested = FALSE) only_all_tested = FALSE)
portion_IR(..., minimum = 30, as_percent = FALSE, portion_IR(..., minimum = 30, as_percent = FALSE,
also_single_tested = FALSE) only_all_tested = FALSE)
portion_I(..., minimum = 30, as_percent = FALSE, portion_I(..., minimum = 30, as_percent = FALSE,
also_single_tested = FALSE) only_all_tested = FALSE)
portion_SI(..., minimum = 30, as_percent = FALSE, portion_SI(..., minimum = 30, as_percent = FALSE,
also_single_tested = FALSE) only_all_tested = FALSE)
portion_S(..., minimum = 30, as_percent = FALSE, portion_S(..., minimum = 30, as_percent = FALSE,
also_single_tested = FALSE) only_all_tested = FALSE)
portion_df(data, translate_ab = "name", language = get_locale(), portion_df(data, translate_ab = "name", language = get_locale(),
minimum = 30, as_percent = FALSE, combine_SI = TRUE, minimum = 30, as_percent = FALSE, combine_SI = TRUE,
@@ -46,7 +46,7 @@ rsi_df(data, translate_ab = "name", language = get_locale(),
\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\%"}.}
\item{also_single_tested}{a logical to indicate whether for 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 could lead to selection bias.}} \item{only_all_tested}{(for combination therapies, i.e. using more than one variable for \code{...}) a logical to indicate that isolates must be tested for all antibiotics, see section \emph{Combination therapy} below}
\item{data}{a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}})} \item{data}{a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}})}
@@ -67,31 +67,61 @@ These functions can be used to calculate the (co-)resistance of microbial isolat
\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
} }
\details{ \details{
\strong{Remember that you should filter your table to let it contain only first isolates!} Use \code{\link{first_isolate}} to determine them in your data set. \strong{Remember that you should filter your table to let it contain only first isolates!} This is needed to exclude duplicates and to reduce selection bias. Use \code{\link{first_isolate}} to determine them in your data set.
These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. \emph{Low counts can infuence the outcome - these \code{portion} functions may camouflage this, since they only return the portion albeit being dependent on the \code{minimum} parameter.} These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. \emph{Low counts can infuence the outcome - these \code{portion} functions may camouflage this, since they only return the portion albeit being dependent on the \code{minimum} parameter.}
The function \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each group and each variable with class \code{"rsi"}. The function \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each group and each variable with class \code{"rsi"}.
The function \code{rsi_df} works exactly like \code{portion_df}, but adds the number of isolates. The function \code{rsi_df} works exactly like \code{portion_df}, but adds the number of isolates.
\if{html}{
\cr\cr
To calculate the probability (\emph{p}) of susceptibility of one antibiotic, we use this formula:
\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
\cr
For two antibiotics:
\out{<div style="text-align: center;">}\figure{combi_therapy_2.png}\out{</div>}
\cr
For three antibiotics:
\out{<div style="text-align: center;">}\figure{combi_therapy_2.png}\out{</div>}
\cr
And so on.
} }
\section{Combination therapy}{
When using more than one variable for \code{...} (= combination therapy)), use \code{only_all_tested} to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antibiotics, Antibiotic A and Antibiotic B, about how \code{portion_SI} works to calculate the \%SI:
\preformatted{
-------------------------------------------------------------------------
only_all_tested = FALSE only_all_tested = TRUE
Antibiotic Antibiotic ----------------------- -----------------------
A B include as include as include as include as
numerator denominator numerator denominator
---------- ---------- ---------- ----------- ---------- -----------
S S X X X X
I S X X X X
R S X X X X
not tested S X X - -
S I X X X X
I I X X X X
R I X X X X
not tested I X X - -
S R X X X X
I R X X X X
R R - X - X
not tested R - - - -
S not tested X X - -
I not tested X X - -
R not tested - - - -
not tested not tested - - - -
-------------------------------------------------------------------------
} }
Please note that for \code{only_all_tested = TRUE} applies that:
\preformatted{
count_S() + count_I() + count_R() == count_all()
portion_S() + portion_I() + portion_R() == 1
}
and that for \code{only_all_tested = FALSE} applies that:
\preformatted{
count_S() + count_I() + count_R() >= count_all()
portion_S() + portion_I() + portion_R() >= 1
}
Using \code{only_all_tested} has no impact when only using one antibiotic as input.
}
\section{Interpretation of S, I and R}{ \section{Interpretation of S, I and R}{
In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations". In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (\url{http://www.eucast.org/newsiandr/}). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".
\itemize{ \itemize{
\item{\strong{S} - }{Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.} \item{\strong{S} - }{Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.}
@@ -101,9 +131,7 @@ In 2019, EUCAST has decided to change the definitions of susceptibility testing
Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection. Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.
Source: \url{http://www.eucast.org/newsiandr/}. This AMR package honours this new insight. Use \code{\link{portion_SI}} to determine antimicrobial susceptibility and \code{\link{count_SI}} to count susceptible isolates.
\strong{This AMR package honours this new insight.}
} }
\section{Read more on our website!}{ \section{Read more on our website!}{
@@ -132,7 +160,7 @@ septic_patients \%>\% portion_SI(AMX)
septic_patients \%>\% septic_patients \%>\%
group_by(hospital_id) \%>\% group_by(hospital_id) \%>\%
summarise(p = portion_S(CIP), summarise(p = portion_SI(CIP),
n = n_rsi(CIP)) # n_rsi works like n_distinct in dplyr n = n_rsi(CIP)) # n_rsi works like n_distinct in dplyr
septic_patients \%>\% septic_patients \%>\%
@@ -146,32 +174,38 @@ septic_patients \%>\%
# 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:
septic_patients \%>\% portion_S(AMC) # S = 71.4\% septic_patients \%>\% portion_SI(AMC) # \%SI = 76.3\%
septic_patients \%>\% count_all(AMC) # n = 1879 septic_patients \%>\% count_all(AMC) # n = 1879
septic_patients \%>\% portion_S(GEN) # S = 74.0\% septic_patients \%>\% portion_SI(GEN) # \%SI = 75.4\%
septic_patients \%>\% count_all(GEN) # n = 1855 septic_patients \%>\% count_all(GEN) # n = 1855
septic_patients \%>\% portion_S(AMC, GEN) # S = 92.3\% septic_patients \%>\% portion_SI(AMC, GEN) # \%SI = 94.1\%
septic_patients \%>\% count_all(AMC, GEN) # n = 1798 septic_patients \%>\% count_all(AMC, GEN) # n = 1939
# Using `also_single_tested` can be useful ...
# See Details on how `only_all_tested` works. Example:
septic_patients \%>\% septic_patients \%>\%
portion_S(AMC, GEN, summarise(numerator = count_SI(AMC, GEN),
also_single_tested = TRUE) # S = 92.6\% denominator = count_all(AMC, GEN),
# ... but can also lead to selection bias - the data only has 2,000 rows: portion = portion_SI(AMC, GEN))
# numerator denominator portion
# 1764 1936 0.9408
septic_patients \%>\% septic_patients \%>\%
count_all(AMC, GEN, summarise(numerator = count_SI(AMC, GEN, only_all_tested = TRUE),
also_single_tested = TRUE) # n = 2555 denominator = count_all(AMC, GEN, only_all_tested = TRUE),
portion = portion_SI(AMC, GEN, only_all_tested = TRUE))
# numerator denominator portion
# 1687 1798 0.9383
septic_patients \%>\% septic_patients \%>\%
group_by(hospital_id) \%>\% group_by(hospital_id) \%>\%
summarise(cipro_p = portion_S(CIP, as_percent = TRUE), summarise(cipro_p = portion_SI(CIP, as_percent = TRUE),
cipro_n = count_all(CIP), cipro_n = count_all(CIP),
genta_p = portion_S(GEN, as_percent = TRUE), genta_p = portion_SI(GEN, as_percent = TRUE),
genta_n = count_all(GEN), genta_n = count_all(GEN),
combination_p = portion_S(CIP, GEN, as_percent = TRUE), combination_p = portion_SI(CIP, GEN, as_percent = TRUE),
combination_n = count_all(CIP, GEN)) combination_n = count_all(CIP, GEN))
# Get portions S/I/R immediately of all rsi columns # Get portions S/I/R immediately of all rsi columns

View File

@@ -33,20 +33,22 @@ test_that("counts work", {
library(dplyr) library(dplyr)
expect_equal(septic_patients %>% count_S(AMC), 1342) expect_equal(septic_patients %>% count_S(AMC), 1342)
expect_equal(septic_patients %>% count_S(AMC, GEN), 1660) expect_equal(septic_patients %>% count_S(AMC, GEN, only_all_tested = TRUE), 1660)
expect_equal(septic_patients %>% count_all(AMC, GEN), 1798) expect_equal(septic_patients %>% count_S(AMC, GEN, only_all_tested = FALSE), 1728)
expect_identical(septic_patients %>% count_all(AMC, GEN), expect_equal(septic_patients %>% count_all(AMC, GEN, only_all_tested = TRUE), 1798)
septic_patients %>% count_S(AMC, GEN) + expect_equal(septic_patients %>% count_all(AMC, GEN, only_all_tested = FALSE), 1936)
septic_patients %>% count_IR(AMC, GEN)) expect_identical(septic_patients %>% count_all(AMC, GEN, only_all_tested = TRUE),
septic_patients %>% count_S(AMC, GEN, only_all_tested = TRUE) +
septic_patients %>% count_IR(AMC, GEN, only_all_tested = TRUE))
# count of cases # count of cases
expect_equal(septic_patients %>% expect_equal(septic_patients %>%
group_by(hospital_id) %>% group_by(hospital_id) %>%
summarise(cipro = count_S(CIP), summarise(cipro = count_SI(CIP),
genta = count_S(GEN), genta = count_SI(GEN),
combination = count_S(CIP, GEN)) %>% combination = count_SI(CIP, GEN)) %>%
pull(combination), pull(combination),
c(192, 446, 184, 474)) c(253, 465, 192, 558))
# count_df # count_df
expect_equal( expect_equal(

View File

@@ -32,14 +32,14 @@ test_that("portions works", {
expect_equal(portion_S(septic_patients$AMX) + portion_I(septic_patients$AMX), expect_equal(portion_S(septic_patients$AMX) + portion_I(septic_patients$AMX),
portion_SI(septic_patients$AMX)) portion_SI(septic_patients$AMX))
expect_equal(septic_patients %>% portion_S(AMC), expect_equal(septic_patients %>% portion_SI(AMC),
0.7142097, 0.7626397,
tolerance = 0.0001) tolerance = 0.0001)
expect_equal(septic_patients %>% portion_S(AMC, GEN), expect_equal(septic_patients %>% portion_SI(AMC, GEN),
0.9232481, 0.9408,
tolerance = 0.0001) tolerance = 0.0001)
expect_equal(septic_patients %>% portion_S(AMC, GEN, also_single_tested = TRUE), expect_equal(septic_patients %>% portion_SI(AMC, GEN, only_all_tested = TRUE),
0.926045, 0.9382647,
tolerance = 0.0001) tolerance = 0.0001)
# percentages # percentages
@@ -57,14 +57,14 @@ test_that("portions works", {
# count of cases # count of cases
expect_equal(septic_patients %>% expect_equal(septic_patients %>%
group_by(hospital_id) %>% group_by(hospital_id) %>%
summarise(CIPo_p = portion_S(CIP, as_percent = TRUE), summarise(cipro_p = portion_SI(CIP, as_percent = TRUE),
CIPo_n = n_rsi(CIP), cipro_n = n_rsi(CIP),
GENa_p = portion_S(GEN, as_percent = TRUE), genta_p = portion_SI(GEN, as_percent = TRUE),
GENa_n = n_rsi(GEN), genta_n = n_rsi(GEN),
combination_p = portion_S(CIP, GEN, as_percent = TRUE), combination_p = portion_SI(CIP, GEN, as_percent = TRUE),
combination_n = n_rsi(CIP, GEN)) %>% combination_n = n_rsi(CIP, GEN)) %>%
pull(combination_n), pull(combination_n),
c(202, 488, 201, 499)) c(305, 617, 241, 711))
expect_warning(portion_R(as.character(septic_patients$AMC))) expect_warning(portion_R(as.character(septic_patients$AMC)))
expect_warning(portion_S(as.character(septic_patients$AMC))) expect_warning(portion_S(as.character(septic_patients$AMC)))
@@ -83,7 +83,7 @@ test_that("portions works", {
expect_error(portion_I("test", as_percent = "test")) expect_error(portion_I("test", as_percent = "test"))
expect_error(portion_S("test", minimum = "test")) expect_error(portion_S("test", minimum = "test"))
expect_error(portion_S("test", as_percent = "test")) expect_error(portion_S("test", as_percent = "test"))
expect_error(portion_S("test", also_single_tested = "test")) expect_error(portion_S("test", also_single_tested = TRUE))
# check too low amount of isolates # check too low amount of isolates
expect_identical(suppressWarnings(portion_R(septic_patients$AMX, minimum = nrow(septic_patients) + 1)), expect_identical(suppressWarnings(portion_R(septic_patients$AMX, minimum = nrow(septic_patients) + 1)),