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

added mdr_tb()

This commit is contained in:
2019-05-23 16:58:59 +02:00
parent 07d26cd485
commit 60983a1640
60 changed files with 1479 additions and 626 deletions

View File

@@ -1,6 +1,6 @@
Package: AMR
Version: 0.6.1.9034
Date: 2019-05-20
Version: 0.6.1.9035
Date: 2019-05-23
Title: Antimicrobial Resistance Analysis
Authors@R: c(
person(

View File

@@ -132,6 +132,7 @@ export(kurtosis)
export(labels_rsi_count)
export(left_join_microorganisms)
export(like)
export(mdr_tb)
export(mdro)
export(mo_authors)
export(mo_class)

10
NEWS.md
View File

@@ -1,9 +1,10 @@
# AMR 0.6.1.9001
# AMR 0.6.1.90xx
**Note: latest development version**
#### New
* 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 `as.rsi()` on an MIC value (created with `as.mic()`), a disk diffusion value (created with the new `as.disk()`) or on a complete date set containing columns with MIC or disk diffusion values.
* Function `mo_name()` as alias of `mo_fullname()`
* Added guidelines of the WHO to determine mutli-drug resistance (MDR) for TB (`mdr_tb()`) and added a new vignette about MDR
#### Changed
* Completely reworked the `antibiotics` data set:
@@ -11,7 +12,7 @@
* Column `ab` contains a human readable EARS-Net code, used by ECDC and WHO/WHONET - this is the primary identifier used in this package
* Column `atc` contains the ATC code, used by WHO/WHOCC
* Column `cid` contains the CID code (Compound ID), used by PubChem
* Based on the Compound ID, more than a thousand official brand names have been added from many different countries
* Based on the Compound ID, almost 5,000 official brand names have been added from many different countries
* All references to antibiotics in our package now use EARS-Net codes, like `AMX` for amoxicillin
* Functions `atc_certe`, `ab_umcg` and `atc_trivial_nl` have been removed
* All `atc_*` functions are superceded by `ab_*` functions
@@ -24,7 +25,10 @@
* Added ~5,000 more old taxonomic names to the `microorganisms.old` data set, which leads to better results finding when using the `as.mo()` function
* This package now honours the new EUCAST insight (2019) that S and I are but classified as susceptible, where I is defined as 'increased exposure' and not 'intermediate' anymore. For functions like `portion_df()` and `count_df()` this means that their new parameter `combine_SI` is TRUE at default.
* Removed deprecated functions `guess_mo()`, `guess_atc()`, `EUCAST_rules()`, `interpretive_reading()`, `rsi()`
* Frequency tables of microbial IDs speed improvement
* Frequency tables (`freq()`):
* speed improvement for microbial IDs
* fixed level names in markdown
*
* Removed all hardcoded EUCAST rules and replaced them with a new reference file: `./inst/eucast/eucast.tsv`
* Added ceftazidim intrinsic resistance to *Streptococci*
* Changed default settings for `age_groups()`, to let groups of fives and tens end with 100+ instead of 120+

View File

@@ -22,7 +22,7 @@
#' Data set with ~450 antibiotics
#'
#' A data set containing all antibiotics. Use \code{\link{as.ab}} or one of the \code{\link{ab_property}} functions to retrieve values from this data set. Three identifiers are included in this data set: an antibiotic ID (\code{ab}, primarily used in this package) as defined by WHONET/EARS-Net, an ATC code (\code{atc}) as defined by the WHO, and a Compound ID (\code{cid}) as found in PubChem. Other properties in this data set are derived from one or more of these codes.
#' @format A \code{\link{data.frame}} with 455 observations and 13 variables:
#' @format A \code{\link{data.frame}} with 454 observations and 13 variables:
#' \describe{
#' \item{\code{ab}}{Antibiotic ID as used in this package (like \code{AMC}), using the official EARS-Net (European Antimicrobial Resistance Surveillance Network) codes where available}
#' \item{\code{atc}}{ATC code (Anatomical Therapeutic Chemical) as defined by the WHOCC, like \code{J01CR02}}

View File

@@ -116,7 +116,7 @@ EUCAST_VERSION_EXPERT_RULES <- "3.1, 2016"
#' @export
#' @importFrom dplyr %>% select pull mutate_at vars group_by summarise n
#' @importFrom crayon bold bgGreen bgYellow bgRed black green blue italic strip_style white
#' @return The input of \code{tbl_}, possibly with edited values of antibiotics. Or, if \code{verbose = TRUE}, a \code{data.frame} with all original and new values of the affected bug-drug combinations.
#' @return The input of \code{x}, possibly with edited values of antibiotics. Or, if \code{verbose = TRUE}, a \code{data.frame} with all original and new values of the affected bug-drug combinations.
#' @source
#' \itemize{
#' \item{
@@ -184,16 +184,16 @@ eucast_rules <- function(x,
verbose = FALSE,
...) {
tbl_ <- x
x <- x
if (!is.data.frame(tbl_)) {
if (!is.data.frame(x)) {
stop("`x` must be a data frame.", call. = FALSE)
}
# try to find columns based on type
# -- mo
if (is.null(col_mo)) {
col_mo <- search_type_in_df(tbl = tbl_, type = "mo")
col_mo <- search_type_in_df(x = x, type = "mo")
}
if (is.null(col_mo)) {
stop("`col_mo` must be set.", call. = FALSE)
@@ -376,12 +376,12 @@ eucast_rules <- function(x,
edit_rsi <- function(to, rule, rows, cols) {
cols <- unique(cols[!is.na(cols) & !is.null(cols)])
if (length(rows) > 0 & length(cols) > 0) {
before_df <- tbl_original
before <- as.character(unlist(as.list(tbl_original[rows, cols])))
before_df <- x_original
before <- as.character(unlist(as.list(x_original[rows, cols])))
tryCatch(
# insert into original table
tbl_original[rows, cols] <<- to,
x_original[rows, cols] <<- to,
warning = function(w) {
if (w$message %like% 'invalid factor level') {
warning('Value "', to, '" could not be applied to column(s) `', paste(cols, collapse = '`, `'), '` because this value is not an existing factor level.', call. = FALSE)
@@ -396,9 +396,9 @@ eucast_rules <- function(x,
}
)
tbl_[rows, cols] <<- tbl_original[rows, cols]
x[rows, cols] <<- x_original[rows, cols]
after <- as.character(unlist(as.list(tbl_original[rows, cols])))
after <- as.character(unlist(as.list(x_original[rows, cols])))
# before_df might not be a data.frame, but a tibble of data.table instead
old <- as.data.frame(before_df, stringsAsFactors = FALSE)[rows,]
@@ -406,9 +406,9 @@ eucast_rules <- function(x,
for (i in 1:length(cols)) {
verbose_new <- data.frame(row = rows,
col = cols[i],
mo_fullname = tbl_[rows, "fullname"],
mo_fullname = x[rows, "fullname"],
old = as.character(old[, cols[i]]),
new = as.character(tbl_[rows, cols[i]]),
new = as.character(x[rows, cols[i]]),
rule = strip_style(rule[1]),
rule_group = strip_style(rule[2]),
rule_name = strip_style(rule[3]),
@@ -426,11 +426,11 @@ eucast_rules <- function(x,
}
# save original table
tbl_original <- tbl_
x_original <- x
# join to microorganisms data set
suppressWarnings(
tbl_ <- tbl_ %>%
x <- x %>%
mutate_at(vars(col_mo), as.mo) %>%
left_join_microorganisms(by = col_mo, suffix = c("_oldcols", "")) %>%
mutate(gramstain = mo_gramstain(pull(., col_mo), language = "en"),
@@ -448,18 +448,18 @@ eucast_rules <- function(x,
if (!ab_missing(AMP) & !ab_missing(AMX)) {
if (verbose == TRUE) {
cat("\n VERBOSE: transforming",
length(which(tbl_[, AMX] == "S" & !tbl_[, AMP] %in% c("S", "I", "R"))),
length(which(x[, AMX] == "S" & !x[, AMP] %in% c("S", "I", "R"))),
"empty ampicillin fields to 'S' based on amoxicillin. ")
cat("\n VERBOSE: transforming",
length(which(tbl_[, AMX] == "I" & !tbl_[, AMP] %in% c("S", "I", "R"))),
length(which(x[, AMX] == "I" & !x[, AMP] %in% c("S", "I", "R"))),
"empty ampicillin fields to 'I' based on amoxicillin. ")
cat("\n VERBOSE: transforming",
length(which(tbl_[, AMX] == "R" & !tbl_[, AMP] %in% c("S", "I", "R"))),
length(which(x[, AMX] == "R" & !x[, AMP] %in% c("S", "I", "R"))),
"empty ampicillin fields to 'R' based on amoxicillin. \n")
}
tbl_[which(tbl_[, AMX] == "S" & !tbl_[, AMP] %in% c("S", "I", "R")), AMP] <- "S"
tbl_[which(tbl_[, AMX] == "I" & !tbl_[, AMP] %in% c("S", "I", "R")), AMP] <- "I"
tbl_[which(tbl_[, AMX] == "R" & !tbl_[, AMP] %in% c("S", "I", "R")), AMP] <- "R"
x[which(x[, AMX] == "S" & !x[, AMP] %in% c("S", "I", "R")), AMP] <- "S"
x[which(x[, AMX] == "I" & !x[, AMP] %in% c("S", "I", "R")), AMP] <- "I"
x[which(x[, AMX] == "R" & !x[, AMP] %in% c("S", "I", "R")), AMP] <- "R"
} else if (ab_missing(AMP) & !ab_missing(AMX)) {
# ampicillin column is missing, but amoxicillin is available
message(blue(paste0("NOTE: Using column `", bold(AMX), "` as input for ampicillin (J01CA01) since many EUCAST rules depend on it.")))
@@ -605,36 +605,36 @@ eucast_rules <- function(x,
target_value <- eucast_rules_df[i, 7]
if (is.na(source_antibiotics)) {
rows <- tryCatch(which(tbl_[, col_mo_property] %like% mo_value),
rows <- tryCatch(which(x[, col_mo_property] %like% mo_value),
error = function(e) integer(0))
} else {
source_antibiotics <- get_antibiotic_columns(source_antibiotics, tbl_)
source_antibiotics <- get_antibiotic_columns(source_antibiotics, x)
if (length(source_value) == 1 & length(source_antibiotics) > 1) {
source_value <- rep(source_value, length(source_antibiotics))
}
if (length(source_antibiotics) == 0) {
rows <- integer(0)
} else if (length(source_antibiotics) == 1) {
rows <- tryCatch(which(tbl_[, col_mo_property] %like% mo_value
& tbl_[, source_antibiotics[1L]] == source_value[1L]),
rows <- tryCatch(which(x[, col_mo_property] %like% mo_value
& x[, source_antibiotics[1L]] == source_value[1L]),
error = function(e) integer(0))
} else if (length(source_antibiotics) == 2) {
rows <- tryCatch(which(tbl_[, col_mo_property] %like% mo_value
& tbl_[, source_antibiotics[1L]] == source_value[1L]
& tbl_[, source_antibiotics[2L]] == source_value[2L]),
rows <- tryCatch(which(x[, col_mo_property] %like% mo_value
& x[, source_antibiotics[1L]] == source_value[1L]
& x[, source_antibiotics[2L]] == source_value[2L]),
error = function(e) integer(0))
} else if (length(source_antibiotics) == 3) {
rows <- tryCatch(which(tbl_[, col_mo_property] %like% mo_value
& tbl_[, source_antibiotics[1L]] == source_value[1L]
& tbl_[, source_antibiotics[2L]] == source_value[2L]
& tbl_[, source_antibiotics[3L]] == source_value[3L]),
rows <- tryCatch(which(x[, col_mo_property] %like% mo_value
& x[, source_antibiotics[1L]] == source_value[1L]
& x[, source_antibiotics[2L]] == source_value[2L]
& x[, source_antibiotics[3L]] == source_value[3L]),
error = function(e) integer(0))
} else {
stop("only 3 antibiotics supported for source_antibiotics ", call. = FALSE)
}
}
cols <- get_antibiotic_columns(target_antibiotics, tbl_)
cols <- get_antibiotic_columns(target_antibiotics, x)
# Apply rule on data ------------------------------------------------------
# this will return the unique number of changes
@@ -671,7 +671,7 @@ eucast_rules <- function(x,
cat(paste0("\n", silver(strrep("-", options()$width - 1)), "\n"))
cat(bold(paste('EUCAST rules', paste0(wouldve, 'affected'),
formatnr(n_distinct(verbose_info$row)),
'out of', formatnr(nrow(tbl_original)),
'out of', formatnr(nrow(x_original)),
'rows, making a total of', formatnr(nrow(verbose_info)), 'edits\n')))
n_added <- verbose_info %>% filter(is.na(old)) %>% nrow()
@@ -742,7 +742,7 @@ eucast_rules <- function(x,
if (verbose == TRUE) {
verbose_info
} else {
tbl_original
x_original
}
}

View File

@@ -191,7 +191,7 @@ first_isolate <- function(x,
# try to find columns based on type
# -- mo
if (is.null(col_mo)) {
col_mo <- search_type_in_df(tbl = x, type = "mo")
col_mo <- search_type_in_df(x = x, type = "mo")
}
if (is.null(col_mo)) {
stop("`col_mo` must be set.", call. = FALSE)
@@ -199,7 +199,7 @@ first_isolate <- function(x,
# -- date
if (is.null(col_date)) {
col_date <- search_type_in_df(tbl = x, type = "date")
col_date <- search_type_in_df(x = x, type = "date")
}
if (is.null(col_date)) {
stop("`col_date` must be set.", call. = FALSE)
@@ -217,7 +217,7 @@ first_isolate <- function(x,
col_patient_id <- "patient_id"
message(blue(paste0("NOTE: Using combined columns ", bold("`First name`, `Last name` and `Sex`"), " as input for `col_patient_id`.")))
} else {
col_patient_id <- search_type_in_df(tbl = x, type = "patient_id")
col_patient_id <- search_type_in_df(x = x, type = "patient_id")
}
}
if (is.null(col_patient_id)) {
@@ -226,7 +226,7 @@ first_isolate <- function(x,
# -- key antibiotics
if (is.null(col_keyantibiotics)) {
col_keyantibiotics <- search_type_in_df(tbl = x, type = "keyantibiotics")
col_keyantibiotics <- search_type_in_df(x = x, type = "keyantibiotics")
}
if (isFALSE(col_keyantibiotics)) {
col_keyantibiotics <- NULL
@@ -234,7 +234,7 @@ first_isolate <- function(x,
# -- specimen
if (is.null(col_specimen)) {
col_specimen <- search_type_in_df(tbl = x, type = "specimen")
col_specimen <- search_type_in_df(x = x, type = "specimen")
}
if (isFALSE(col_specimen)) {
col_specimen <- NULL

View File

@@ -336,9 +336,10 @@ frequency_tbl <- function(x,
cols <- unlist(strsplit(x.name, "$", fixed = TRUE))[2]
x.name <- unlist(strsplit(x.name, "$", fixed = TRUE))[1]
# try to find the object to determine dimensions
x.obj <- tryCatch(get(x.name), error = function(e) NULL)
x.name <- paste0("`", x.name , "`")
if (!is.null(x.obj)) {
if (!is.null(dim(x.obj))) {
x.name <- paste0(x.name,
" (",
x.obj %>%
@@ -664,6 +665,10 @@ format_header <- function(x, markdown = FALSE, decimal.mark = ".", big.mark = ",
if (nchar(levels_text) > 70) {
# levels text wider than half the console
levels_text <- paste0(substr(levels_text, 1, 70 - 3), "...")
if (nchar(gsub("[^`]", "", levels_text)) %% 2 == 1) {
# odd number of backticks, should be even
levels_text <- paste0(levels_text, "`")
}
}
header$levels <- paste0(length(header$levels), ": ", levels_text)
header <- header[names(header) != "ordered"]

View File

@@ -22,7 +22,7 @@
#' Key antibiotics for first \emph{weighted} isolates
#'
#' These function can be used to determine first isolates (see \code{\link{first_isolate}}). Using key antibiotics to determine first isolates is more reliable than without key antibiotics. These selected isolates will then be called first \emph{weighted} isolates.
#' @param tbl table with antibiotics coloms, like \code{amox} and \code{amcl}.
#' @param x table with antibiotics coloms, like \code{AMX} or \code{amox}
#' @param x,y characters to compare
#' @inheritParams first_isolate
#' @param universal_1,universal_2,universal_3,universal_4,universal_5,universal_6 column names of \strong{broad-spectrum} antibiotics, case-insensitive. At default, the columns containing these antibiotics will be guessed with \code{\link{guess_ab_col}}.
@@ -76,33 +76,33 @@
#'
#' key_antibiotics_equal(strainA, strainB, ignore_I = FALSE)
#' # FALSE, because I is not ignored and so the 4th value differs
key_antibiotics <- function(tbl,
key_antibiotics <- function(x,
col_mo = NULL,
universal_1 = guess_ab_col(tbl, "AMX"),
universal_2 = guess_ab_col(tbl, "AMC"),
universal_3 = guess_ab_col(tbl, "CXM"),
universal_4 = guess_ab_col(tbl, "TZP"),
universal_5 = guess_ab_col(tbl, "CIP"),
universal_6 = guess_ab_col(tbl, "SXT"),
GramPos_1 = guess_ab_col(tbl, "VAN"),
GramPos_2 = guess_ab_col(tbl, "TEC"),
GramPos_3 = guess_ab_col(tbl, "TCY"),
GramPos_4 = guess_ab_col(tbl, "ERY"),
GramPos_5 = guess_ab_col(tbl, "OXA"),
GramPos_6 = guess_ab_col(tbl, "RIF"),
GramNeg_1 = guess_ab_col(tbl, "GEN"),
GramNeg_2 = guess_ab_col(tbl, "TOB"),
GramNeg_3 = guess_ab_col(tbl, "COL"),
GramNeg_4 = guess_ab_col(tbl, "CTX"),
GramNeg_5 = guess_ab_col(tbl, "CAZ"),
GramNeg_6 = guess_ab_col(tbl, "MEM"),
universal_1 = guess_ab_col(x, "AMX"),
universal_2 = guess_ab_col(x, "AMC"),
universal_3 = guess_ab_col(x, "CXM"),
universal_4 = guess_ab_col(x, "TZP"),
universal_5 = guess_ab_col(x, "CIP"),
universal_6 = guess_ab_col(x, "SXT"),
GramPos_1 = guess_ab_col(x, "VAN"),
GramPos_2 = guess_ab_col(x, "TEC"),
GramPos_3 = guess_ab_col(x, "TCY"),
GramPos_4 = guess_ab_col(x, "ERY"),
GramPos_5 = guess_ab_col(x, "OXA"),
GramPos_6 = guess_ab_col(x, "RIF"),
GramNeg_1 = guess_ab_col(x, "GEN"),
GramNeg_2 = guess_ab_col(x, "TOB"),
GramNeg_3 = guess_ab_col(x, "COL"),
GramNeg_4 = guess_ab_col(x, "CTX"),
GramNeg_5 = guess_ab_col(x, "CAZ"),
GramNeg_6 = guess_ab_col(x, "MEM"),
warnings = TRUE,
...) {
# try to find columns based on type
# -- mo
if (is.null(col_mo)) {
col_mo <- search_type_in_df(tbl = tbl, type = "mo")
col_mo <- search_type_in_df(x = x, type = "mo")
}
if (is.null(col_mo)) {
stop("`col_mo` must be set.", call. = FALSE)
@@ -112,7 +112,7 @@ key_antibiotics <- function(tbl,
col.list <- c(universal_1, universal_2, universal_3, universal_4, universal_5, universal_6,
GramPos_1, GramPos_2, GramPos_3, GramPos_4, GramPos_5, GramPos_6,
GramNeg_1, GramNeg_2, GramNeg_3, GramNeg_4, GramNeg_5, GramNeg_6)
check_available_columns <- function(tbl, col.list, info = TRUE) {
check_available_columns <- function(x, col.list, info = TRUE) {
# check columns
col.list <- col.list[!is.na(col.list) & !is.null(col.list)]
names(col.list) <- col.list
@@ -121,18 +121,18 @@ key_antibiotics <- function(tbl,
for (i in 1:length(col.list)) {
if (is.null(col.list[i]) | isTRUE(is.na(col.list[i]))) {
col.list[i] <- NA
} else if (toupper(col.list[i]) %in% colnames(tbl)) {
} else if (toupper(col.list[i]) %in% colnames(x)) {
col.list[i] <- toupper(col.list[i])
} else if (tolower(col.list[i]) %in% colnames(tbl)) {
} else if (tolower(col.list[i]) %in% colnames(x)) {
col.list[i] <- tolower(col.list[i])
} else if (!col.list[i] %in% colnames(tbl)) {
} else if (!col.list[i] %in% colnames(x)) {
col.list[i] <- NA
}
}
if (!all(col.list %in% colnames(tbl))) {
if (!all(col.list %in% colnames(x))) {
if (info == TRUE) {
warning('Some columns do not exist and will be ignored: ',
col.list.bak[!(col.list %in% colnames(tbl))] %>% toString(),
col.list.bak[!(col.list %in% colnames(x))] %>% toString(),
'.\nTHIS MAY STRONGLY INFLUENCE THE OUTCOME.',
immediate. = TRUE,
call. = FALSE)
@@ -141,7 +141,7 @@ key_antibiotics <- function(tbl,
col.list
}
col.list <- check_available_columns(tbl = tbl, col.list = col.list, info = warnings)
col.list <- check_available_columns(x = x, col.list = col.list, info = warnings)
universal_1 <- col.list[universal_1]
universal_2 <- col.list[universal_2]
universal_3 <- col.list[universal_3]
@@ -183,30 +183,30 @@ key_antibiotics <- function(tbl,
}
# join to microorganisms data set
tbl <- tbl %>%
x <- x %>%
mutate_at(vars(col_mo), as.mo) %>%
left_join_microorganisms(by = col_mo) %>%
mutate(key_ab = NA_character_,
gramstain = mo_gramstain(pull(., col_mo)))
# Gram +
tbl <- tbl %>% mutate(key_ab =
x <- x %>% mutate(key_ab =
if_else(gramstain == "Gram positive",
apply(X = tbl[, gram_positive],
apply(X = x[, gram_positive],
MARGIN = 1,
FUN = function(x) paste(x, collapse = "")),
key_ab))
# Gram -
tbl <- tbl %>% mutate(key_ab =
x <- x %>% mutate(key_ab =
if_else(gramstain == "Gram negative",
apply(X = tbl[, gram_negative],
apply(X = x[, gram_negative],
MARGIN = 1,
FUN = function(x) paste(x, collapse = "")),
key_ab))
# format
key_abs <- tbl %>%
key_abs <- x %>%
pull(key_ab) %>%
gsub('(NA|NULL)', '.', .) %>%
gsub('[^SIR]', '.', ., ignore.case = TRUE)

282
R/mdro.R
View File

@@ -23,12 +23,25 @@
#'
#' Determine which isolates are multidrug-resistant organisms (MDRO) according to country-specific guidelines.
#' @param x table with antibiotic columns, like e.g. \code{AMX} and \code{AMC}
#' @param country country code to determine guidelines. EUCAST rules will be used when left empty, see Details. Should be or a code from the \href{https://en.wikipedia.org/wiki/ISO_3166-1_alpha-2#Officially_assigned_code_elements}{list of ISO 3166-1 alpha-2 country codes}. Case-insensitive. Currently supported are \code{de} (Germany) and \code{nl} (the Netherlands).
#' @param country country code to determine guidelines. Should be or a code from the \href{https://en.wikipedia.org/wiki/ISO_3166-1_alpha-2#Officially_assigned_code_elements}{list of ISO 3166-1 alpha-2 country codes}. Case-insensitive.
#' @param guideline a specific guideline to mention. For some countries this will be determined automatically, see Details. EUCAST guidelines will be used when left empty, see Details.
#' @param info print progress
#' @inheritParams eucast_rules
#' @param verbose print additional info: missing antibiotic columns per parameter
#' @inheritSection eucast_rules Antibiotics
#' @details When \code{country} will be left blank, guidelines will be taken from EUCAST Expert Rules Version 3.1 "Intrinsic Resistance and Exceptional Phenotypes Tables" (\href{http://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf}{link}).
#' @details When \code{country} is set, the parameter guideline will be ignored as these guidelines will be used:
#'
#' \itemize{
#' \item{\code{country = "nl"}: Rijksinstituut voor Volksgezondheid en Milieu "WIP-richtlijn BRMO (Bijzonder Resistente Micro-Organismen) [ZKH]" (\href{https://www.rivm.nl/Documenten_en_publicaties/Professioneel_Praktisch/Richtlijnen/Infectieziekten/WIP_Richtlijnen/WIP_Richtlijnen/Ziekenhuizen/WIP_richtlijn_BRMO_Bijzonder_Resistente_Micro_Organismen_ZKH}{link})}
#' }
#'
#' Please suggest your own country's specific guidelines by letting us know: \url{https://gitlab.com/msberends/AMR/issues/new}.
#'
#' Other currently supported guidelines are:
#' \itemize{
#' \item{\code{guideline = "eucast"}: EUCAST Expert Rules Version 3.1 "Intrinsic Resistance and Exceptional Phenotypes Tables" (\href{http://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf}{link})}
#' \item{\code{guideline = "tb"}: World Health Organization "Companion handbook to the WHO guidelines for the programmatic management of drug-resistant tuberculosis" (\href{https://www.who.int/tb/publications/pmdt_companionhandbook/en/}{link})}
#' }
#' @return Ordered factor with levels \code{Negative < Positive, unconfirmed < Positive}.
#' @rdname mdro
#' @importFrom dplyr %>%
@@ -43,21 +56,41 @@
#' BRMO = brmo(.))
mdro <- function(x,
country = NULL,
guideline = NULL,
col_mo = NULL,
info = TRUE,
verbose = FALSE,
...) {
tbl_ <- x
if (!is.data.frame(tbl_)) {
if (!is.data.frame(x)) {
stop("`x` must be a data frame.", call. = FALSE)
}
if (length(guideline) > 1) {
stop("`guideline` must be a length one character string.", call. = FALSE)
}
if (!is.null(country)) {
guideline <- country
}
if (is.null(guideline)) {
guideline <- "eucast"
}
if (!tolower(guideline) %in% c("nl", "de", "eucast", "tb")) {
stop("invalid guideline: ", guideline, call. = FALSE)
}
guideline <- list(code = tolower(guideline))
# try to find columns based on type
# -- mo
if (is.null(col_mo)) {
col_mo <- search_type_in_df(tbl = tbl_, type = "mo")
col_mo <- search_type_in_df(x = x, type = "mo")
}
if (is.null(col_mo) & guideline$code == "tb") {
message(blue("NOTE: No column found as input for `col_mo`,",
bold("assuming all records contain",
italic("Mycobacterium tuberculosis."))))
x$mo <- AMR::as.mo("Mycobacterium tuberculosis")
col_mo <- "mo"
}
if (is.null(col_mo)) {
stop("`col_mo` must be set.", call. = FALSE)
@@ -67,50 +100,59 @@ mdro <- function(x,
stop("`country` must be a length one character string.", call. = FALSE)
}
if (is.null(country)) {
country <- "EUCAST"
}
country <- trimws(country)
if (tolower(country) != "eucast" & !country %like% "^[a-z]{2}$") {
stop("This is not a valid ISO 3166-1 alpha-2 country code: '", country, "'. Please see ?mdro.", call. = FALSE)
}
# create list and make country code case-independent
guideline <- list(country = list(code = tolower(country)))
if (guideline$country$code == "eucast") {
guideline$country$name <- "(European guidelines)"
if (guideline$code == "eucast") {
guideline$name <- "EUCAST Expert Rules, \"Intrinsic Resistance and Exceptional Phenotypes Tables\""
guideline$version <- "Version 3.1"
guideline$author <- "EUCAST (European Committee on Antimicrobial Susceptibility Testing)"
guideline$version <- "3.1"
guideline$source <- "http://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf"
} else if (guideline$code == "tb") {
guideline$name <- "Companion handbook to the WHO guidelines for the programmatic management of drug-resistant tuberculosis"
guideline$author <- "WHO (World Health Organization)"
guideline$version <- "WHO/HTM/TB/2014.11"
guideline$source <- "https://www.who.int/tb/publications/pmdt_companionhandbook/en/"
# support per country:
} else if (guideline$country$code == "de") {
guideline$country$name <- "Germany"
} else if (guideline$code == "de") {
guideline$name <- "Germany"
guideline$name <- ""
guideline$version <- ""
guideline$source <- ""
} else if (guideline$country$code == "nl") {
guideline$country$name <- "The Netherlands"
guideline$name <- "WIP-Richtlijn BRMO"
} else if (guideline$code == "nl") {
guideline$name <- "WIP-Richtlijn Bijzonder Resistente Micro-organismen (BRMO)"
guideline$author <- "RIVM (Rijksinstituut voor de Volksgezondheid)"
guideline$version <- "Revision as of December 2017"
guideline$source <- "https://www.rivm.nl/Documenten_en_publicaties/Professioneel_Praktisch/Richtlijnen/Infectieziekten/WIP_Richtlijnen/WIP_Richtlijnen/Ziekenhuizen/WIP_richtlijn_BRMO_Bijzonder_Resistente_Micro_Organismen_ZKH"
# add here more countries like this:
# } else if (country$code == "xx") {
# country$name <- "country name"
} else {
stop("This country code is currently unsupported: ", guideline$country$code, call. = FALSE)
stop("This guideline is currently unsupported: ", guideline$code, call. = FALSE)
}
if (info == TRUE) {
cat("Determining multidrug-resistant organisms (MDRO), according to:\n",
"Guideline: ", red(paste0(guideline$name, ", ", guideline$version, "\n")),
"Country : ", red(paste0(guideline$country$name, "\n")),
"Source : ", blue(paste0(guideline$source, "\n")),
"Guideline: ", red(guideline$name), "\n",
"Version: ", red(guideline$version), "\n",
"Author: ", red(guideline$author), "\n",
"Source: ", blue(guideline$source), "\n",
"\n", sep = "")
}
if (guideline$code == "tb") {
cols_ab <- get_column_abx(x = x,
soft_dependencies = c("CAP",
"ETH",
"GAT",
"INH",
"PZA",
"RIF",
"RIB",
"RFP"),
verbose = verbose, ...)
} else {
cols_ab <- get_column_abx(x = x, verbose = verbose, ...)
}
AMC <- cols_ab["AMC"]
AMK <- cols_ab["AMK"]
@@ -175,7 +217,20 @@ mdro <- function(x,
TOB <- cols_ab["TOB"]
TZP <- cols_ab["TZP"]
VAN <- cols_ab["VAN"]
# additional for TB
CAP <- cols_ab["CAP"]
ETH <- cols_ab["ETH"]
GAT <- cols_ab["GAT"]
INH <- cols_ab["INH"]
PZA <- cols_ab["PZA"]
RIF <- cols_ab["RIF"]
RIB <- cols_ab["RIB"]
RFP <- cols_ab["RFP"]
abx_tb <- c(CAP, ETH, GAT, INH, PZA, RIF, RIB, RFP)
abx_tb <- abx_tb[!is.na(abx_tb)]
if (guideline$code == "tb" & length(abx_tb) == 0) {
stop("No antimycobacterials found in data set.", call. = FALSE)
}
ab_missing <- function(ab) {
isTRUE(ab %in% c(NULL, NA)) | length(ab) == 0
@@ -194,96 +249,96 @@ mdro <- function(x,
cols <- cols[!is.na(cols)]
if (length(rows) > 0 & length(cols) > 0) {
if (any_all == "any") {
row_filter <- which(tbl_[, cols] == "R")
row_filter <- which(x[, cols] == "R")
} else if (any_all == "all") {
row_filter <- tbl_ %>%
row_filter <- x %>%
mutate(index = 1:nrow(.)) %>%
filter_at(vars(cols), all_vars(. == "R")) %>%
pull((index))
}
rows <- rows[rows %in% row_filter]
tbl_[rows, "MDRO"] <<- to
x[rows, "MDRO"] <<- to
}
}
tbl_ <- tbl_ %>%
x <- x %>%
mutate_at(vars(col_mo), as.mo) %>%
# join to microorganisms data set
left_join_microorganisms(by = col_mo) %>%
# add unconfirmed to where genus is available
mutate(MDRO = ifelse(!is.na(genus), 1, NA_integer_))
if (guideline$country$code == "eucast") {
if (guideline$code == "eucast") {
# EUCAST ------------------------------------------------------------------
# Table 5
trans_tbl(3,
which(tbl_$family == "Enterobacteriaceae"
| tbl_$fullname %like% "^Pseudomonas aeruginosa"
| tbl_$genus == "Acinetobacter"),
which(x$family == "Enterobacteriaceae"
| x$fullname %like% "^Pseudomonas aeruginosa"
| x$genus == "Acinetobacter"),
COL,
"all")
trans_tbl(3,
which(tbl_$fullname %like% "^Salmonella Typhi"),
which(x$fullname %like% "^Salmonella Typhi"),
c(carbapenems, fluoroquinolones),
"any")
trans_tbl(3,
which(tbl_$fullname %like% "^Haemophilus influenzae"),
which(x$fullname %like% "^Haemophilus influenzae"),
c(cephalosporins_3rd, carbapenems, fluoroquinolones),
"any")
trans_tbl(3,
which(tbl_$fullname %like% "^Moraxella catarrhalis"),
which(x$fullname %like% "^Moraxella catarrhalis"),
c(cephalosporins_3rd, fluoroquinolones),
"any")
trans_tbl(3,
which(tbl_$fullname %like% "^Neisseria meningitidis"),
which(x$fullname %like% "^Neisseria meningitidis"),
c(cephalosporins_3rd, fluoroquinolones),
"any")
trans_tbl(3,
which(tbl_$fullname %like% "^Neisseria gonorrhoeae"),
which(x$fullname %like% "^Neisseria gonorrhoeae"),
AZM,
"any")
# Table 6
trans_tbl(3,
which(tbl_$fullname %like% "^Staphylococcus (aureus|epidermidis|coagulase negatief|hominis|haemolyticus|intermedius|pseudointermedius)"),
which(x$fullname %like% "^Staphylococcus (aureus|epidermidis|coagulase negatief|hominis|haemolyticus|intermedius|pseudointermedius)"),
c(VAN, TEC, DAP, LNZ, QDA, TGC),
"any")
trans_tbl(3,
which(tbl_$genus == "Corynebacterium"),
which(x$genus == "Corynebacterium"),
c(VAN, TEC, DAP, LNZ, QDA, TGC),
"any")
trans_tbl(3,
which(tbl_$fullname %like% "^Streptococcus pneumoniae"),
which(x$fullname %like% "^Streptococcus pneumoniae"),
c(carbapenems, VAN, TEC, DAP, LNZ, QDA, TGC, RIF),
"any")
trans_tbl(3, # Sr. groups A/B/C/G
which(tbl_$fullname %like% "^Streptococcus (pyogenes|agalactiae|equisimilis|equi|zooepidemicus|dysgalactiae|anginosus)"),
which(x$fullname %like% "^Streptococcus (pyogenes|agalactiae|equisimilis|equi|zooepidemicus|dysgalactiae|anginosus)"),
c(PEN, cephalosporins, VAN, TEC, DAP, LNZ, QDA, TGC),
"any")
trans_tbl(3,
which(tbl_$genus == "Enterococcus"),
which(x$genus == "Enterococcus"),
c(DAP, LNZ, TGC, TEC),
"any")
trans_tbl(3,
which(tbl_$fullname %like% "^Enterococcus faecalis"),
which(x$fullname %like% "^Enterococcus faecalis"),
c(AMP, AMX),
"any")
# Table 7
trans_tbl(3,
which(tbl_$genus == "Bacteroides"),
which(x$genus == "Bacteroides"),
MTR,
"any")
trans_tbl(3,
which(tbl_$fullname %like% "^Clostridium difficile"),
which(x$fullname %like% "^Clostridium difficile"),
c(MTR, VAN),
"any")
}
if (guideline$country$code == "de") {
if (guideline$code == "de") {
# Germany -----------------------------------------------------------------
stop("We are still working on German guidelines in this beta version.", call. = FALSE)
}
if (guideline$country$code == "nl") {
if (guideline$code == "nl") {
# Netherlands -------------------------------------------------------------
aminoglycosides <- aminoglycosides[!is.na(aminoglycosides)]
fluoroquinolones <- fluoroquinolones[!is.na(fluoroquinolones)]
@@ -298,32 +353,32 @@ mdro <- function(x,
# Table 1
trans_tbl(3,
which(tbl_$family == "Enterobacteriaceae"),
which(x$family == "Enterobacteriaceae"),
c(aminoglycosides, fluoroquinolones),
"all")
trans_tbl(2,
which(tbl_$family == "Enterobacteriaceae"),
which(x$family == "Enterobacteriaceae"),
carbapenems,
"any")
trans_tbl(2,
which(tbl_$family == "Enterobacteriaceae"),
which(x$family == "Enterobacteriaceae"),
ESBLs,
"all")
# Table 2
trans_tbl(2,
which(tbl_$genus == "Acinetobacter"),
which(x$genus == "Acinetobacter"),
c(carbapenems),
"any")
trans_tbl(3,
which(tbl_$genus == "Acinetobacter"),
which(x$genus == "Acinetobacter"),
c(aminoglycosides, fluoroquinolones),
"all")
trans_tbl(3,
which(tbl_$fullname %like% "^Stenotrophomonas maltophilia"),
which(x$fullname %like% "^Stenotrophomonas maltophilia"),
SXT,
"all")
@@ -332,39 +387,108 @@ mdro <- function(x,
& !ab_missing(CIP)
& !ab_missing(CAZ)
& !ab_missing(TZP) ) {
tbl_$psae <- 0
tbl_[which(tbl_[, MEM] == "R" | tbl_[, IPM] == "R"), "psae"] <- 1 + tbl_[which(tbl_[, MEM] == "R" | tbl_[, IPM] == "R"), "psae"]
tbl_[which(tbl_[, GEN] == "R" & tbl_[, TOB] == "R"), "psae"] <- 1 + tbl_[which(tbl_[, GEN] == "R" & tbl_[, TOB] == "R"), "psae"]
tbl_[which(tbl_[, CIP] == "R"), "psae"] <- 1 + tbl_[which(tbl_[, CIP] == "R"), "psae"]
tbl_[which(tbl_[, CAZ] == "R"), "psae"] <- 1 + tbl_[which(tbl_[, CAZ] == "R"), "psae"]
tbl_[which(tbl_[, TZP] == "R"), "psae"] <- 1 + tbl_[which(tbl_[, TZP] == "R"), "psae"]
x$psae <- 0
x[which(x[, MEM] == "R" | x[, IPM] == "R"), "psae"] <- 1 + x[which(x[, MEM] == "R" | x[, IPM] == "R"), "psae"]
x[which(x[, GEN] == "R" & x[, TOB] == "R"), "psae"] <- 1 + x[which(x[, GEN] == "R" & x[, TOB] == "R"), "psae"]
x[which(x[, CIP] == "R"), "psae"] <- 1 + x[which(x[, CIP] == "R"), "psae"]
x[which(x[, CAZ] == "R"), "psae"] <- 1 + x[which(x[, CAZ] == "R"), "psae"]
x[which(x[, TZP] == "R"), "psae"] <- 1 + x[which(x[, TZP] == "R"), "psae"]
} else {
tbl_$psae <- 0
x$psae <- 0
}
tbl_[which(
tbl_$fullname %like% "Pseudomonas aeruginosa"
& tbl_$psae >= 3
x[which(
x$fullname %like% "Pseudomonas aeruginosa"
& x$psae >= 3
), "MDRO"] <- 3
# Table 3
trans_tbl(3,
which(tbl_$fullname %like% "Streptococcus pneumoniae"),
which(x$fullname %like% "Streptococcus pneumoniae"),
PEN,
"all")
trans_tbl(3,
which(tbl_$fullname %like% "Streptococcus pneumoniae"),
which(x$fullname %like% "Streptococcus pneumoniae"),
VAN,
"all")
trans_tbl(3,
which(tbl_$fullname %like% "Enterococcus faecium"),
which(x$fullname %like% "Enterococcus faecium"),
c(PEN, VAN),
"all")
}
factor(x = tbl_$MDRO,
prepare_drug <- function(ab) {
# returns vector values of drug
# if `ab` is a column name, looks up the values in `x`
if (length(ab) == 1 & is.character(ab)) {
if (ab %in% colnames(x)) {
ab <- as.data.frame(x)[, ab]
}
}
ab <- as.character(as.rsi(ab))
ab[is.na(ab)] <- ""
ab
}
drug_is_R <- function(ab) {
# returns logical vector
ab <- prepare_drug(ab)
if (length(ab) == 1) {
rep(ab, NROW(x)) == "R"
} else {
ab == "R"
}
}
drug_is_not_R <- function(ab) {
# returns logical vector
ab <- prepare_drug(ab)
if (length(ab) == 1) {
rep(ab, NROW(x)) != "R"
} else {
ab != "R"
}
}
if (guideline$code == "tb") {
# Tuberculosis ------------------------------------------------------------
x <- x %>%
mutate(mono_count = 0,
mono_count = ifelse(drug_is_R(INH), mono_count + 1, mono_count),
mono_count = ifelse(drug_is_R(RIF), mono_count + 1, mono_count),
mono_count = ifelse(drug_is_R(ETH), mono_count + 1, mono_count),
mono_count = ifelse(drug_is_R(PZA), mono_count + 1, mono_count),
mono_count = ifelse(drug_is_R(RIB), mono_count + 1, mono_count),
mono_count = ifelse(drug_is_R(RFP), mono_count + 1, mono_count),
# from here on logicals
mono = mono_count > 0,
poly = ifelse(mono_count > 1 & drug_is_not_R(RIF) & drug_is_not_R(INH),
TRUE, FALSE),
mdr = ifelse(drug_is_R(RIF) & drug_is_R(INH),
TRUE, FALSE),
xdr = ifelse(drug_is_R(LVX) | drug_is_R(MFX) | drug_is_R(GAT),
TRUE, FALSE),
second = ifelse(drug_is_R(CAP) | drug_is_R(KAN) | drug_is_R(AMK),
TRUE, FALSE),
xdr = ifelse(mdr & xdr & second, TRUE, FALSE)) %>%
mutate(mdr_tb = case_when(xdr ~ 5,
mdr ~ 4,
poly ~ 3,
mono ~ 2,
TRUE ~ 1),
# keep all real TB, make other species NA
mdr_tb = ifelse(x$fullname == "Mycobacterium tuberculosis", mdr_tb, NA_real_))
}
# return results
if (guideline$code == "tb") {
factor(x = x$mdr_tb,
levels = 1:5,
labels = c("Negative", "Mono-resistance", "Poly-resistance", "Multidrug resistance", "Extensive drug resistance"),
ordered = TRUE)
} else {
factor(x = x$MDRO,
levels = 1:3,
labels = c("Negative", "Positive, unconfirmed", "Positive"),
ordered = TRUE)
}
}
#' @rdname mdro
@@ -381,6 +505,12 @@ mrgn <- function(x, country = "de", ...) {
#' @rdname mdro
#' @export
eucast_exceptional_phenotypes <- function(x, country = "EUCAST", ...) {
mdro(x = x, country = "EUCAST", ...)
mdr_tb <- function(x, guideline = "TB", ...) {
mdro(x = x, guideline = "TB", ...)
}
#' @rdname mdro
#' @export
eucast_exceptional_phenotypes <- function(x, guideline = "EUCAST", ...) {
mdro(x = x, guideline = "EUCAST", ...)
}

View File

@@ -87,43 +87,43 @@ percent <- function(x, round = 1, force_zero = FALSE, decimal.mark = getOption("
#' @importFrom crayon blue bold red
#' @importFrom dplyr %>% pull
search_type_in_df <- function(tbl, type) {
search_type_in_df <- function(x, type) {
# try to find columns based on type
found <- NULL
colnames(tbl) <- trimws(colnames(tbl))
colnames(x) <- trimws(colnames(x))
# -- mo
if (type == "mo") {
if ("mo" %in% lapply(tbl, class)) {
found <- colnames(tbl)[lapply(tbl, class) == "mo"][1]
} else if (any(colnames(tbl) %like% "^(mo|microorganism|organism|bacteria)")) {
found <- colnames(tbl)[colnames(tbl) %like% "^(mo|microorganism|organism|bacteria)"][1]
} else if (any(colnames(tbl) %like% "species")) {
found <- colnames(tbl)[colnames(tbl) %like% "species"][1]
if ("mo" %in% lapply(x, class)) {
found <- colnames(x)[lapply(x, class) == "mo"][1]
} else if (any(colnames(x) %like% "^(mo|microorganism|organism|bacteria)s?$")) {
found <- colnames(x)[colnames(x) %like% "^(mo|microorganism|organism|bacteria)s?$"][1]
} else if (any(colnames(x) %like% "species")) {
found <- colnames(x)[colnames(x) %like% "species"][1]
}
}
# -- key antibiotics
if (type == "keyantibiotics") {
if (any(colnames(tbl) %like% "^key.*(ab|antibiotics)")) {
found <- colnames(tbl)[colnames(tbl) %like% "^key.*(ab|antibiotics)"][1]
if (any(colnames(x) %like% "^key.*(ab|antibiotics)")) {
found <- colnames(x)[colnames(x) %like% "^key.*(ab|antibiotics)"][1]
}
}
# -- date
if (type == "date") {
if (any(colnames(tbl) %like% "^(specimen date|specimen_date|spec_date)")) {
if (any(colnames(x) %like% "^(specimen date|specimen_date|spec_date)")) {
# WHONET support
found <- colnames(tbl)[colnames(tbl) %like% "^(specimen date|specimen_date|spec_date)"][1]
if (!any(class(tbl %>% pull(found)) %in% c("Date", "POSIXct"))) {
found <- colnames(x)[colnames(x) %like% "^(specimen date|specimen_date|spec_date)"][1]
if (!any(class(x %>% pull(found)) %in% c("Date", "POSIXct"))) {
stop(red(paste0("ERROR: Found column `", bold(found), "` to be used as input for `col_", type,
"`, but this column contains no valid dates. Transform its values to valid dates first.")),
call. = FALSE)
}
} else {
for (i in 1:ncol(tbl)) {
if (any(class(tbl %>% pull(i)) %in% c("Date", "POSIXct"))) {
found <- colnames(tbl)[i]
for (i in 1:ncol(x)) {
if (any(class(x %>% pull(i)) %in% c("Date", "POSIXct"))) {
found <- colnames(x)[i]
break
}
}
@@ -131,16 +131,16 @@ search_type_in_df <- function(tbl, type) {
}
# -- patient id
if (type == "patient_id") {
if (any(colnames(tbl) %like% "^(identification |patient|patid)")) {
found <- colnames(tbl)[colnames(tbl) %like% "^(identification |patient|patid)"][1]
if (any(colnames(x) %like% "^(identification |patient|patid)")) {
found <- colnames(x)[colnames(x) %like% "^(identification |patient|patid)"][1]
}
}
# -- specimen
if (type == "specimen") {
if (any(colnames(tbl) %like% "(specimen type|spec_type)")) {
found <- colnames(tbl)[colnames(tbl) %like% "(specimen type|spec_type)"][1]
} else if (any(colnames(tbl) %like% "^(specimen)")) {
found <- colnames(tbl)[colnames(tbl) %like% "^(specimen)"][1]
if (any(colnames(x) %like% "(specimen type|spec_type)")) {
found <- colnames(x)[colnames(x) %like% "(specimen type|spec_type)"][1]
} else if (any(colnames(x) %like% "^(specimen)")) {
found <- colnames(x)[colnames(x) %like% "^(specimen)"][1]
}
}

View File

@@ -31,7 +31,7 @@
#' @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}}
#' @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 below. Default is now \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}.
#' @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.

View File

@@ -140,7 +140,7 @@ resistance_predict <- function(x,
# -- date
if (is.null(col_date)) {
col_date <- search_type_in_df(tbl = x, type = "date")
col_date <- search_type_in_df(x = x, type = "date")
}
if (is.null(col_date)) {
stop("`col_date` must be set.", call. = FALSE)

30
R/rsi.R
View File

@@ -39,9 +39,9 @@
#' 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".
#'
#' \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{I}}{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.}
#' \item{\strong{R}}{Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.}
#' \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{I} - }{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.}
#' \item{\strong{R} - }{Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.}
#' }
#'
#' 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.
@@ -259,9 +259,9 @@ exec_as.rsi <- function(method, x, mo, ab, guideline) {
#' @importFrom crayon red blue
#' @export
as.rsi.data.frame <- function(x, col_mo = NULL, guideline = "EUCAST", ...) {
tbl_ <- x
x <- x
ab_cols <- colnames(tbl_)[sapply(tbl_, function(x) is.mic(x) | is.disk(x))]
ab_cols <- colnames(x)[sapply(x, function(y) is.mic(y) | is.disk(y))]
if (length(ab_cols) == 0) {
stop("No columns with MIC values or disk zones found in this data set. Use as.mic or as.disk to transform antibiotic columns.", call. = FALSE)
}
@@ -269,14 +269,14 @@ as.rsi.data.frame <- function(x, col_mo = NULL, guideline = "EUCAST", ...) {
# try to find columns based on type
# -- mo
if (is.null(col_mo)) {
col_mo <- search_type_in_df(tbl = tbl_, type = "mo")
col_mo <- search_type_in_df(x = x, type = "mo")
}
if (is.null(col_mo)) {
stop("`col_mo` must be set.", call. = FALSE)
}
# transform all MICs
ab_cols <- colnames(tbl_)[sapply(tbl_, is.mic)]
ab_cols <- colnames(x)[sapply(x, is.mic)]
if (length(ab_cols) > 0) {
for (i in 1:length(ab_cols)) {
if (is.na(suppressWarnings(as.ab(ab_cols[i])))) {
@@ -284,16 +284,16 @@ as.rsi.data.frame <- function(x, col_mo = NULL, guideline = "EUCAST", ...) {
next
}
message(blue(paste0("Interpreting column `", bold(ab_cols[i]), "` (", ab_name(ab_cols[i], tolower = TRUE), ")...")), appendLF = FALSE)
tbl_[, ab_cols[i]] <- exec_as.rsi(method = "mic",
x = tbl_ %>% pull(ab_cols[i]),
mo = tbl_ %>% pull(col_mo),
x[, ab_cols[i]] <- exec_as.rsi(method = "mic",
x = x %>% pull(ab_cols[i]),
mo = x %>% pull(col_mo),
ab = as.ab(ab_cols[i]),
guideline = guideline)
message(blue(" OK."))
}
}
# transform all disks
ab_cols <- colnames(tbl_)[sapply(tbl_, is.disk)]
ab_cols <- colnames(x)[sapply(x, is.disk)]
if (length(ab_cols) > 0) {
for (i in 1:length(ab_cols)) {
if (is.na(suppressWarnings(as.ab(ab_cols[i])))) {
@@ -301,16 +301,16 @@ as.rsi.data.frame <- function(x, col_mo = NULL, guideline = "EUCAST", ...) {
next
}
message(blue(paste0("Interpreting column `", bold(ab_cols[i]), "` (", ab_name(ab_cols[i], tolower = TRUE), ")...")), appendLF = FALSE)
tbl_[, ab_cols[i]] <- exec_as.rsi(method = "disk",
x = tbl_ %>% pull(ab_cols[i]),
mo = tbl_ %>% pull(col_mo),
x[, ab_cols[i]] <- exec_as.rsi(method = "disk",
x = x %>% pull(ab_cols[i]),
mo = x %>% pull(col_mo),
ab = as.ab(ab_cols[i]),
guideline = guideline)
message(blue(" OK."))
}
}
tbl_
x
}
#' @rdname as.rsi

View File

@@ -38,6 +38,9 @@ navbar:
- text: 'Predict antimicrobial resistance'
icon: 'fa-dice'
href: 'articles/resistance_predict.html'
- text: 'Determine multi-drug resistance (MDR)'
icon: 'fa-skull-crossbones'
href: 'articles/MDR.html'
- text: 'Work with WHONET data'
icon: 'fa-globe-americas'
href: 'articles/WHONET.html'

Binary file not shown.

View File

@@ -78,7 +78,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9034</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -114,6 +114,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="articles/WHONET.html">
<span class="fa fa-globe-americas"></span>

View File

@@ -40,7 +40,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9034</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -76,6 +76,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -192,7 +199,7 @@
<h1>How to conduct AMR analysis</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">20 May 2019</h4>
<h4 class="date">23 May 2019</h4>
<div class="hidden name"><code>AMR.Rmd</code></div>
@@ -201,7 +208,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 20 May 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 23 May 2019.</p>
<div id="introduction" class="section level1">
<h1 class="hasAnchor">
<a href="#introduction" class="anchor"></a>Introduction</h1>
@@ -217,21 +224,21 @@
</tr></thead>
<tbody>
<tr class="odd">
<td align="center">2019-05-20</td>
<td align="center">2019-05-23</td>
<td align="center">abcd</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">S</td>
</tr>
<tr class="even">
<td align="center">2019-05-20</td>
<td align="center">2019-05-23</td>
<td align="center">abcd</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">R</td>
</tr>
<tr class="odd">
<td align="center">2019-05-20</td>
<td align="center">2019-05-23</td>
<td align="center">efgh</td>
<td align="center">Escherichia coli</td>
<td align="center">R</td>
@@ -327,66 +334,66 @@
</tr></thead>
<tbody>
<tr class="odd">
<td align="center">2013-08-26</td>
<td align="center">Q7</td>
<td align="center">Hospital A</td>
<td align="center">2012-10-26</td>
<td align="center">T6</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">R</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="even">
<td align="center">2012-10-04</td>
<td align="center">2011-10-13</td>
<td align="center">Y4</td>
<td align="center">Hospital B</td>
<td align="center">Streptococcus pneumoniae</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="odd">
<td align="center">2010-02-09</td>
<td align="center">O2</td>
<td align="center">Hospital A</td>
<td align="center">Escherichia coli</td>
<td align="center">Hospital B</td>
<td align="center">Streptococcus pneumoniae</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="odd">
<td align="center">2012-10-23</td>
<td align="center">C4</td>
<td align="center">Hospital C</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td>
</tr>
<tr class="even">
<td align="center">2011-08-17</td>
<td align="center">R4</td>
<td align="center">2010-09-18</td>
<td align="center">T5</td>
<td align="center">Hospital B</td>
<td align="center">Escherichia coli</td>
<td align="center">R</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">F</td>
</tr>
<tr class="odd">
<td align="center">2016-01-18</td>
<td align="center">L2</td>
<td align="center">Hospital B</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">2017-07-26</td>
<td align="center">J10</td>
<td align="center">Hospital D</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">M</td>
</tr>
<tr class="even">
<td align="center">2011-09-06</td>
<td align="center">O1</td>
<td align="center">Hospital A</td>
<td align="center">Escherichia coli</td>
<td align="center">R</td>
<td align="center">2015-09-19</td>
<td align="center">P5</td>
<td align="center">Hospital D</td>
<td align="center">Streptococcus pneumoniae</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
@@ -411,8 +418,8 @@
#
# Item Count Percent Cum. Count Cum. Percent
# --- ----- ------- -------- ----------- -------------
# 1 M 10,378 51.9% 10,378 51.9%
# 2 F 9,622 48.1% 20,000 100.0%</code></pre>
# 1 M 10,310 51.6% 10,310 51.6%
# 2 F 9,690 48.4% 20,000 100.0%</code></pre>
<p>So, we can draw at least two conclusions immediately. From a data scientist perspective, the data looks clean: only values <code>M</code> and <code>F</code>. From a researcher perspective: there are slightly more men. Nothing we didnt already know.</p>
<p>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>
@@ -442,14 +449,14 @@
<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-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 (1443 new changes)</span></a>
<a class="sourceLine" id="cb14-21" title="21"><span class="co"># Streptococcus pneumoniae (1542 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-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 (1303 new changes)</span></a>
<a class="sourceLine" id="cb14-25" title="25"><span class="co"># Table 01: Intrinsic resistance in Enterobacteriaceae (1286 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-28" title="28"><span class="co"># Table 04: Intrinsic resistance in Gram-positive bacteria (2746 new changes)</span></a>
<a class="sourceLine" id="cb14-28" title="28"><span class="co"># Table 04: Intrinsic resistance in Gram-positive bacteria (2788 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-31" title="31"><span class="co"># Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins (no new changes)</span></a>
@@ -457,24 +464,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-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-36" title="36"><span class="co"># Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (2313 new changes)</span></a>
<a class="sourceLine" id="cb14-37" title="37"><span class="co"># Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (115 new changes)</span></a>
<a class="sourceLine" id="cb14-36" title="36"><span class="co"># Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (2231 new changes)</span></a>
<a class="sourceLine" id="cb14-37" title="37"><span class="co"># Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (126 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-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-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-44" title="44"><span class="co"># EUCAST rules affected 6,579 out of 20,000 rows, making a total of 7,920 edits</span></a>
<a class="sourceLine" id="cb14-44" title="44"><span class="co"># EUCAST rules affected 6,562 out of 20,000 rows, making a total of 7,973 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-46" title="46"><span class="co"># </span></a>
<a class="sourceLine" id="cb14-47" title="47"><span class="co"># =&gt; changed 7,920 test results</span></a>
<a class="sourceLine" id="cb14-48" title="48"><span class="co"># - 123 test results changed from S to I</span></a>
<a class="sourceLine" id="cb14-49" title="49"><span class="co"># - 4,680 test results changed from S to R</span></a>
<a class="sourceLine" id="cb14-50" title="50"><span class="co"># - 1,131 test results changed from I to S</span></a>
<a class="sourceLine" id="cb14-51" title="51"><span class="co"># - 306 test results changed from I to R</span></a>
<a class="sourceLine" id="cb14-52" title="52"><span class="co"># - 1,657 test results changed from R to S</span></a>
<a class="sourceLine" id="cb14-53" title="53"><span class="co"># - 23 test results changed from R to I</span></a>
<a class="sourceLine" id="cb14-47" title="47"><span class="co"># =&gt; changed 7,973 test results</span></a>
<a class="sourceLine" id="cb14-48" title="48"><span class="co"># - 114 test results changed from S to I</span></a>
<a class="sourceLine" id="cb14-49" title="49"><span class="co"># - 4,779 test results changed from S to R</span></a>
<a class="sourceLine" id="cb14-50" title="50"><span class="co"># - 1,118 test results changed from I to S</span></a>
<a class="sourceLine" id="cb14-51" title="51"><span class="co"># - 330 test results changed from I to R</span></a>
<a class="sourceLine" id="cb14-52" title="52"><span class="co"># - 1,606 test results changed from R to S</span></a>
<a class="sourceLine" id="cb14-53" title="53"><span class="co"># - 26 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-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>
@@ -502,8 +509,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-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-6" title="6"><span class="co"># =&gt; Found 5,674 first isolates (28.4% of total)</span></a></code></pre></div>
<p>So only 28.4% is suitable for resistance analysis! We can now filter on it with the <code><a href="https://dplyr.tidyverse.org/reference/filter.html">filter()</a></code> function, also from the <code>dplyr</code> package:</p>
<a class="sourceLine" id="cb16-6" title="6"><span class="co"># =&gt; Found 5,699 first isolates (28.5% of total)</span></a></code></pre></div>
<p>So only 28.5% 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>
<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>
@@ -529,8 +536,8 @@
<tbody>
<tr class="odd">
<td align="center">1</td>
<td align="center">2010-03-19</td>
<td align="center">N8</td>
<td align="center">2010-04-13</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
@@ -540,10 +547,10 @@
</tr>
<tr class="even">
<td align="center">2</td>
<td align="center">2010-05-06</td>
<td align="center">N8</td>
<td align="center">2010-06-02</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
@@ -551,43 +558,43 @@
</tr>
<tr class="odd">
<td align="center">3</td>
<td align="center">2010-05-20</td>
<td align="center">N8</td>
<td align="center">2010-07-21</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">I</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>
</tr>
<tr class="even">
<td align="center">4</td>
<td align="center">2010-07-20</td>
<td align="center">N8</td>
<td align="center">2010-09-19</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">FALSE</td>
</tr>
<tr class="odd">
<td align="center">5</td>
<td align="center">2010-09-04</td>
<td align="center">N8</td>
<td align="center">2010-09-19</td>
<td align="center">S1</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">FALSE</td>
</tr>
<tr class="even">
<td align="center">6</td>
<td align="center">2010-09-13</td>
<td align="center">N8</td>
<td align="center">2010-10-14</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
@@ -595,19 +602,19 @@
</tr>
<tr class="odd">
<td align="center">7</td>
<td align="center">2011-04-01</td>
<td align="center">N8</td>
<td align="center">2010-10-28</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">TRUE</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">8</td>
<td align="center">2011-10-15</td>
<td align="center">N8</td>
<td align="center">2010-12-09</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
@@ -617,8 +624,8 @@
</tr>
<tr class="odd">
<td align="center">9</td>
<td align="center">2011-11-14</td>
<td align="center">N8</td>
<td align="center">2010-12-15</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
@@ -628,18 +635,18 @@
</tr>
<tr class="even">
<td align="center">10</td>
<td align="center">2012-02-11</td>
<td align="center">N8</td>
<td align="center">2011-01-07</td>
<td align="center">S1</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">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
</tr>
</tbody>
</table>
<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>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>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>
<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 +657,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-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-10" title="10"><span class="co"># =&gt; Found 14,968 first weighted isolates (74.8% of total)</span></a></code></pre></div>
<a class="sourceLine" id="cb19-10" title="10"><span class="co"># =&gt; Found 15,125 first weighted isolates (75.6% of total)</span></a></code></pre></div>
<table class="table">
<thead><tr class="header">
<th align="center">isolate</th>
@@ -667,8 +674,8 @@
<tbody>
<tr class="odd">
<td align="center">1</td>
<td align="center">2010-03-19</td>
<td align="center">N8</td>
<td align="center">2010-04-13</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
@@ -679,58 +686,58 @@
</tr>
<tr class="even">
<td align="center">2</td>
<td align="center">2010-05-06</td>
<td align="center">N8</td>
<td align="center">2010-06-02</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
<td align="center">FALSE</td>
</tr>
<tr class="odd">
<td align="center">3</td>
<td align="center">2010-05-20</td>
<td align="center">N8</td>
<td align="center">2010-07-21</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">I</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>
</tr>
<tr class="even">
<td align="center">4</td>
<td align="center">2010-07-20</td>
<td align="center">N8</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">5</td>
<td align="center">2010-09-04</td>
<td align="center">N8</td>
<tr class="even">
<td align="center">4</td>
<td align="center">2010-09-19</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td>
</tr>
<tr class="odd">
<td align="center">5</td>
<td align="center">2010-09-19</td>
<td align="center">S1</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">6</td>
<td align="center">2010-09-13</td>
<td align="center">N8</td>
<td align="center">2010-10-14</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
@@ -739,20 +746,20 @@
</tr>
<tr class="odd">
<td align="center">7</td>
<td align="center">2011-04-01</td>
<td align="center">N8</td>
<td align="center">2010-10-28</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">TRUE</td>
<td align="center">TRUE</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">8</td>
<td align="center">2011-10-15</td>
<td align="center">N8</td>
<td align="center">2010-12-09</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
@@ -763,8 +770,8 @@
</tr>
<tr class="odd">
<td align="center">9</td>
<td align="center">2011-11-14</td>
<td align="center">N8</td>
<td align="center">2010-12-15</td>
<td align="center">S1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
@@ -775,23 +782,23 @@
</tr>
<tr class="even">
<td align="center">10</td>
<td align="center">2012-02-11</td>
<td align="center">N8</td>
<td align="center">2011-01-07</td>
<td align="center">S1</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">I</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>
</tr>
</tbody>
</table>
<p>Instead of 2, now 7 isolates are flagged. In total, 74.8% of all isolates are marked first weighted - 46.5% 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 1, now 7 isolates are flagged. In total, 75.6% of all isolates are marked first weighted - 47.1% 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>
<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>
<p>So we end up with 14,968 isolates for analysis.</p>
<p>So we end up with 15,125 isolates for analysis.</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>
<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,6 +806,7 @@
<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">
<thead><tr class="header">
<th></th>
<th align="center">date</th>
<th align="center">patient_id</th>
<th align="center">hospital</th>
@@ -815,12 +823,13 @@
</tr></thead>
<tbody>
<tr class="odd">
<td align="center">2013-08-26</td>
<td align="center">Q7</td>
<td align="center">Hospital A</td>
<td>1</td>
<td align="center">2012-10-26</td>
<td align="center">T6</td>
<td align="center">Hospital D</td>
<td align="center">B_STPHY_AUR</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">F</td>
@@ -830,9 +839,58 @@
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">2012-10-04</td>
<td>2</td>
<td align="center">2011-10-13</td>
<td align="center">Y4</td>
<td align="center">Hospital B</td>
<td align="center">B_STRPT_PNE</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">F</td>
<td align="center">Gram positive</td>
<td align="center">Streptococcus</td>
<td align="center">pneumoniae</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td>3</td>
<td align="center">2010-02-09</td>
<td align="center">O2</td>
<td align="center">Hospital A</td>
<td align="center">Hospital B</td>
<td align="center">B_STRPT_PNE</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">F</td>
<td align="center">Gram positive</td>
<td align="center">Streptococcus</td>
<td align="center">pneumoniae</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td>6</td>
<td align="center">2015-09-19</td>
<td align="center">P5</td>
<td align="center">Hospital D</td>
<td align="center">B_STRPT_PNE</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">F</td>
<td align="center">Gram positive</td>
<td align="center">Streptococcus</td>
<td align="center">pneumoniae</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td>7</td>
<td align="center">2011-05-13</td>
<td align="center">X5</td>
<td align="center">Hospital B</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
@@ -844,60 +902,16 @@
<td align="center">coli</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">2012-10-23</td>
<td align="center">C4</td>
<tr class="even">
<td>8</td>
<td align="center">2015-03-07</td>
<td align="center">Z7</td>
<td align="center">Hospital C</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">M</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">2011-08-17</td>
<td align="center">R4</td>
<td align="center">Hospital B</td>
<td align="center">B_ESCHR_COL</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">Escherichia</td>
<td align="center">coli</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">2016-01-18</td>
<td align="center">L2</td>
<td align="center">Hospital B</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">M</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">2011-09-06</td>
<td align="center">O1</td>
<td align="center">Hospital A</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">F</td>
<td align="center">Gram negative</td>
<td align="center">Escherichia</td>
@@ -921,9 +935,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>
<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>
<p><strong>Frequency table of <code>genus</code> and <code>species</code> from a <code>data.frame</code> (14,968 x 13)</strong></p>
<p><strong>Frequency table of <code>genus</code> and <code>species</code> from a <code>data.frame</code> (15,125 x 13)</strong></p>
<p>Columns: 2<br>
Length: 14,968 (of which NA: 0 = 0.00%)<br>
Length: 15,125 (of which NA: 0 = 0.00%)<br>
Unique: 4</p>
<p>Shortest: 16<br>
Longest: 24</p>
@@ -940,33 +954,33 @@ Longest: 24</p>
<tr class="odd">
<td align="left">1</td>
<td align="left">Escherichia coli</td>
<td align="right">7,394</td>
<td align="right">49.4%</td>
<td align="right">7,394</td>
<td align="right">49.4%</td>
<td align="right">7,486</td>
<td align="right">49.5%</td>
<td align="right">7,486</td>
<td align="right">49.5%</td>
</tr>
<tr class="even">
<td align="left">2</td>
<td align="left">Staphylococcus aureus</td>
<td align="right">3,716</td>
<td align="right">24.8%</td>
<td align="right">11,110</td>
<td align="right">3,731</td>
<td align="right">24.7%</td>
<td align="right">11,217</td>
<td align="right">74.2%</td>
</tr>
<tr class="odd">
<td align="left">3</td>
<td align="left">Streptococcus pneumoniae</td>
<td align="right">2,291</td>
<td align="right">15.3%</td>
<td align="right">13,401</td>
<td align="right">89.5%</td>
<td align="right">2,360</td>
<td align="right">15.6%</td>
<td align="right">13,577</td>
<td align="right">89.8%</td>
</tr>
<tr class="even">
<td align="left">4</td>
<td align="left">Klebsiella pneumoniae</td>
<td align="right">1,567</td>
<td align="right">10.5%</td>
<td align="right">14,968</td>
<td align="right">1,548</td>
<td align="right">10.2%</td>
<td align="right">15,125</td>
<td align="right">100.0%</td>
</tr>
</tbody>
@@ -977,7 +991,7 @@ Longest: 24</p>
<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>
<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.4659941</span></a></code></pre></div>
<a class="sourceLine" id="cb25-2" title="2"><span class="co"># [1] 0.4628099</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>
<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>
@@ -990,19 +1004,19 @@ Longest: 24</p>
<tbody>
<tr class="odd">
<td align="center">Hospital A</td>
<td align="center">0.4708540</td>
<td align="center">0.4556355</td>
</tr>
<tr class="even">
<td align="center">Hospital B</td>
<td align="center">0.4617585</td>
<td align="center">0.4661553</td>
</tr>
<tr class="odd">
<td align="center">Hospital C</td>
<td align="center">0.4622030</td>
<td align="center">0.4759657</td>
</tr>
<tr class="even">
<td align="center">Hospital D</td>
<td align="center">0.4691689</td>
<td align="center">0.4577347</td>
</tr>
</tbody>
</table>
@@ -1020,23 +1034,23 @@ Longest: 24</p>
<tbody>
<tr class="odd">
<td align="center">Hospital A</td>
<td align="center">0.4708540</td>
<td align="center">4426</td>
<td align="center">0.4556355</td>
<td align="center">4587</td>
</tr>
<tr class="even">
<td align="center">Hospital B</td>
<td align="center">0.4617585</td>
<td align="center">5243</td>
<td align="center">0.4661553</td>
<td align="center">5215</td>
</tr>
<tr class="odd">
<td align="center">Hospital C</td>
<td align="center">0.4622030</td>
<td align="center">2315</td>
<td align="center">0.4759657</td>
<td align="center">2330</td>
</tr>
<tr class="even">
<td align="center">Hospital D</td>
<td align="center">0.4691689</td>
<td align="center">2984</td>
<td align="center">0.4577347</td>
<td align="center">2993</td>
</tr>
</tbody>
</table>
@@ -1056,27 +1070,27 @@ Longest: 24</p>
<tbody>
<tr class="odd">
<td align="center">Escherichia</td>
<td align="center">0.9249391</td>
<td align="center">0.8991074</td>
<td align="center">0.9935082</td>
<td align="center">0.9226556</td>
<td align="center">0.8966070</td>
<td align="center">0.9941224</td>
</tr>
<tr class="even">
<td align="center">Klebsiella</td>
<td align="center">0.8162093</td>
<td align="center">0.9119336</td>
<td align="center">0.9910657</td>
<td align="center">0.8113695</td>
<td align="center">0.9102067</td>
<td align="center">0.9909561</td>
</tr>
<tr class="odd">
<td align="center">Staphylococcus</td>
<td align="center">0.9179225</td>
<td align="center">0.9198062</td>
<td align="center">0.9916577</td>
<td align="center">0.9187885</td>
<td align="center">0.9193246</td>
<td align="center">0.9949075</td>
</tr>
<tr class="even">
<td align="center">Streptococcus</td>
<td align="center">0.6294195</td>
<td align="center">0.6152542</td>
<td align="center">0.0000000</td>
<td align="center">0.6294195</td>
<td align="center">0.6152542</td>
</tr>
</tbody>
</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: 19 KiB

After

Width:  |  Height:  |  Size: 19 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 67 KiB

After

Width:  |  Height:  |  Size: 67 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 50 KiB

After

Width:  |  Height:  |  Size: 50 KiB

View File

@@ -40,7 +40,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9034</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -76,6 +76,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -192,7 +199,7 @@
<h1>How to apply EUCAST rules</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">20 May 2019</h4>
<h4 class="date">23 May 2019</h4>
<div class="hidden name"><code>EUCAST.Rmd</code></div>

View File

@@ -40,7 +40,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -76,6 +76,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -192,7 +199,7 @@
<h1>How to use the <em>G</em>-test</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">17 May 2019</h4>
<h4 class="date">23 May 2019</h4>
<div class="hidden name"><code>G_test.Rmd</code></div>

323
docs/articles/MDR.html Normal file
View File

@@ -0,0 +1,323 @@
<!DOCTYPE html>
<!-- Generated by pkgdown: do not edit by hand --><html lang="en">
<head>
<meta http-equiv="Content-Type" content="text/html; charset=UTF-8">
<meta charset="utf-8">
<meta http-equiv="X-UA-Compatible" content="IE=edge">
<meta name="viewport" content="width=device-width, initial-scale=1.0">
<title>How to determine multi-drug resistance (MDR) • AMR (for R)</title>
<!-- favicons --><link rel="icon" type="image/png" sizes="16x16" href="../favicon-16x16.png">
<link rel="icon" type="image/png" sizes="32x32" href="../favicon-32x32.png">
<link rel="apple-touch-icon" type="image/png" sizes="180x180" href="../apple-touch-icon.png">
<link rel="apple-touch-icon" type="image/png" sizes="120x120" href="../apple-touch-icon-120x120.png">
<link rel="apple-touch-icon" type="image/png" sizes="76x76" href="../apple-touch-icon-76x76.png">
<link rel="apple-touch-icon" type="image/png" sizes="60x60" href="../apple-touch-icon-60x60.png">
<!-- jquery --><script src="https://cdnjs.cloudflare.com/ajax/libs/jquery/3.3.1/jquery.min.js" integrity="sha256-FgpCb/KJQlLNfOu91ta32o/NMZxltwRo8QtmkMRdAu8=" crossorigin="anonymous"></script><!-- Bootstrap --><link href="https://cdnjs.cloudflare.com/ajax/libs/bootswatch/3.3.7/flatly/bootstrap.min.css" rel="stylesheet" crossorigin="anonymous">
<script src="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.3.7/js/bootstrap.min.js" integrity="sha256-U5ZEeKfGNOja007MMD3YBI0A3OSZOQbeG6z2f2Y0hu8=" crossorigin="anonymous"></script><!-- Font Awesome icons --><link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/4.7.0/css/font-awesome.min.css" integrity="sha256-eZrrJcwDc/3uDhsdt61sL2oOBY362qM3lon1gyExkL0=" crossorigin="anonymous">
<!-- clipboard.js --><script src="https://cdnjs.cloudflare.com/ajax/libs/clipboard.js/2.0.4/clipboard.min.js" integrity="sha256-FiZwavyI2V6+EXO1U+xzLG3IKldpiTFf3153ea9zikQ=" crossorigin="anonymous"></script><!-- sticky kit --><script src="https://cdnjs.cloudflare.com/ajax/libs/sticky-kit/1.1.3/sticky-kit.min.js" integrity="sha256-c4Rlo1ZozqTPE2RLuvbusY3+SU1pQaJC0TjuhygMipw=" crossorigin="anonymous"></script><!-- pkgdown --><link href="../pkgdown.css" rel="stylesheet">
<script src="../pkgdown.js"></script><!-- docsearch --><script src="../docsearch.js"></script><link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/docsearch.js/2.6.1/docsearch.min.css" integrity="sha256-QOSRU/ra9ActyXkIBbiIB144aDBdtvXBcNc3OTNuX/Q=" crossorigin="anonymous">
<link href="../docsearch.css" rel="stylesheet">
<script src="https://cdnjs.cloudflare.com/ajax/libs/mark.js/8.11.1/jquery.mark.min.js" integrity="sha256-4HLtjeVgH0eIB3aZ9mLYF6E8oU5chNdjU6p6rrXpl9U=" crossorigin="anonymous"></script><link href="../extra.css" rel="stylesheet">
<script src="../extra.js"></script><meta property="og:title" content="How to determine multi-drug resistance (MDR)">
<meta property="og:description" content="">
<meta property="og:image" content="https://msberends.gitlab.io/AMR/logo.png">
<meta name="twitter:card" content="summary">
<!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]>
<script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script>
<script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script>
<![endif]-->
</head>
<body>
<div class="container template-article">
<header><div class="navbar navbar-default navbar-fixed-top" role="navigation">
<div class="container">
<div class="navbar-header">
<button type="button" class="navbar-toggle collapsed" data-toggle="collapse" data-target="#navbar" aria-expanded="false">
<span class="sr-only">Toggle navigation</span>
<span class="icon-bar"></span>
<span class="icon-bar"></span>
<span class="icon-bar"></span>
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
<div id="navbar" class="navbar-collapse collapse">
<ul class="nav navbar-nav">
<li>
<a href="../index.html">
<span class="fa fa-home"></span>
Home
</a>
</li>
<li class="dropdown">
<a href="#" class="dropdown-toggle" data-toggle="dropdown" role="button" aria-expanded="false">
<span class="fa fa-question-circle"></span>
How to
<span class="caret"></span>
</a>
<ul class="dropdown-menu" role="menu">
<li>
<a href="../articles/AMR.html">
<span class="fa fa-directions"></span>
Conduct AMR analysis
</a>
</li>
<li>
<a href="../articles/resistance_predict.html">
<span class="fa fa-dice"></span>
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
Work with WHONET data
</a>
</li>
<li>
<a href="../articles/SPSS.html">
<span class="fa fa-file-upload"></span>
Import data from SPSS/SAS/Stata
</a>
</li>
<li>
<a href="../articles/EUCAST.html">
<span class="fa fa-exchange-alt"></span>
Apply EUCAST rules
</a>
</li>
<li>
<a href="../reference/mo_property.html">
<span class="fa fa-bug"></span>
Get properties of a microorganism
</a>
</li>
<li>
<a href="../reference/ab_property.html">
<span class="fa fa-capsules"></span>
Get properties of an antibiotic
</a>
</li>
<li>
<a href="../articles/freq.html">
<span class="fa fa-sort-amount-down"></span>
Create frequency tables
</a>
</li>
<li>
<a href="../articles/G_test.html">
<span class="fa fa-clipboard-check"></span>
Use the G-test
</a>
</li>
<li>
<a href="../articles/benchmarks.html">
<span class="fa fa-shipping-fast"></span>
Other: benchmarks
</a>
</li>
</ul>
</li>
<li>
<a href="../reference/">
<span class="fa fa-book-open"></span>
Manual
</a>
</li>
<li>
<a href="../authors.html">
<span class="fa fa-users"></span>
Authors
</a>
</li>
<li>
<a href="../news/">
<span class="far fa far fa-newspaper"></span>
Changelog
</a>
</li>
</ul>
<ul class="nav navbar-nav navbar-right">
<li>
<a href="https://gitlab.com/msberends/AMR">
<span class="fab fa fab fa-gitlab"></span>
Source Code
</a>
</li>
<li>
<a href="../LICENSE-text.html">
<span class="fa fa-book"></span>
Licence
</a>
</li>
</ul>
<form class="navbar-form navbar-right" role="search">
<div class="form-group">
<input type="search" class="form-control" name="search-input" id="search-input" placeholder="Search..." aria-label="Search for..." autocomplete="off">
</div>
</form>
</div>
<!--/.nav-collapse -->
</div>
<!--/.container -->
</div>
<!--/.navbar -->
</header><div class="row">
<div class="col-md-9 contents">
<div class="page-header toc-ignore">
<h1>How to determine multi-drug resistance (MDR)</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">23 May 2019</h4>
<div class="hidden name"><code>MDR.Rmd</code></div>
</div>
<p>With the function <code><a href="../reference/mdro.html">mdro()</a></code>, you can determine multi-drug resistant organisms (MDRO). It currently support these guidelines:</p>
<ul>
<li>“Intrinsic Resistance and Exceptional Phenotypes Tables”, by EUCAST (European Committee on Antimicrobial Susceptibility Testing)</li>
<li>“Companion handbook to the WHO guidelines for the programmatic management of drug-resistant tuberculosis”, by WHO (World Health Organization)</li>
<li>“WIP-Richtlijn Bijzonder Resistente Micro-organismen (BRMO)”, by RIVM (Rijksinstituut voor de Volksgezondheid, the Netherlands National Institute for Public Health and the Environment)</li>
</ul>
<p>As an example, I will make a data set to determine multi-drug resistant TB:</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"># a helper function to get a random vector with values S, I and R</span></a>
<a class="sourceLine" id="cb1-2" title="2"><span class="co"># with the probabilities 50%-10%-40%</span></a>
<a class="sourceLine" id="cb1-3" title="3">sample_rsi &lt;-<span class="st"> </span><span class="cf">function</span>() {</a>
<a class="sourceLine" id="cb1-4" title="4"> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/sample">sample</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="st">"S"</span>, <span class="st">"I"</span>, <span class="st">"R"</span>),</a>
<a class="sourceLine" id="cb1-5" title="5"> <span class="dt">size =</span> <span class="dv">5000</span>,</a>
<a class="sourceLine" id="cb1-6" title="6"> <span class="dt">prob =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="fl">0.5</span>, <span class="fl">0.1</span>, <span class="fl">0.4</span>),</a>
<a class="sourceLine" id="cb1-7" title="7"> <span class="dt">replace =</span> <span class="ot">TRUE</span>)</a>
<a class="sourceLine" id="cb1-8" title="8">}</a>
<a class="sourceLine" id="cb1-9" title="9"></a>
<a class="sourceLine" id="cb1-10" title="10">my_TB_data &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/data.frame">data.frame</a></span>(<span class="dt">rifampicin =</span> <span class="kw">sample_rsi</span>(),</a>
<a class="sourceLine" id="cb1-11" title="11"> <span class="dt">isoniazid =</span> <span class="kw">sample_rsi</span>(),</a>
<a class="sourceLine" id="cb1-12" title="12"> <span class="dt">gatifloxacin =</span> <span class="kw">sample_rsi</span>(),</a>
<a class="sourceLine" id="cb1-13" title="13"> <span class="dt">ethambutol =</span> <span class="kw">sample_rsi</span>(),</a>
<a class="sourceLine" id="cb1-14" title="14"> <span class="dt">pyrazinamide =</span> <span class="kw">sample_rsi</span>(),</a>
<a class="sourceLine" id="cb1-15" title="15"> <span class="dt">moxifloxacin =</span> <span class="kw">sample_rsi</span>(),</a>
<a class="sourceLine" id="cb1-16" title="16"> <span class="dt">kanamycin =</span> <span class="kw">sample_rsi</span>())</a></code></pre></div>
<p>Because all column names are automatically verified for valid drug names or codes, this would have worked exactly the same:</p>
<div class="sourceCode" id="cb2"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb2-1" title="1">my_TB_data &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/data.frame">data.frame</a></span>(<span class="dt">RIF =</span> <span class="kw">sample_rsi</span>(),</a>
<a class="sourceLine" id="cb2-2" title="2"> <span class="dt">INH =</span> <span class="kw">sample_rsi</span>(),</a>
<a class="sourceLine" id="cb2-3" title="3"> <span class="dt">GAT =</span> <span class="kw">sample_rsi</span>(),</a>
<a class="sourceLine" id="cb2-4" title="4"> <span class="dt">ETH =</span> <span class="kw">sample_rsi</span>(),</a>
<a class="sourceLine" id="cb2-5" title="5"> <span class="dt">PZA =</span> <span class="kw">sample_rsi</span>(),</a>
<a class="sourceLine" id="cb2-6" title="6"> <span class="dt">MFX =</span> <span class="kw">sample_rsi</span>(),</a>
<a class="sourceLine" id="cb2-7" title="7"> <span class="dt">KAN =</span> <span class="kw">sample_rsi</span>())</a></code></pre></div>
<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>
<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 R R R R S</span></a>
<a class="sourceLine" id="cb3-4" title="4"><span class="co"># 2 S R R S R S</span></a>
<a class="sourceLine" id="cb3-5" title="5"><span class="co"># 3 R S S I S S</span></a>
<a class="sourceLine" id="cb3-6" title="6"><span class="co"># 4 R S S R S S</span></a>
<a class="sourceLine" id="cb3-7" title="7"><span class="co"># 5 R R S I I R</span></a>
<a class="sourceLine" id="cb3-8" title="8"><span class="co"># 6 R S S S S S</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-11" title="11"><span class="co"># 2 R</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 R</span></a>
<a class="sourceLine" id="cb3-14" title="14"><span class="co"># 5 S</span></a>
<a class="sourceLine" id="cb3-15" title="15"><span class="co"># 6 I</span></a></code></pre></div>
<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>
<a class="sourceLine" id="cb4-2" title="2"><span class="co"># </span><span class="al">NOTE</span><span class="co">: No column found as input for `col_mo`, assuming all records contain Mycobacterium tuberculosis.</span></a>
<a class="sourceLine" id="cb4-3" title="3"><span class="co"># Determining multidrug-resistant organisms (MDRO), according to:</span></a>
<a class="sourceLine" id="cb4-4" title="4"><span class="co"># Guideline: Companion handbook to the WHO guidelines for the programmatic management of drug-resistant tuberculosis</span></a>
<a class="sourceLine" id="cb4-5" title="5"><span class="co"># Version: WHO/HTM/TB/2014.11</span></a>
<a class="sourceLine" id="cb4-6" title="6"><span class="co"># Author: WHO (World Health Organization)</span></a>
<a class="sourceLine" id="cb4-7" title="7"><span class="co"># Source: https://www.who.int/tb/publications/pmdt_companionhandbook/en/</span></a>
<a class="sourceLine" id="cb4-8" title="8"><span class="co"># Warning: Reliability might be improved if these antimicrobial results</span></a>
<a class="sourceLine" id="cb4-9" title="9"><span class="co"># would be available too: `CAP` (capreomycin), `RIB` (rifabutin), `RFP`</span></a>
<a class="sourceLine" id="cb4-10" title="10"><span class="co"># (rifapentine)</span></a></code></pre></div>
<p>And review the result with a frequency table:</p>
<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/freq.html">freq</a></span>(my_TB_data<span class="op">$</span>mdr)</a>
<a class="sourceLine" id="cb5-2" title="2"><span class="co"># </span></a>
<a class="sourceLine" id="cb5-3" title="3"><span class="co"># </span></a>
<a class="sourceLine" id="cb5-4" title="4"><span class="co"># **Frequency table of `mdr` from `my_TB_data` (5,000 x 8)** </span></a>
<a class="sourceLine" id="cb5-5" title="5"><span class="co"># </span></a>
<a class="sourceLine" id="cb5-6" title="6"><span class="co"># Class: `factor` &gt; `ordered` (`numeric`) </span></a>
<a class="sourceLine" id="cb5-7" title="7"><span class="co"># Length: 5,000 (of which NA: 0 = 0.00%) </span></a>
<a class="sourceLine" id="cb5-8" title="8"><span class="co"># Levels: 5: `Negative` &lt; `Mono-resistance` &lt; `Poly-resistance` &lt; `Multidrug res...` </span></a>
<a class="sourceLine" id="cb5-9" title="9"><span class="co"># Unique: 5</span></a>
<a class="sourceLine" id="cb5-10" title="10"><span class="co"># </span></a>
<a class="sourceLine" id="cb5-11" title="11"><span class="co"># </span></a>
<a class="sourceLine" id="cb5-12" title="12"><span class="co"># | |Item | Count| Percent| Cum. Count| Cum. Percent|</span></a>
<a class="sourceLine" id="cb5-13" title="13"><span class="co"># |:--|:-------------------------|-----:|-------:|----------:|------------:|</span></a>
<a class="sourceLine" id="cb5-14" title="14"><span class="co"># |1 |Mono-resistance | 3,297| 65.9%| 3,297| 65.9%|</span></a>
<a class="sourceLine" id="cb5-15" title="15"><span class="co"># |2 |Negative | 627| 12.5%| 3,924| 78.5%|</span></a>
<a class="sourceLine" id="cb5-16" title="16"><span class="co"># |3 |Multidrug resistance | 612| 12.2%| 4,536| 90.7%|</span></a>
<a class="sourceLine" id="cb5-17" title="17"><span class="co"># |4 |Poly-resistance | 263| 5.3%| 4,799| 96.0%|</span></a>
<a class="sourceLine" id="cb5-18" title="18"><span class="co"># |5 |Extensive drug resistance | 201| 4.0%| 5,000| 100.0%|</span></a></code></pre></div>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="sidebar">
</div>
</div>
<footer><div class="copyright">
<p>Developed by <a href="https://www.rug.nl/staff/m.s.berends/">Matthijs S. Berends</a>, <a href="https://www.rug.nl/staff/c.f.luz/">Christian F. Luz</a>, <a href="https://www.rug.nl/staff/c.glasner/">Corinna Glasner</a>, <a href="https://www.rug.nl/staff/a.w.friedrich/">Alex W. Friedrich</a>, <a href="https://www.rug.nl/staff/b.sinha/">Bhanu N. M. Sinha</a>.</p>
</div>
<div class="pkgdown">
<p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.3.0.</p>
</div>
</footer>
</div>
<script src="https://cdnjs.cloudflare.com/ajax/libs/docsearch.js/2.6.1/docsearch.min.js" integrity="sha256-GKvGqXDznoRYHCwKXGnuchvKSwmx9SRMrZOTh2g4Sb0=" crossorigin="anonymous"></script><script>
docsearch({
apiKey: 'f737050abfd4d726c63938e18f8c496e',
indexName: 'amr',
inputSelector: 'input#search-input.form-control',
transformData: function(hits) {
return hits.map(function (hit) {
hit.url = updateHitURL(hit);
return hit;
});
}
});
</script>
</body>
</html>

View File

@@ -40,7 +40,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9034</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -76,6 +76,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -192,7 +199,7 @@
<h1>How to import data from SPSS / SAS / Stata</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">20 May 2019</h4>
<h4 class="date">23 May 2019</h4>
<div class="hidden name"><code>SPSS.Rmd</code></div>

View File

@@ -40,7 +40,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -76,6 +76,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -192,7 +199,7 @@
<h1>How to work with WHONET data</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">17 May 2019</h4>
<h4 class="date">23 May 2019</h4>
<div class="hidden name"><code>WHONET.Rmd</code></div>

View File

@@ -40,7 +40,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9034</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -76,6 +76,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -192,7 +199,7 @@
<h1>How to get properties of an antibiotic</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">20 May 2019</h4>
<h4 class="date">23 May 2019</h4>
<div class="hidden name"><code>ab_property.Rmd</code></div>

View File

@@ -40,7 +40,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9034</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -76,6 +76,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -192,7 +199,7 @@
<h1>Benchmarks</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">20 May 2019</h4>
<h4 class="date">23 May 2019</h4>
<div class="hidden name"><code>benchmarks.Rmd</code></div>
@@ -218,13 +225,13 @@
<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-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") 18 18 22.0 18 18.0 62.0 10</span></a>
<a class="sourceLine" id="cb2-13" title="13"><span class="co"># as.mo("stau") 47 47 57.0 48 50.0 92.0 10</span></a>
<a class="sourceLine" id="cb2-14" title="14"><span class="co"># as.mo("staaur") 17 18 23.0 18 19.0 62.0 10</span></a>
<a class="sourceLine" id="cb2-15" title="15"><span class="co"># as.mo("STAAUR") 17 17 18.0 17 18.0 23.0 10</span></a>
<a class="sourceLine" id="cb2-16" title="16"><span class="co"># as.mo("S. aureus") 28 28 38.0 29 29.0 78.0 10</span></a>
<a class="sourceLine" id="cb2-17" title="17"><span class="co"># as.mo("S. aureus") 28 28 48.0 29 73.0 130.0 10</span></a>
<a class="sourceLine" id="cb2-18" title="18"><span class="co"># as.mo("Staphylococcus aureus") 8 8 8.1 8 8.1 8.2 10</span></a></code></pre></div>
<a class="sourceLine" id="cb2-12" title="12"><span class="co"># as.mo("sau") 17.0 18 32.0 18 62.0 68.0 10</span></a>
<a class="sourceLine" id="cb2-13" title="13"><span class="co"># as.mo("stau") 48.0 48 64.0 53 92.0 96.0 10</span></a>
<a class="sourceLine" id="cb2-14" title="14"><span class="co"># as.mo("staaur") 17.0 18 18.0 18 18.0 19.0 10</span></a>
<a class="sourceLine" id="cb2-15" title="15"><span class="co"># as.mo("STAAUR") 17.0 17 18.0 18 18.0 20.0 10</span></a>
<a class="sourceLine" id="cb2-16" title="16"><span class="co"># as.mo("S. aureus") 28.0 28 33.0 29 29.0 73.0 10</span></a>
<a class="sourceLine" id="cb2-17" title="17"><span class="co"># as.mo("S. aureus") 28.0 28 44.0 28 29.0 140.0 10</span></a>
<a class="sourceLine" id="cb2-18" title="18"><span class="co"># as.mo("Staphylococcus aureus") 7.9 8 8.1 8 8.2 8.2 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>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>
@@ -236,12 +243,12 @@
<a class="sourceLine" id="cb3-7" title="7"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(T.islandicus, <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="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-10" title="10"><span class="co"># as.mo("theisl") 470 480 510 520 530 530 10</span></a>
<a class="sourceLine" id="cb3-11" title="11"><span class="co"># as.mo("THEISL") 470 470 500 490 520 530 10</span></a>
<a class="sourceLine" id="cb3-12" title="12"><span class="co"># as.mo("T. islandicus") 74 75 85 76 81 120 10</span></a>
<a class="sourceLine" id="cb3-13" title="13"><span class="co"># as.mo("T. islandicus") 74 75 92 76 120 140 10</span></a>
<a class="sourceLine" id="cb3-14" title="14"><span class="co"># as.mo("Thermus islandicus") 73 73 74 74 74 75 10</span></a></code></pre></div>
<p>That takes 8.2 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>
<a class="sourceLine" id="cb3-10" title="10"><span class="co"># as.mo("theisl") 470 470 500 500 520 520 10</span></a>
<a class="sourceLine" id="cb3-11" title="11"><span class="co"># as.mo("THEISL") 470 470 510 520 520 530 10</span></a>
<a class="sourceLine" id="cb3-12" title="12"><span class="co"># as.mo("T. islandicus") 73 74 79 74 74 120 10</span></a>
<a class="sourceLine" id="cb3-13" title="13"><span class="co"># as.mo("T. islandicus") 73 74 84 74 75 130 10</span></a>
<a class="sourceLine" id="cb3-14" title="14"><span class="co"># as.mo("Thermus islandicus") 74 74 94 75 120 140 10</span></a></code></pre></div>
<p>That takes 8.1 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>
<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>
<a class="sourceLine" id="cb4-2" title="2"></a>
@@ -287,8 +294,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-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-27" title="27"><span class="co"># mo_fullname(x) 677 770 812 790 884 988 10</span></a></code></pre></div>
<p>So transforming 500,000 values (!!) of 50 unique values only takes 0.79 seconds (789 ms). You only lose time on your unique input values.</p>
<a class="sourceLine" id="cb5-27" title="27"><span class="co"># mo_fullname(x) 633 675 747 722 763 933 10</span></a></code></pre></div>
<p>So transforming 500,000 values (!!) of 50 unique values only takes 0.72 seconds (721 ms). You only lose time on your unique input values.</p>
</div>
<div id="precalculated-results" class="section level3">
<h3 class="hasAnchor">
@@ -301,9 +308,9 @@
<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-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.9 13.20 13.30 13.40 13.50 13.50 10</span></a>
<a class="sourceLine" id="cb6-9" title="9"><span class="co"># B 25.3 25.80 30.40 25.80 26.20 71.60 10</span></a>
<a class="sourceLine" id="cb6-10" title="10"><span class="co"># C 1.3 1.37 1.56 1.67 1.73 1.74 10</span></a></code></pre></div>
<a class="sourceLine" id="cb6-8" title="8"><span class="co"># A 12.90 13.1 18.0 13.20 14.10 59.1 10</span></a>
<a class="sourceLine" id="cb6-9" title="9"><span class="co"># B 25.20 25.3 26.2 26.10 27.00 27.4 10</span></a>
<a class="sourceLine" id="cb6-10" title="10"><span class="co"># C 1.25 1.4 1.6 1.68 1.69 1.9 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>
<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>
@@ -317,14 +324,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-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-13" title="13"><span class="co"># A 0.442 0.477 0.583 0.572 0.673 0.806 10</span></a>
<a class="sourceLine" id="cb7-14" title="14"><span class="co"># B 0.442 0.502 0.626 0.611 0.761 0.826 10</span></a>
<a class="sourceLine" id="cb7-15" title="15"><span class="co"># C 1.360 1.620 1.820 1.810 2.060 2.150 10</span></a>
<a class="sourceLine" id="cb7-16" title="16"><span class="co"># D 0.449 0.514 0.622 0.639 0.725 0.798 10</span></a>
<a class="sourceLine" id="cb7-17" title="17"><span class="co"># E 0.401 0.440 0.530 0.508 0.568 0.799 10</span></a>
<a class="sourceLine" id="cb7-18" title="18"><span class="co"># F 0.353 0.391 0.502 0.494 0.635 0.695 10</span></a>
<a class="sourceLine" id="cb7-19" title="19"><span class="co"># G 0.451 0.559 0.595 0.609 0.646 0.747 10</span></a>
<a class="sourceLine" id="cb7-20" title="20"><span class="co"># H 0.191 0.278 0.395 0.376 0.528 0.653 10</span></a></code></pre></div>
<a class="sourceLine" id="cb7-13" title="13"><span class="co"># A 0.357 0.374 0.447 0.435 0.514 0.567 10</span></a>
<a class="sourceLine" id="cb7-14" title="14"><span class="co"># B 0.404 0.507 0.541 0.533 0.575 0.755 10</span></a>
<a class="sourceLine" id="cb7-15" title="15"><span class="co"># C 1.350 1.400 1.700 1.720 1.890 2.150 10</span></a>
<a class="sourceLine" id="cb7-16" title="16"><span class="co"># D 0.416 0.550 0.589 0.603 0.632 0.750 10</span></a>
<a class="sourceLine" id="cb7-17" title="17"><span class="co"># E 0.400 0.480 0.559 0.541 0.667 0.737 10</span></a>
<a class="sourceLine" id="cb7-18" title="18"><span class="co"># F 0.346 0.384 0.493 0.498 0.628 0.643 10</span></a>
<a class="sourceLine" id="cb7-19" title="19"><span class="co"># G 0.393 0.421 0.486 0.430 0.570 0.620 10</span></a>
<a class="sourceLine" id="cb7-20" title="20"><span class="co"># H 0.258 0.280 0.332 0.290 0.377 0.508 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>
</div>
<div id="results-in-other-languages" class="section level3">
@@ -351,13 +358,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-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-21" title="21"><span class="co"># en 18.16 18.23 22.82 18.29 18.57 63.28 10</span></a>
<a class="sourceLine" id="cb8-22" title="22"><span class="co"># de 23.00 23.09 23.35 23.21 23.59 23.96 10</span></a>
<a class="sourceLine" id="cb8-23" title="23"><span class="co"># nl 36.60 36.74 37.00 36.97 37.32 37.41 10</span></a>
<a class="sourceLine" id="cb8-24" title="24"><span class="co"># es 23.10 23.15 23.40 23.29 23.63 23.97 10</span></a>
<a class="sourceLine" id="cb8-25" title="25"><span class="co"># it 23.04 23.14 23.28 23.27 23.43 23.58 10</span></a>
<a class="sourceLine" id="cb8-26" title="26"><span class="co"># fr 23.13 23.21 33.12 23.90 28.96 68.96 10</span></a>
<a class="sourceLine" id="cb8-27" title="27"><span class="co"># pt 22.98 23.16 23.37 23.44 23.51 23.65 10</span></a></code></pre></div>
<a class="sourceLine" id="cb8-21" title="21"><span class="co"># en 18.10 18.20 18.30 18.25 18.38 18.57 10</span></a>
<a class="sourceLine" id="cb8-22" title="22"><span class="co"># de 23.06 23.14 32.22 23.21 23.48 68.37 10</span></a>
<a class="sourceLine" id="cb8-23" title="23"><span class="co"># nl 36.30 36.40 41.09 36.59 36.85 81.13 10</span></a>
<a class="sourceLine" id="cb8-24" title="24"><span class="co"># es 22.85 23.07 23.24 23.20 23.46 23.72 10</span></a>
<a class="sourceLine" id="cb8-25" title="25"><span class="co"># it 22.92 22.99 27.72 23.17 23.61 68.07 10</span></a>
<a class="sourceLine" id="cb8-26" title="26"><span class="co"># fr 23.02 23.14 27.79 23.23 23.58 68.27 10</span></a>
<a class="sourceLine" id="cb8-27" title="27"><span class="co"># pt 23.00 23.09 23.24 23.19 23.45 23.52 10</span></a></code></pre></div>
<p>Currently supported are German, Dutch, Spanish, Italian, French and Portuguese.</p>
</div>
</div>

Binary file not shown.

Before

Width:  |  Height:  |  Size: 26 KiB

After

Width:  |  Height:  |  Size: 27 KiB

View File

@@ -40,7 +40,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -76,6 +76,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -192,7 +199,7 @@
<h1>How to create frequency tables</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">17 May 2019</h4>
<h4 class="date">23 May 2019</h4>
<div class="hidden name"><code>freq.Rmd</code></div>
@@ -714,7 +721,7 @@ Median: 31 July 2009 (47.39%)</p>
<div id="assigning-a-frequency-table-to-an-object" class="section level2">
<h2 class="hasAnchor">
<a href="#assigning-a-frequency-table-to-an-object" class="anchor"></a>Assigning a frequency table to an object</h2>
<p>A frequency table is actaually a regular <code>data.frame</code>, with the exception that it contains an additional class.</p>
<p>A frequency table is actually a regular <code>data.frame</code>, with the exception that it contains an additional class.</p>
<div class="sourceCode" id="cb11"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb11-1" title="1">my_df &lt;-<span class="st"> </span>septic_patients <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="cb11-2" title="2"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/class">class</a></span>(my_df)</a></code></pre></div>
<p>[1] “frequency_tbl” “data.frame”</p>
@@ -729,7 +736,7 @@ Median: 31 July 2009 (47.39%)</p>
<h3 class="hasAnchor">
<a href="#parameter-na-rm" class="anchor"></a>Parameter <code>na.rm</code>
</h3>
<p>With the <code>na.rm</code> parameter (defaults to <code>TRUE</code>, but they will always be shown into the header), you can include <code>NA</code> values in the frequency table:</p>
<p>With the <code>na.rm</code> parameter you can remove <code>NA</code> values from the frequency table (defaults to <code>TRUE</code>, but the number of <code>NA</code> values will always be shown into the header):</p>
<div class="sourceCode" id="cb13"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb13-1" title="1">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb13-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(AMX, <span class="dt">na.rm =</span> <span class="ot">FALSE</span>)</a></code></pre></div>
<p><strong>Frequency table of <code>AMX</code> from a <code>data.frame</code> (2,000 x 49)</strong></p>
@@ -784,14 +791,68 @@ Group: Beta-lactams/penicillins<br>
</tr>
</tbody>
</table>
<div class="sourceCode" id="cb14"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb14-1" title="1">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb14-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(AMX, <span class="dt">na.rm =</span> <span class="ot">FALSE</span>)</a></code></pre></div>
<p><strong>Frequency table of <code>AMX</code> from a <code>data.frame</code> (2,000 x 49)</strong></p>
<p>Class: <code>factor</code> &gt; <code>ordered</code> &gt; <code>rsi</code> (<code>numeric</code>)<br>
Length: 2,000 (of which NA: 771 = 38.55%)<br>
Levels: 3: <code>S</code> &lt; <code>I</code> &lt; <code>R</code><br>
Unique: 4</p>
<p>Drug: Amoxicillin (AMX, J01CA04)<br>
Group: Beta-lactams/penicillins<br>
%SI: 44.43%</p>
<table class="table">
<thead><tr class="header">
<th align="left"></th>
<th align="left">Item</th>
<th align="right">Count</th>
<th align="right">Percent</th>
<th align="right">Cum. Count</th>
<th align="right">Cum. Percent</th>
</tr></thead>
<tbody>
<tr class="odd">
<td align="left">1</td>
<td align="left">(NA)</td>
<td align="right">771</td>
<td align="right">38.6%</td>
<td align="right">771</td>
<td align="right">38.6%</td>
</tr>
<tr class="even">
<td align="left">2</td>
<td align="left">R</td>
<td align="right">683</td>
<td align="right">34.2%</td>
<td align="right">1,454</td>
<td align="right">72.7%</td>
</tr>
<tr class="odd">
<td align="left">3</td>
<td align="left">S</td>
<td align="right">543</td>
<td align="right">27.2%</td>
<td align="right">1,997</td>
<td align="right">99.8%</td>
</tr>
<tr class="even">
<td align="left">4</td>
<td align="left">I</td>
<td align="right">3</td>
<td align="right">0.2%</td>
<td align="right">2,000</td>
<td align="right">100.0%</td>
</tr>
</tbody>
</table>
</div>
<div id="parameter-row-names" class="section level3">
<h3 class="hasAnchor">
<a href="#parameter-row-names" class="anchor"></a>Parameter <code>row.names</code>
</h3>
<p>The default frequency tables shows row indices. To remove them, use <code>row.names = FALSE</code>:</p>
<div class="sourceCode" id="cb14"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb14-1" title="1">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb14-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(hospital_id, <span class="dt">row.names =</span> <span class="ot">FALSE</span>)</a></code></pre></div>
<p>A frequency table shows row indices. To remove them, use <code>row.names = FALSE</code>:</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></a>
<a class="sourceLine" id="cb15-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(hospital_id, <span class="dt">row.names =</span> <span class="ot">FALSE</span>)</a></code></pre></div>
<p><strong>Frequency table of <code>hospital_id</code> from a <code>data.frame</code> (2,000 x 49)</strong></p>
<p>Class: <code>factor</code> (<code>numeric</code>)<br>
Length: 2,000 (of which NA: 0 = 0.00%)<br>
@@ -842,8 +903,8 @@ Unique: 4</p>
<a href="#parameter-markdown" class="anchor"></a>Parameter <code>markdown</code>
</h3>
<p>The <code>markdown</code> parameter is <code>TRUE</code> at default in non-interactive sessions, like in reports created with R Markdown. This will always print all rows, unless <code>nmax</code> is set.</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></a>
<a class="sourceLine" id="cb15-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(hospital_id, <span class="dt">markdown =</span> <span class="ot">TRUE</span>)</a></code></pre></div>
<div class="sourceCode" id="cb16"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb16-1" title="1">septic_patients <span class="op">%&gt;%</span></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="dt">markdown =</span> <span class="ot">TRUE</span>)</a></code></pre></div>
<p><strong>Frequency table of <code>hospital_id</code> from a <code>data.frame</code> (2,000 x 49)</strong></p>
<p>Class: <code>factor</code> (<code>numeric</code>)<br>
Length: 2,000 (of which NA: 0 = 0.00%)<br>

View File

@@ -78,7 +78,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9034</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -114,6 +114,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -239,6 +246,7 @@
<li><a href="AMR.html">How to conduct AMR analysis</a></li>
<li><a href="EUCAST.html">How to apply EUCAST rules</a></li>
<li><a href="G_test.html">How to use the *G*-test</a></li>
<li><a href="MDR.html">How to determine multi-drug resistance (MDR)</a></li>
<li><a href="SPSS.html">How to import data from SPSS / SAS / Stata</a></li>
<li><a href="WHONET.html">How to work with WHONET data</a></li>
<li><a href="ab_property.html">How to get properties of an antibiotic</a></li>

View File

@@ -40,7 +40,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9034</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -76,6 +76,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -192,7 +199,7 @@
<h1>How to get properties of a microorganism</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">20 May 2019</h4>
<h4 class="date">23 May 2019</h4>
<div class="hidden name"><code>mo_property.Rmd</code></div>

View File

@@ -40,7 +40,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9034</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -76,6 +76,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -192,7 +199,7 @@
<h1>How to predict antimicrobial resistance</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">20 May 2019</h4>
<h4 class="date">23 May 2019</h4>
<div class="hidden name"><code>resistance_predict.Rmd</code></div>

View File

@@ -78,7 +78,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9034</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -114,6 +114,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="articles/WHONET.html">
<span class="fa fa-globe-americas"></span>

View File

@@ -42,7 +42,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9034</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -78,6 +78,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -202,19 +209,19 @@
<p>We created this package for both academic research and routine analysis at the Faculty of Medical Sciences of the University of Groningen, the Netherlands, and the Medical Microbiology &amp; Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG). This R package is actively maintained and is free software; you can freely use and distribute it for both personal and commercial (but <strong>not</strong> patent) purposes under the terms of the GNU General Public License version 2.0 (GPL-2), as published by the Free Software Foundation. Read the full license <a href="./LICENSE-text.html">here</a>.</p>
<p>This package can be used for:</p>
<ul>
<li>Reference for microorganisms, since it contains all microbial (sub)species from the <a href="http://www.catalogueoflife.org">Catalogue of Life</a>
<li>Reference for microorganisms, since it contains all microbial (sub)species from the <a href="http://www.catalogueoflife.org">Catalogue of Life</a> (<a href="./reference/mo_property.html">manual</a>)</li>
<li>Interpreting raw MIC and disk diffusion values, based on the latest CLSI or EUCAST guidelines (<a href="./reference/as.rsi.html">manual</a>)</li>
<li>Calculating antimicrobial resistance (<a href="./articles/AMR.html">tutorial</a>)</li>
<li>Determining multi-drug resistance (MDR) / multi-drug resistant organisms (MDRO) (<a href="./articles/MDR.html">tutorial</a>)</li>
<li>Calculating empirical susceptibility of both mono therapy and combination therapy (<a href="./articles/AMR.html">tutorial</a>)</li>
<li>Predicting future antimicrobial resistance using regression models (<a href="./articles/resistance_predict.html">tutorial</a>)</li>
<li>Getting properties for any microorganism (like Gram stain, species, genus or family) (<a href="./reference/mo_property.html">manual</a>)</li>
<li>Getting properties for any antibiotic (like name, ATC code, defined daily dose or trade name) (<a href="./reference/ab_property.html">manual</a>)</li>
<li>Plotting antimicrobial resistance (<a href="./articles/AMR.html">tutorial</a>)</li>
<li>Determining first isolates to be used for AMR analysis (<a href="./reference/first_isolate.html">manual</a>)</li>
<li>Applying EUCAST expert rules (<a href="./reference/eucast_rules.html">manual</a>
</li>
<li>Interpreting raw MIC and disk diffusion values, based on the latest CLSI or EUCAST guidelines</li>
<li>Calculating antimicrobial resistance</li>
<li>Calculating empirical susceptibility of both mono therapy and combination therapy</li>
<li>Predicting future antimicrobial resistance using regression models</li>
<li>Getting properties for any microorganism (like Gram stain, species, genus or family)</li>
<li>Getting properties for any antibiotic (like name, ATC code, defined daily dose or trade name)</li>
<li>Plotting antimicrobial resistance</li>
<li>Determining first isolates to be used for AMR analysis</li>
<li>Applying EUCAST expert rules</li>
<li>Determining multi-drug resistant organisms (MDRO)</li>
<li>Descriptive statistics: frequency tables, kurtosis and skewness</li>
<li>Descriptive statistics: frequency tables, kurtosis and skewness (<a href="./articles/freq.html">tutorial</a>)</li>
</ul>
<p>This package is ready-to-use for a professional environment by specialists in the following fields:</p>
<p>Medical Microbiology</p>

View File

@@ -78,7 +78,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9034</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -114,6 +114,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -232,9 +239,9 @@
</div>
<div id="amr-0619001" class="section level1">
<div id="amr-06190xx" class="section level1">
<h1 class="page-header">
<a href="#amr-0619001" class="anchor"></a>AMR 0.6.1.9001<small> Unreleased </small>
<a href="#amr-06190xx" class="anchor"></a>AMR 0.6.1.90xx<small> Unreleased </small>
</h1>
<p><strong>Note: latest development version</strong></p>
<div id="new" class="section level4">
@@ -244,6 +251,7 @@
<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>
<li>Added guidelines of the WHO to determine mutli-drug resistance (MDR) for TB (<code><a href="../reference/mdro.html">mdr_tb()</a></code>) and added a new vignette about MDR</li>
</ul>
</div>
<div id="changed" class="section level4">
@@ -259,7 +267,7 @@
<li>Column <code>cid</code> contains the CID code (Compound ID), used by PubChem</li>
</ul>
</li>
<li>Based on the Compound ID, more than a thousand official brand names have been added from many different countries</li>
<li>Based on the Compound ID, almost 5,000 official brand names have been added from many different countries</li>
<li>All references to antibiotics in our package now use EARS-Net codes, like <code>AMX</code> for amoxicillin</li>
<li>Functions <code>atc_certe</code>, <code>ab_umcg</code> and <code>atc_trivial_nl</code> have been removed</li>
<li>All <code>atc_*</code> functions are superceded by <code>ab_*</code> functions</li>
@@ -275,7 +283,14 @@ Please create an issue in one of our repositories if you want additions in this
<li>This package now honours the new EUCAST insight (2019) that S and I are but classified as susceptible, where I is defined as increased exposure and not intermediate anymore. For functions like <code><a href="../reference/portion.html">portion_df()</a></code> and <code><a href="../reference/count.html">count_df()</a></code> this means that their new parameter <code>combine_SI</code> is TRUE at default.</li>
<li>Removed deprecated functions <code>guess_mo()</code>, <code>guess_atc()</code>, <code>EUCAST_rules()</code>, <code>interpretive_reading()</code>, <code>rsi()</code>
</li>
<li>Frequency tables of microbial IDs speed improvement</li>
<li>Frequency tables (<code><a href="../reference/freq.html">freq()</a></code>):
<ul>
<li>speed improvement for microbial IDs</li>
<li>fixed level names in markdown</li>
<li>
</li>
</ul>
</li>
<li>Removed all hardcoded EUCAST rules and replaced them with a new reference file: <code>./inst/eucast/eucast.tsv</code>
</li>
<li>Added ceftazidim intrinsic resistance to <em>Streptococci</em>
@@ -1028,7 +1043,7 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<div id="tocnav">
<h2>Contents</h2>
<ul class="nav nav-pills nav-stacked">
<li><a href="#amr-0619001">0.6.1.9001</a></li>
<li><a href="#amr-06190xx">0.6.1.90</a></li>
<li><a href="#amr-061">0.6.1</a></li>
<li><a href="#amr-060">0.6.0</a></li>
<li><a href="#amr-050">0.5.0</a></li>

View File

@@ -5,6 +5,7 @@ articles:
AMR: AMR.html
EUCAST: EUCAST.html
G_test: G_test.html
MDR: MDR.html
SPSS: SPSS.html
WHONET: WHONET.html
ab_property: ab_property.html

View File

@@ -80,7 +80,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9033</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -116,6 +116,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -245,7 +252,7 @@
<h2 class="hasAnchor" id="format"><a class="anchor" href="#format"></a>Format</h2>
<p>A <code><a href='https://www.rdocumentation.org/packages/base/topics/data.frame'>data.frame</a></code> with 455 observations and 13 variables:</p><dl class='dl-horizontal'>
<p>A <code><a href='https://www.rdocumentation.org/packages/base/topics/data.frame'>data.frame</a></code> with 454 observations and 13 variables:</p><dl class='dl-horizontal'>
<dt><code>ab</code></dt><dd><p>Antibiotic ID as used in this package (like <code>AMC</code>), using the official EARS-Net (European Antimicrobial Resistance Surveillance Network) codes where available</p></dd>
<dt><code>atc</code></dt><dd><p>ATC code (Anatomical Therapeutic Chemical) as defined by the WHOCC, like <code>J01CR02</code></p></dd>
<dt><code>cid</code></dt><dd><p>Compound ID as found in PubChem</p></dd>

View File

@@ -80,7 +80,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9033</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -116,6 +116,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -305,9 +312,9 @@
<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>
<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>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>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>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>
<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>

View File

@@ -81,7 +81,7 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9033</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -117,6 +117,13 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -285,7 +292,7 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
</tr>
<tr>
<th>combine_SI</th>
<td><p>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</code>, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now <code>TRUE</code>.</p></td>
<td><p>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</code>, 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</code>.</p></td>
</tr>
<tr>
<th>combine_IR</th>
@@ -312,9 +319,9 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
<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>
<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>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>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>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>
<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>

View File

@@ -80,7 +80,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9033</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -116,6 +116,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -290,7 +297,7 @@
<h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2>
<p>The input of <code>tbl_</code>, possibly with edited values of antibiotics. Or, if <code>verbose = TRUE</code>, a <code>data.frame</code> with all original and new values of the affected bug-drug combinations.</p>
<p>The input of <code>x</code>, possibly with edited values of antibiotics. Or, if <code>verbose = TRUE</code>, a <code>data.frame</code> with all original and new values of the affected bug-drug combinations.</p>
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>

View File

@@ -80,7 +80,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9033</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -116,6 +116,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -301,7 +308,7 @@
</tr>
<tr>
<th>combine_SI</th>
<td><p>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</code>, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now <code>TRUE</code>.</p></td>
<td><p>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</code>, 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</code>.</p></td>
</tr>
<tr>
<th>combine_IR</th>

View File

@@ -78,7 +78,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9034</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -114,6 +114,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -361,7 +368,7 @@
</tr><tr>
<td>
<p><code><a href="mdro.html">mdro()</a></code> <code><a href="mdro.html">brmo()</a></code> <code><a href="mdro.html">mrgn()</a></code> <code><a href="mdro.html">eucast_exceptional_phenotypes()</a></code> </p>
<p><code><a href="mdro.html">mdro()</a></code> <code><a href="mdro.html">brmo()</a></code> <code><a href="mdro.html">mrgn()</a></code> <code><a href="mdro.html">mdr_tb()</a></code> <code><a href="mdro.html">eucast_exceptional_phenotypes()</a></code> </p>
</td>
<td><p>Determine multidrug-resistant organisms (MDRO)</p></td>
</tr><tr>

View File

@@ -80,7 +80,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9033</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -116,6 +116,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -241,20 +248,19 @@
</div>
<pre class="usage"><span class='fu'>key_antibiotics</span>(<span class='no'>tbl</span>, <span class='kw'>col_mo</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>universal_1</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>,
<span class='st'>"AMX"</span>), <span class='kw'>universal_2</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>, <span class='st'>"AMC"</span>),
<span class='kw'>universal_3</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>, <span class='st'>"CXM"</span>),
<span class='kw'>universal_4</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>, <span class='st'>"TZP"</span>),
<span class='kw'>universal_5</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>, <span class='st'>"CIP"</span>),
<span class='kw'>universal_6</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>, <span class='st'>"SXT"</span>), <span class='kw'>GramPos_1</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>,
<span class='st'>"VAN"</span>), <span class='kw'>GramPos_2</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>, <span class='st'>"TEC"</span>),
<span class='kw'>GramPos_3</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>, <span class='st'>"TCY"</span>), <span class='kw'>GramPos_4</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>,
<span class='st'>"ERY"</span>), <span class='kw'>GramPos_5</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>, <span class='st'>"OXA"</span>),
<span class='kw'>GramPos_6</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>, <span class='st'>"RIF"</span>), <span class='kw'>GramNeg_1</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>,
<span class='st'>"GEN"</span>), <span class='kw'>GramNeg_2</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>, <span class='st'>"TOB"</span>),
<span class='kw'>GramNeg_3</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>, <span class='st'>"COL"</span>), <span class='kw'>GramNeg_4</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>,
<span class='st'>"CTX"</span>), <span class='kw'>GramNeg_5</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>, <span class='st'>"CAZ"</span>),
<span class='kw'>GramNeg_6</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>tbl</span>, <span class='st'>"MEM"</span>), <span class='kw'>warnings</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='no'>...</span>)
<pre class="usage"><span class='fu'>key_antibiotics</span>(<span class='no'>x</span>, <span class='kw'>col_mo</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>universal_1</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>, <span class='st'>"AMX"</span>),
<span class='kw'>universal_2</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>, <span class='st'>"AMC"</span>), <span class='kw'>universal_3</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>,
<span class='st'>"CXM"</span>), <span class='kw'>universal_4</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>, <span class='st'>"TZP"</span>),
<span class='kw'>universal_5</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>, <span class='st'>"CIP"</span>), <span class='kw'>universal_6</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>,
<span class='st'>"SXT"</span>), <span class='kw'>GramPos_1</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>, <span class='st'>"VAN"</span>),
<span class='kw'>GramPos_2</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>, <span class='st'>"TEC"</span>), <span class='kw'>GramPos_3</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>,
<span class='st'>"TCY"</span>), <span class='kw'>GramPos_4</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>, <span class='st'>"ERY"</span>),
<span class='kw'>GramPos_5</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>, <span class='st'>"OXA"</span>), <span class='kw'>GramPos_6</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>,
<span class='st'>"RIF"</span>), <span class='kw'>GramNeg_1</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>, <span class='st'>"GEN"</span>),
<span class='kw'>GramNeg_2</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>, <span class='st'>"TOB"</span>), <span class='kw'>GramNeg_3</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>,
<span class='st'>"COL"</span>), <span class='kw'>GramNeg_4</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>, <span class='st'>"CTX"</span>),
<span class='kw'>GramNeg_5</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>, <span class='st'>"CAZ"</span>), <span class='kw'>GramNeg_6</span> <span class='kw'>=</span> <span class='fu'><a href='guess_ab_col.html'>guess_ab_col</a></span>(<span class='no'>x</span>,
<span class='st'>"MEM"</span>), <span class='kw'>warnings</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='no'>...</span>)
<span class='fu'>key_antibiotics_equal</span>(<span class='no'>x</span>, <span class='no'>y</span>, <span class='kw'>type</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/c'>c</a></span>(<span class='st'>"keyantibiotics"</span>, <span class='st'>"points"</span>),
<span class='kw'>ignore_I</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='kw'>points_threshold</span> <span class='kw'>=</span> <span class='fl'>2</span>, <span class='kw'>info</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)</pre>
@@ -263,8 +269,8 @@
<table class="ref-arguments">
<colgroup><col class="name" /><col class="desc" /></colgroup>
<tr>
<th>tbl</th>
<td><p>table with antibiotics coloms, like <code>amox</code> and <code>amcl</code>.</p></td>
<th>x</th>
<td><p>table with antibiotics coloms, like <code>AMX</code> or <code>amox</code></p></td>
</tr>
<tr>
<th>col_mo</th>
@@ -290,10 +296,6 @@
<th>...</th>
<td><p>other parameters passed on to function</p></td>
</tr>
<tr>
<th>x, y</th>
<td><p>characters to compare</p></td>
</tr>
<tr>
<th>type</th>
<td><p>type to determine weighed isolates; can be <code>"keyantibiotics"</code> or <code>"points"</code>, see Details</p></td>
@@ -310,6 +312,10 @@
<th>info</th>
<td><p>print progress</p></td>
</tr>
<tr>
<th>x, y</th>
<td><p>characters to compare</p></td>
</tr>
</table>
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>

View File

@@ -80,7 +80,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9033</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -116,6 +116,13 @@
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -241,14 +248,16 @@
</div>
<pre class="usage"><span class='fu'>mdro</span>(<span class='no'>x</span>, <span class='kw'>country</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>col_mo</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>info</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>,
<span class='kw'>verbose</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <span class='no'>...</span>)
<pre class="usage"><span class='fu'>mdro</span>(<span class='no'>x</span>, <span class='kw'>country</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>guideline</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>col_mo</span> <span class='kw'>=</span> <span class='kw'>NULL</span>,
<span class='kw'>info</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='kw'>verbose</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <span class='no'>...</span>)
<span class='fu'>brmo</span>(<span class='no'>...</span>, <span class='kw'>country</span> <span class='kw'>=</span> <span class='st'>"nl"</span>)
<span class='fu'>mrgn</span>(<span class='no'>x</span>, <span class='kw'>country</span> <span class='kw'>=</span> <span class='st'>"de"</span>, <span class='no'>...</span>)
<span class='fu'>eucast_exceptional_phenotypes</span>(<span class='no'>x</span>, <span class='kw'>country</span> <span class='kw'>=</span> <span class='st'>"EUCAST"</span>, <span class='no'>...</span>)</pre>
<span class='fu'>mdr_tb</span>(<span class='no'>x</span>, <span class='kw'>guideline</span> <span class='kw'>=</span> <span class='st'>"TB"</span>, <span class='no'>...</span>)
<span class='fu'>eucast_exceptional_phenotypes</span>(<span class='no'>x</span>, <span class='kw'>guideline</span> <span class='kw'>=</span> <span class='st'>"EUCAST"</span>, <span class='no'>...</span>)</pre>
<h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2>
<table class="ref-arguments">
@@ -259,7 +268,11 @@
</tr>
<tr>
<th>country</th>
<td><p>country code to determine guidelines. EUCAST rules will be used when left empty, see Details. Should be or a code from the <a href='https://en.wikipedia.org/wiki/ISO_3166-1_alpha-2#Officially_assigned_code_elements'>list of ISO 3166-1 alpha-2 country codes</a>. Case-insensitive. Currently supported are <code>de</code> (Germany) and <code>nl</code> (the Netherlands).</p></td>
<td><p>country code to determine guidelines. Should be or a code from the <a href='https://en.wikipedia.org/wiki/ISO_3166-1_alpha-2#Officially_assigned_code_elements'>list of ISO 3166-1 alpha-2 country codes</a>. Case-insensitive.</p></td>
</tr>
<tr>
<th>guideline</th>
<td><p>a specific guideline to mention. For some countries this will be determined automatically, see Details. EUCAST guidelines will be used when left empty, see Details.</p></td>
</tr>
<tr>
<th>col_mo</th>
@@ -285,7 +298,15 @@
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p>When <code>country</code> will be left blank, guidelines will be taken from EUCAST Expert Rules Version 3.1 "Intrinsic Resistance and Exceptional Phenotypes Tables" (<a href='http://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf'>link</a>).</p>
<p>When <code>country</code> is set, the parameter guideline will be ignored as these guidelines will be used:</p>
<ul>
<li><p><code>country = "nl"</code>: Rijksinstituut voor Volksgezondheid en Milieu "WIP-richtlijn BRMO (Bijzonder Resistente Micro-Organismen) [ZKH]" (<a href='https://www.rivm.nl/Documenten_en_publicaties/Professioneel_Praktisch/Richtlijnen/Infectieziekten/WIP_Richtlijnen/WIP_Richtlijnen/Ziekenhuizen/WIP_richtlijn_BRMO_Bijzonder_Resistente_Micro_Organismen_ZKH'>link</a>)</p></li>
</ul>
<p>Please suggest your own country's specific guidelines by letting us know: <a href='https://gitlab.com/msberends/AMR/issues/new'>https://gitlab.com/msberends/AMR/issues/new</a>.</p>
<p>Other currently supported guidelines are:</p><ul>
<li><p><code>guideline = "eucast"</code>: EUCAST Expert Rules Version 3.1 "Intrinsic Resistance and Exceptional Phenotypes Tables" (<a href='http://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf'>link</a>)</p></li>
<li><p><code>guideline = "tb"</code>: World Health Organization "Companion handbook to the WHO guidelines for the programmatic management of drug-resistant tuberculosis" (<a href='https://www.who.int/tb/publications/pmdt_companionhandbook/en/'>link</a>)</p></li>
</ul>
<h2 class="hasAnchor" id="antibiotics"><a class="anchor" href="#antibiotics"></a>Antibiotics</h2>

View File

@@ -81,7 +81,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9033</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.6.1.9035</span>
</span>
</div>
@@ -117,6 +117,13 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/MDR.html">
<span class="fa fa-skull-crossbones"></span>
Determine multi-drug resistance (MDR)
</a>
</li>
<li>
<a href="../articles/WHONET.html">
<span class="fa fa-globe-americas"></span>
@@ -295,7 +302,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
</tr>
<tr>
<th>combine_SI</th>
<td><p>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</code>, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now <code>TRUE</code>.</p></td>
<td><p>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</code>, 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</code>.</p></td>
</tr>
<tr>
<th>combine_IR</th>
@@ -335,9 +342,9 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
<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>
<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>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>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>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>
<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>

View File

@@ -144,6 +144,9 @@
<url>
<loc>https://msberends.gitlab.io/AMR/articles/G_test.html</loc>
</url>
<url>
<loc>https://msberends.gitlab.io/AMR/articles/MDR.html</loc>
</url>
<url>
<loc>https://msberends.gitlab.io/AMR/articles/SPSS.html</loc>
</url>

View File

@@ -15,18 +15,18 @@ This R package is actively maintained and is free software; you can freely use a
This package can be used for:
* Reference for microorganisms, since it contains all microbial (sub)species from the [Catalogue of Life](http://www.catalogueoflife.org)
* Interpreting raw MIC and disk diffusion values, based on the latest CLSI or EUCAST guidelines
* Calculating antimicrobial resistance
* Calculating empirical susceptibility of both mono therapy and combination therapy
* Predicting future antimicrobial resistance using regression models
* Getting properties for any microorganism (like Gram stain, species, genus or family)
* Getting properties for any antibiotic (like name, ATC code, defined daily dose or trade name)
* Plotting antimicrobial resistance
* Determining first isolates to be used for AMR analysis
* Applying EUCAST expert rules
* Determining multi-drug resistant organisms (MDRO)
* Descriptive statistics: frequency tables, kurtosis and skewness
* Reference for microorganisms, since it contains all microbial (sub)species from the [Catalogue of Life](http://www.catalogueoflife.org) ([manual](./reference/mo_property.html))
* Interpreting raw MIC and disk diffusion values, based on the latest CLSI or EUCAST guidelines ([manual](./reference/as.rsi.html))
* Calculating antimicrobial resistance ([tutorial](./articles/AMR.html))
* Determining multi-drug resistance (MDR) / multi-drug resistant organisms (MDRO) ([tutorial](./articles/MDR.html))
* Calculating empirical susceptibility of both mono therapy and combination therapy ([tutorial](./articles/AMR.html))
* Predicting future antimicrobial resistance using regression models ([tutorial](./articles/resistance_predict.html))
* Getting properties for any microorganism (like Gram stain, species, genus or family) ([manual](./reference/mo_property.html))
* Getting properties for any antibiotic (like name, ATC code, defined daily dose or trade name) ([manual](./reference/ab_property.html))
* Plotting antimicrobial resistance ([tutorial](./articles/AMR.html))
* Determining first isolates to be used for AMR analysis ([manual](./reference/first_isolate.html))
* Applying EUCAST expert rules ([manual](./reference/eucast_rules.html)
* Descriptive statistics: frequency tables, kurtosis and skewness ([tutorial](./articles/freq.html))
This package is ready-to-use for a professional environment by specialists in the following fields:

View File

@@ -4,7 +4,7 @@
\name{antibiotics}
\alias{antibiotics}
\title{Data set with ~450 antibiotics}
\format{A \code{\link{data.frame}} with 455 observations and 13 variables:
\format{A \code{\link{data.frame}} with 454 observations and 13 variables:
\describe{
\item{\code{ab}}{Antibiotic ID as used in this package (like \code{AMC}), using the official EARS-Net (European Antimicrobial Resistance Surveillance Network) codes where available}
\item{\code{atc}}{ATC code (Anatomical Therapeutic Chemical) as defined by the WHOCC, like \code{J01CR02}}

View File

@@ -55,9 +55,9 @@ The function \code{is.rsi.eligible} returns \code{TRUE} when a columns contains
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".
\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{I}}{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.}
\item{\strong{R}}{Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.}
\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{I} - }{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.}
\item{\strong{R} - }{Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.}
}
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.

View File

@@ -43,7 +43,7 @@ count_df(data, translate_ab = "name", language = get_locale(),
\item{language}{language of the returned text, defaults to system language (see \code{\link{get_locale}}) and can also be set with \code{\link{getOption}("AMR_locale")}. Use \code{language = NULL} or \code{language = ""} to prevent translation.}
\item{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 below. Default is now \code{TRUE}.}
\item{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}.}
\item{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}.}
}
@@ -67,9 +67,9 @@ These functions are meant to count isolates. Use the \code{\link{portion}_*} fun
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".
\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{I}}{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.}
\item{\strong{R}}{Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.}
\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{I} - }{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.}
\item{\strong{R} - }{Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.}
}
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.

View File

@@ -43,7 +43,7 @@ eucast_rules_file()
\item{...}{column name of an antibiotic, see section Antibiotics}
}
\value{
The input of \code{tbl_}, possibly with edited values of antibiotics. Or, if \code{verbose = TRUE}, a \code{data.frame} with all original and new values of the affected bug-drug combinations.
The input of \code{x}, possibly with edited values of antibiotics. Or, if \code{verbose = TRUE}, a \code{data.frame} with all original and new values of the affected bug-drug combinations.
}
\description{
Apply susceptibility rules as defined by the European Committee on Antimicrobial Susceptibility Testing (EUCAST, \url{http://eucast.org}), see \emph{Source}. This includes (1) expert rules, (2) intrinsic resistance and (3) inferred resistance as defined in their breakpoint tables.

View File

@@ -50,7 +50,7 @@ labels_rsi_count(position = NULL, x = "Antibiotic",
\item{translate_ab}{a column name of the \code{\link{antibiotics}} data set to translate the antibiotic abbreviations to, using \code{\link{ab_property}}}
\item{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 below. Default is now \code{TRUE}.}
\item{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}.}
\item{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}.}

View File

@@ -5,26 +5,25 @@
\alias{key_antibiotics_equal}
\title{Key antibiotics for first \emph{weighted} isolates}
\usage{
key_antibiotics(tbl, col_mo = NULL, universal_1 = guess_ab_col(tbl,
"AMX"), universal_2 = guess_ab_col(tbl, "AMC"),
universal_3 = guess_ab_col(tbl, "CXM"),
universal_4 = guess_ab_col(tbl, "TZP"),
universal_5 = guess_ab_col(tbl, "CIP"),
universal_6 = guess_ab_col(tbl, "SXT"), GramPos_1 = guess_ab_col(tbl,
"VAN"), GramPos_2 = guess_ab_col(tbl, "TEC"),
GramPos_3 = guess_ab_col(tbl, "TCY"), GramPos_4 = guess_ab_col(tbl,
"ERY"), GramPos_5 = guess_ab_col(tbl, "OXA"),
GramPos_6 = guess_ab_col(tbl, "RIF"), GramNeg_1 = guess_ab_col(tbl,
"GEN"), GramNeg_2 = guess_ab_col(tbl, "TOB"),
GramNeg_3 = guess_ab_col(tbl, "COL"), GramNeg_4 = guess_ab_col(tbl,
"CTX"), GramNeg_5 = guess_ab_col(tbl, "CAZ"),
GramNeg_6 = guess_ab_col(tbl, "MEM"), warnings = TRUE, ...)
key_antibiotics(x, col_mo = NULL, universal_1 = guess_ab_col(x, "AMX"),
universal_2 = guess_ab_col(x, "AMC"), universal_3 = guess_ab_col(x,
"CXM"), universal_4 = guess_ab_col(x, "TZP"),
universal_5 = guess_ab_col(x, "CIP"), universal_6 = guess_ab_col(x,
"SXT"), GramPos_1 = guess_ab_col(x, "VAN"),
GramPos_2 = guess_ab_col(x, "TEC"), GramPos_3 = guess_ab_col(x,
"TCY"), GramPos_4 = guess_ab_col(x, "ERY"),
GramPos_5 = guess_ab_col(x, "OXA"), GramPos_6 = guess_ab_col(x,
"RIF"), GramNeg_1 = guess_ab_col(x, "GEN"),
GramNeg_2 = guess_ab_col(x, "TOB"), GramNeg_3 = guess_ab_col(x,
"COL"), GramNeg_4 = guess_ab_col(x, "CTX"),
GramNeg_5 = guess_ab_col(x, "CAZ"), GramNeg_6 = guess_ab_col(x,
"MEM"), warnings = TRUE, ...)
key_antibiotics_equal(x, y, type = c("keyantibiotics", "points"),
ignore_I = TRUE, points_threshold = 2, info = FALSE)
}
\arguments{
\item{tbl}{table with antibiotics coloms, like \code{amox} and \code{amcl}.}
\item{x}{table with antibiotics coloms, like \code{AMX} or \code{amox}}
\item{col_mo}{column name of the unique IDs of the microorganisms (see \code{\link{mo}}), defaults to the first column of class \code{mo}. Values will be coerced using \code{\link{as.mo}}.}
@@ -38,8 +37,6 @@ key_antibiotics_equal(x, y, type = c("keyantibiotics", "points"),
\item{...}{other parameters passed on to function}
\item{x, y}{characters to compare}
\item{type}{type to determine weighed isolates; can be \code{"keyantibiotics"} or \code{"points"}, see Details}
\item{ignore_I}{logical to determine whether antibiotic interpretations with \code{"I"} will be ignored when \code{type = "keyantibiotics"}, see Details}
@@ -47,6 +44,8 @@ key_antibiotics_equal(x, y, type = c("keyantibiotics", "points"),
\item{points_threshold}{points until the comparison of key antibiotics will lead to inclusion of an isolate when \code{type = "points"}, see Details}
\item{info}{print progress}
\item{x, y}{characters to compare}
}
\description{
These function can be used to determine first isolates (see \code{\link{first_isolate}}). Using key antibiotics to determine first isolates is more reliable than without key antibiotics. These selected isolates will then be called first \emph{weighted} isolates.

View File

@@ -4,22 +4,27 @@
\alias{mdro}
\alias{brmo}
\alias{mrgn}
\alias{mdr_tb}
\alias{eucast_exceptional_phenotypes}
\title{Determine multidrug-resistant organisms (MDRO)}
\usage{
mdro(x, country = NULL, col_mo = NULL, info = TRUE,
verbose = FALSE, ...)
mdro(x, country = NULL, guideline = NULL, col_mo = NULL,
info = TRUE, verbose = FALSE, ...)
brmo(..., country = "nl")
mrgn(x, country = "de", ...)
eucast_exceptional_phenotypes(x, country = "EUCAST", ...)
mdr_tb(x, guideline = "TB", ...)
eucast_exceptional_phenotypes(x, guideline = "EUCAST", ...)
}
\arguments{
\item{x}{table with antibiotic columns, like e.g. \code{AMX} and \code{AMC}}
\item{country}{country code to determine guidelines. EUCAST rules will be used when left empty, see Details. Should be or a code from the \href{https://en.wikipedia.org/wiki/ISO_3166-1_alpha-2#Officially_assigned_code_elements}{list of ISO 3166-1 alpha-2 country codes}. Case-insensitive. Currently supported are \code{de} (Germany) and \code{nl} (the Netherlands).}
\item{country}{country code to determine guidelines. Should be or a code from the \href{https://en.wikipedia.org/wiki/ISO_3166-1_alpha-2#Officially_assigned_code_elements}{list of ISO 3166-1 alpha-2 country codes}. Case-insensitive.}
\item{guideline}{a specific guideline to mention. For some countries this will be determined automatically, see Details. EUCAST guidelines will be used when left empty, see Details.}
\item{col_mo}{column name of the unique IDs of the microorganisms (see \code{\link{mo}}), defaults to the first column of class \code{mo}. Values will be coerced using \code{\link{as.mo}}.}
@@ -36,7 +41,19 @@ Ordered factor with levels \code{Negative < Positive, unconfirmed < Positive}.
Determine which isolates are multidrug-resistant organisms (MDRO) according to country-specific guidelines.
}
\details{
When \code{country} will be left blank, guidelines will be taken from EUCAST Expert Rules Version 3.1 "Intrinsic Resistance and Exceptional Phenotypes Tables" (\href{http://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf}{link}).
When \code{country} is set, the parameter guideline will be ignored as these guidelines will be used:
\itemize{
\item{\code{country = "nl"}: Rijksinstituut voor Volksgezondheid en Milieu "WIP-richtlijn BRMO (Bijzonder Resistente Micro-Organismen) [ZKH]" (\href{https://www.rivm.nl/Documenten_en_publicaties/Professioneel_Praktisch/Richtlijnen/Infectieziekten/WIP_Richtlijnen/WIP_Richtlijnen/Ziekenhuizen/WIP_richtlijn_BRMO_Bijzonder_Resistente_Micro_Organismen_ZKH}{link})}
}
Please suggest your own country's specific guidelines by letting us know: \url{https://gitlab.com/msberends/AMR/issues/new}.
Other currently supported guidelines are:
\itemize{
\item{\code{guideline = "eucast"}: EUCAST Expert Rules Version 3.1 "Intrinsic Resistance and Exceptional Phenotypes Tables" (\href{http://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf}{link})}
\item{\code{guideline = "tb"}: World Health Organization "Companion handbook to the WHO guidelines for the programmatic management of drug-resistant tuberculosis" (\href{https://www.who.int/tb/publications/pmdt_companionhandbook/en/}{link})}
}
}
\section{Antibiotics}{

View File

@@ -49,7 +49,7 @@ portion_df(data, translate_ab = "name", language = get_locale(),
\item{language}{language of the returned text, defaults to system language (see \code{\link{get_locale}}) and can also be set with \code{\link{getOption}("AMR_locale")}. Use \code{language = NULL} or \code{language = ""} to prevent translation.}
\item{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 below. Default is now \code{TRUE}.}
\item{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}.}
\item{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}.}
}
@@ -87,9 +87,9 @@ These functions are not meant to count isolates, but to calculate the portion of
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".
\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{I}}{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.}
\item{\strong{R}}{Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.}
\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{I} - }{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.}
\item{\strong{R} - }{Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.}
}
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.

View File

@@ -225,7 +225,7 @@ get_synonyms <- function(CID, clean = TRUE) {
synonyms
}
# get brand names (2-3 min)
# get brand names from PubChem (2-3 min)
synonyms <- get_synonyms(CIDs)
synonyms <- lapply(synonyms,
function(x) {
@@ -244,7 +244,9 @@ antibiotics <- abx2 %>%
atc,
cid = CIDs,
# no capital after a slash: Ampicillin/Sulbactam -> Ampicillin/sulbactam
name = gsub("edta", "EDTA", gsub("/([A-Z])", "/\\L\\1", name, perl = TRUE), ignore.case = TRUE),
name = name %>%
gsub("([/-])([A-Z])", "\\1\\L\\2", ., perl = TRUE) %>%
gsub("edta", "EDTA", ., ignore.case = TRUE),
group = case_when(
paste(atc_group1, atc_group2, CLASS, SUBCLASS) %like% "am(ph|f)enicol" ~ "Amphenicols",
paste(atc_group1, atc_group2, CLASS, SUBCLASS) %like% "aminoglycoside" ~ "Aminoglycosides",
@@ -283,6 +285,10 @@ antibiotics <- filter(antibiotics, ab != "POL")
# 'Latamoxef' (LTM) and 'Moxalactam (Latamoxef)' (MOX) both exist, so:
antibiotics[which(antibiotics$ab == "LTM"), "abbreviations"][[1]] <- list(c("MOX", "moxa"))
antibiotics <- filter(antibiotics, ab != "MOX")
# RFP and RFP1 (the J0 one) both mean 'rifapentine', although 'rifp' is not recognised, so:
antibiotics <- filter(antibiotics, ab != "RFP")
antibiotics[which(antibiotics$ab == "RFP1"), "ab"] <- "RFP"
antibiotics[which(antibiotics$ab == "RFP"), "abbreviations"][[1]] <- list(c("rifp"))
# ESBL E-test codes:
antibiotics[which(antibiotics$ab == "CCV"), "abbreviations"][[1]] <- list(c("xtzl"))
antibiotics[which(antibiotics$ab == "CAZ"), "abbreviations"][[1]] <- list(c(antibiotics[which(antibiotics$ab == "CAZ"), "abbreviations"][[1]], "xtz", "cefta"))
@@ -294,5 +300,6 @@ antibiotics[which(antibiotics$ab == "CTX"), "abbreviations"][[1]] <- list(c(anti
class(antibiotics$ab) <- "ab"
class(antibiotics$atc) <- "atc"
dim(antibiotics) # for R/data.R
usethis::use_data(antibiotics, overwrite = TRUE)
rm(antibiotics)

View File

@@ -24,8 +24,8 @@ context("mdro.R")
test_that("mdro works", {
library(dplyr)
expect_error(suppressWarnings(mdro(septic_patients, "invalid", col_mo = "mo", info = TRUE)))
expect_error(suppressWarnings(mdro(septic_patients, "fr", info = TRUE)))
expect_error(suppressWarnings(mdro(septic_patients, country = "invalid", col_mo = "mo", info = TRUE)))
expect_error(suppressWarnings(mdro(septic_patients, country = "fr", info = TRUE)))
expect_error(suppressWarnings(mdro(septic_patients, country = c("de", "nl"), info = TRUE)))
expect_error(suppressWarnings(mdro(septic_patients, col_mo = "invalid", info = TRUE)))
@@ -46,7 +46,7 @@ test_that("mdro works", {
suppressWarnings(
brmo(septic_patients, info = FALSE)),
suppressWarnings(
mdro(septic_patients, "nl", info = FALSE)
mdro(septic_patients, country = "nl", info = FALSE)
)
)
@@ -81,4 +81,32 @@ test_that("mdro works", {
info = FALSE))
), "Positive")
# MDR TB
expect_equal(
suppressWarnings(
# select only rifampicine, mo will be determined automatically (as M. tuberculosis),
# number of mono-resistant strains should be equal to number of rifampicine-resistant strains
septic_patients %>% select(RIF) %>% mdr_tb() %>% freq() %>% pull(count) %>% .[2]
),
count_R(septic_patients$RIF))
sample_rsi <- function() {
sample(c("S", "I", "R"),
size = 5000,
prob = c(0.5, 0.1, 0.4),
replace = TRUE)
}
expect_gt(
suppressWarnings(
data.frame(rifampicin = sample_rsi(),
inh = sample_rsi(),
gatifloxacin = sample_rsi(),
eth = sample_rsi(),
pza = sample_rsi(),
MFX = sample_rsi(),
KAN = sample_rsi()) %>%
mdr_tb() %>%
n_distinct()),
2)
})

79
vignettes/MDR.Rmd Normal file
View File

@@ -0,0 +1,79 @@
---
title: "How to determine multi-drug resistance (MDR)"
author: "Matthijs S. Berends"
date: '`r format(Sys.Date(), "%d %B %Y")`'
output:
rmarkdown::html_vignette:
toc: true
vignette: >
%\VignetteIndexEntry{How to determine multi-drug resistance (MDR)}
%\VignetteEncoding{UTF-8}
%\VignetteEngine{knitr::rmarkdown}
editor_options:
chunk_output_type: console
---
```{r setup, include = FALSE, results = 'markup'}
knitr::opts_chunk$set(
collapse = TRUE,
comment = "#"
)
library(AMR)
```
With the function `mdro()`, you can determine multi-drug resistant organisms (MDRO). It currently support these guidelines:
* "Intrinsic Resistance and Exceptional Phenotypes Tables", by EUCAST (European Committee on Antimicrobial Susceptibility Testing)
* "Companion handbook to the WHO guidelines for the programmatic management of drug-resistant tuberculosis", by WHO (World Health Organization)
* "WIP-Richtlijn Bijzonder Resistente Micro-organismen (BRMO)", by RIVM (Rijksinstituut voor de Volksgezondheid, the Netherlands National Institute for Public Health and the Environment)
As an example, I will make a data set to determine multi-drug resistant TB:
```{r}
# a helper function to get a random vector with values S, I and R
# with the probabilities 50%-10%-40%
sample_rsi <- function() {
sample(c("S", "I", "R"),
size = 5000,
prob = c(0.5, 0.1, 0.4),
replace = TRUE)
}
my_TB_data <- data.frame(rifampicin = sample_rsi(),
isoniazid = sample_rsi(),
gatifloxacin = sample_rsi(),
ethambutol = sample_rsi(),
pyrazinamide = sample_rsi(),
moxifloxacin = sample_rsi(),
kanamycin = sample_rsi())
```
Because all column names are automatically verified for valid drug names or codes, this would have worked exactly the same:
```{r, eval = FALSE}
my_TB_data <- data.frame(RIF = sample_rsi(),
INH = sample_rsi(),
GAT = sample_rsi(),
ETH = sample_rsi(),
PZA = sample_rsi(),
MFX = sample_rsi(),
KAN = sample_rsi())
```
The data set looks like this now:
```{r}
head(my_TB_data)
```
We can now add the interpretation of MDR-TB to our data set:
```{r}
my_TB_data$mdr <- mdr_tb(my_TB_data)
```
And review the result with a frequency table:
```{r}
freq(my_TB_data$mdr)
```

View File

@@ -128,7 +128,7 @@ septic_patients %>%
## Assigning a frequency table to an object
A frequency table is actaually a regular `data.frame`, with the exception that it contains an additional class.
A frequency table is actually a regular `data.frame`, with the exception that it contains an additional class.
```{r, echo = TRUE}
my_df <- septic_patients %>% freq(age)
@@ -144,15 +144,17 @@ dim(my_df)
## Additional parameters
### Parameter `na.rm`
With the `na.rm` parameter (defaults to `TRUE`, but they will always be shown into the header), you can include `NA` values in the frequency table:
With the `na.rm` parameter you can remove `NA` values from the frequency table (defaults to `TRUE`, but the number of `NA` values will always be shown into the header):
```{r, echo = TRUE}
septic_patients %>%
freq(AMX, na.rm = FALSE)
septic_patients %>%
freq(AMX, na.rm = FALSE)
```
### Parameter `row.names`
The default frequency tables shows row indices. To remove them, use `row.names = FALSE`:
A frequency table shows row indices. To remove them, use `row.names = FALSE`:
```{r, echo = TRUE}
septic_patients %>%