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

(v0.9.0.9029) add uti to as.rsi()

This commit is contained in:
2020-02-20 13:19:23 +01:00
parent a5db82c2fb
commit c6184a0fb8
71 changed files with 1129 additions and 800 deletions

View File

@@ -1,6 +1,6 @@
Package: AMR Package: AMR
Version: 1.0.0 Version: 1.0.0.9000
Date: 2020-02-17 Date: 2020-02-20
Title: Antimicrobial Resistance Analysis Title: Antimicrobial Resistance Analysis
Authors@R: c( Authors@R: c(
person(role = c("aut", "cre"), person(role = c("aut", "cre"),

16
NEWS.md
View File

@@ -1,3 +1,19 @@
# AMR 1.0.0.9000
## <small>Last updated: 20-Feb-2020</small>
### Changed
* Added antibiotic abbreviations for a laboratory manufacturer (GLIMS) for cefuroxime, cefotaxime, ceftazidime, cefepime, cefoxitin and trimethoprim/sulfamethoxazole
* Fixed floating point error for some MIC compa in EUCAST 2020 guideline
* Interpretation from MIC values to R/SI can now be used with `mutate_at()` of the dplyr package:
```r
yourdata %>%
mutate_at(vars(antibiotic1:antibiotic25), as.rsi, mo = "E. coli")
yourdata %>%
mutate_at(vars(antibiotic1:antibiotic25), as.rsi, mo = .$mybacteria)
```
* Added `uti` (as abbreviation of urinary tract infections) as parameter to `as.rsi()`, so interpretation of MIC values and disk zones can be made dependent on isolates specifically from UTIs
# AMR 1.0.0 # AMR 1.0.0
This software is now out of beta and considered stable. Nonetheless, this package will be developed continually. This software is now out of beta and considered stable. Nonetheless, this package will be developed continually.

View File

@@ -85,6 +85,11 @@ as.disk <- function(x, na.rm = FALSE) {
} }
} }
all_valid_disks <- function(x) {
x_disk <- suppressWarnings(as.disk(x[!is.na(x)]))
!any(is.na(x_disk)) & !all(is.na(x))
}
#' @rdname as.disk #' @rdname as.disk
#' @export #' @export
#' @importFrom dplyr %>% #' @importFrom dplyr %>%

10
R/mic.R
View File

@@ -65,11 +65,14 @@ as.mic <- function(x, na.rm = FALSE) {
# comma to period # comma to period
x <- gsub(",", ".", x, fixed = TRUE) x <- gsub(",", ".", x, fixed = TRUE)
# transform Unicode for >= and <=
x <- gsub("\u2264", "<=", x, fixed = TRUE)
x <- gsub("\u2265", ">=", x, fixed = TRUE)
# remove space between operator and number ("<= 0.002" -> "<=0.002") # remove space between operator and number ("<= 0.002" -> "<=0.002")
x <- gsub("(<|=|>) +", "\\1", x) x <- gsub("(<|=|>) +", "\\1", x)
# transform => to >= and =< to <= # transform => to >= and =< to <=
x <- gsub("=>", ">=", x, fixed = TRUE)
x <- gsub("=<", "<=", x, fixed = TRUE) x <- gsub("=<", "<=", x, fixed = TRUE)
x <- gsub("=>", ">=", x, fixed = TRUE)
# starting dots must start with 0 # starting dots must start with 0
x <- gsub("^[.]+", "0.", x) x <- gsub("^[.]+", "0.", x)
# <=0.2560.512 should be 0.512 # <=0.2560.512 should be 0.512
@@ -126,6 +129,11 @@ as.mic <- function(x, na.rm = FALSE) {
} }
} }
all_valid_mics <- function(x) {
x_mic <- suppressWarnings(as.mic(x[!is.na(x)]))
!any(is.na(x_mic)) & !all(is.na(x))
}
#' @rdname as.mic #' @rdname as.mic
#' @export #' @export
#' @importFrom dplyr %>% #' @importFrom dplyr %>%

View File

@@ -117,7 +117,22 @@ search_type_in_df <- function(x, type) {
found <- colnames(x)[colnames(x) %like% "^(specimen)"][1] found <- colnames(x)[colnames(x) %like% "^(specimen)"][1]
} }
} }
# -- UTI (urinary tract infection)
if (type == "uti") {
if (any(colnames(x) == "uti")) {
found <- colnames(x)[colnames(x) == "uti"][1]
} else if (any(colnames(x) %like% "(urine|urinary)")) {
found <- colnames(x)[colnames(x) %like% "(urine|urinary)"][1]
}
if (!is.null(found)) {
if (!is.logical(x[, found, drop = TRUE])) {
message(red(paste0("NOTE: Column `", bold(found), "` found as input for `col_", type,
"`, but this column does not contain 'logical' values (TRUE/FALSE) and was ignored.")))
found <- NULL
}
}
}
if (!is.null(found)) { if (!is.null(found)) {
msg <- paste0("NOTE: Using column `", bold(found), "` as input for `col_", type, "`.") msg <- paste0("NOTE: Using column `", bold(found), "` as input for `col_", type, "`.")
if (type %in% c("keyantibiotics", "specimen")) { if (type %in% c("keyantibiotics", "specimen")) {

363
R/rsi.R
View File

@@ -27,6 +27,7 @@
#' @param x vector of values (for class [`mic`]: an MIC value in mg/L, for class [`disk`]: a disk diffusion radius in millimetres) #' @param x vector of values (for class [`mic`]: an MIC value in mg/L, for class [`disk`]: a disk diffusion radius in millimetres)
#' @param mo any (vector of) text that can be coerced to a valid microorganism code with [as.mo()] #' @param mo any (vector of) text that can be coerced to a valid microorganism code with [as.mo()]
#' @param ab any (vector of) text that can be coerced to a valid antimicrobial code with [as.ab()] #' @param ab any (vector of) text that can be coerced to a valid antimicrobial code with [as.ab()]
#' @param uti (Urinary Tract Infection) A vector with [logical]s (`TRUE` or `FALSE`) to specify whether a UTI specific interpretation from the guideline should be chosen. For using [as.rsi()] on a [data.frame], this can also be a column containing [logical]s or when left blank, the data set will be search for a 'specimen' and rows containing 'urin' in that column will be regarded isolates from a UTI. See *Examples*.
#' @inheritParams first_isolate #' @inheritParams first_isolate
#' @param guideline defaults to the latest included EUCAST guideline, run `unique(rsi_translation$guideline)` for all options #' @param guideline defaults to the latest included EUCAST guideline, run `unique(rsi_translation$guideline)` for all options
#' @param threshold maximum fraction of invalid antimicrobial interpretations of `x`, please see *Examples* #' @param threshold maximum fraction of invalid antimicrobial interpretations of `x`, please see *Examples*
@@ -52,13 +53,45 @@
#' @return Ordered factor with new class [`rsi`] #' @return Ordered factor with new class [`rsi`]
#' @aliases rsi #' @aliases rsi
#' @export #' @export
#' @importFrom dplyr %>% desc arrange filter
#' @seealso [as.mic()] #' @seealso [as.mic()]
#' @inheritSection AMR Read more on our website! #' @inheritSection AMR Read more on our website!
#' @examples #' @examples
#' # For INTERPRETING disk diffusion and MIC values ----------------------- #' # For INTERPRETING disk diffusion and MIC values -----------------------
#'
#' # a whole data set, even with combined MIC values and disk zones
#' df <- data.frame(microorganism = "E. coli",
#' AMP = as.mic(8),
#' CIP = as.mic(0.256),
#' GEN = as.disk(18),
#' TOB = as.disk(16),
#' NIT = as.mic(32))
#' as.rsi(df)
#' #'
#' # single values #' # the dplyr way
#' library(dplyr)
#' df %>%
#' mutate_at(vars(AMP:TOB), as.rsi, mo = "E. coli")
#'
#' df %>%
#' mutate_at(vars(AMP:TOB), as.rsi, mo = .$microorganism)
#'
#' # to include information about urinary tract infections (UTI)
#' data.frame(mo = "E. coli",
#' NIT = c("<= 2", 32),
#' from_the_bladder = c(TRUE, FALSE)) %>%
#' as.rsi(uti = "from_the_bladder")
#'
#' data.frame(mo = "E. coli",
#' NIT = c("<= 2", 32),
#' specimen = c("urine", "blood")) %>%
#' as.rsi() # automatically determines urine isolates
#'
#' df %>%
#' mutate_at(vars(AMP:TOB), as.rsi, mo = "E. coli", uti = TRUE)
#'
#'
#'
#' # for single values
#' as.rsi(x = as.mic(2), #' as.rsi(x = as.mic(2),
#' mo = as.mo("S. pneumoniae"), #' mo = as.mo("S. pneumoniae"),
#' ab = "AMP", #' ab = "AMP",
@@ -68,14 +101,6 @@
#' mo = "Strep pneu", # `mo` will be coerced with as.mo() #' mo = "Strep pneu", # `mo` will be coerced with as.mo()
#' ab = "ampicillin", # and `ab` with as.ab() #' ab = "ampicillin", # and `ab` with as.ab()
#' guideline = "EUCAST") #' guideline = "EUCAST")
#'
#' # a whole data set, even with combined MIC values and disk zones
#' df <- data.frame(microorganism = "E. coli",
#' AMP = as.mic(8),
#' CIP = as.mic(0.256),
#' GEN = as.disk(18),
#' TOB = as.disk(16))
#' as.rsi(df)
#' #'
#' #'
#' # For CLEANING existing R/SI values ------------------------------------ #' # For CLEANING existing R/SI values ------------------------------------
@@ -114,6 +139,11 @@ as.rsi.default <- function(x, ...) {
x x
} else if (identical(levels(x), c("S", "I", "R"))) { } else if (identical(levels(x), c("S", "I", "R"))) {
structure(x, class = c("rsi", "ordered", "factor")) structure(x, class = c("rsi", "ordered", "factor"))
} else if (all_valid_mics(x) & !all(is.na(x))) {
as.rsi(as.mic(x), ab = deparse(substitute(x)), ...)
} else if (all_valid_disks(x) & !all(is.na(x))) {
#message("These values seem to be disk diffusion diameters and were treated as such.")
as.rsi(as.disk(x), ab = deparse(substitute(x)), ...)
} else if (identical(class(x), "integer") & all(x %in% c(1:3, NA))) { } else if (identical(class(x), "integer") & all(x %in% c(1:3, NA))) {
x[x == 1] <- "S" x[x == 1] <- "S"
x[x == 2] <- "I" x[x == 2] <- "I"
@@ -164,6 +194,7 @@ as.rsi.default <- function(x, ...) {
} }
} }
#' @importFrom dplyr %>%
input_resembles_mic <- function(x) { input_resembles_mic <- function(x) {
mic <- x %>% mic <- x %>%
gsub("[^0-9.,]+", "", .) %>% gsub("[^0-9.,]+", "", .) %>%
@@ -178,26 +209,184 @@ input_resembles_mic <- function(x) {
} }
#' @rdname as.rsi #' @rdname as.rsi
#' @importFrom dplyr case_when
#' @export #' @export
as.rsi.mic <- function(x, mo, ab, guideline = "EUCAST", ...) { as.rsi.mic <- function(x, mo, ab = deparse(substitute(x)), guideline = "EUCAST", uti = FALSE, ...) {
exec_as.rsi(method = "mic", if (missing(mo)) {
x = x, stop('No information was supplied about the microorganisms (missing parameter "mo"). See ?as.rsi.\n\n',
mo = mo, "To transform certain columns with e.g. mutate_at(), use\n",
ab = ab, "`data %>% mutate_at(vars(...), as.rsi, mo = .$x)`, where x is your column with microorganisms.\n\n",
guideline = guideline) "To tranform all MIC variables in a data set, use `as.rsi(data)` or `data %>% as.rsi()`.", call. = FALSE)
}
ab_coerced <- suppressWarnings(as.ab(ab))
mo_coerced <- suppressWarnings(as.mo(mo))
guideline_coerced <- get_guideline(guideline)
if (is.na(ab_coerced)) {
message(red(paste0("Unknown drug: `", bold(ab), "`. Rename this column to a drug name or code, and check the output with as.ab().")))
return(as.rsi(rep(NA, length(x))))
}
if (length(mo_coerced) == 1) {
mo_coerced <- rep(mo_coerced, length(x))
}
if (length(uti) == 1) {
uti <- rep(uti, length(x))
}
message(blue(paste0("=> Interpreting MIC values of column `", bold(ab), "` (",
ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""),
ab_name(ab_coerced, tolower = TRUE), ") using guideline ", bold(guideline_coerced), " ... ")),
appendLF = FALSE)
result <- exec_as.rsi(method = "mic",
x = x,
mo = mo_coerced,
ab = ab_coerced,
guideline = guideline_coerced,
uti = uti) # exec_as.rsi will return message(blue(" OK."))
result
} }
#' @rdname as.rsi #' @rdname as.rsi
#' @export #' @export
as.rsi.disk <- function(x, mo, ab, guideline = "EUCAST", ...) { as.rsi.disk <- function(x, mo, ab = deparse(substitute(x)), guideline = "EUCAST", uti = FALSE, ...) {
exec_as.rsi(method = "disk", if (missing(mo)) {
x = x, stop('No information was supplied about the microorganisms (missing parameter "mo"). See ?as.rsi.\n\n',
mo = mo, "To transform certain columns with e.g. mutate_at(), use\n",
ab = ab, "`data %>% mutate_at(vars(...), as.rsi, mo = .$x)`, where x is your column with microorganisms.\n\n",
guideline = guideline) "To tranform all disk diffusion zones in a data set, use `as.rsi(data)` or `data %>% as.rsi()`.", call. = FALSE)
}
ab_coerced <- suppressWarnings(as.ab(ab))
mo_coerced <- suppressWarnings(as.mo(mo))
guideline_coerced <- get_guideline(guideline)
if (is.na(ab_coerced)) {
message(red(paste0("Unknown drug: `", bold(ab), "`. Rename this column to a drug name or code, and check the output with as.ab().")))
return(as.rsi(rep(NA, length(x))))
}
if (length(mo_coerced) == 1) {
mo_coerced <- rep(mo_coerced, length(x))
}
if (length(uti) == 1) {
uti <- rep(uti, length(x))
}
message(blue(paste0("=> Interpreting disk zones of column `", bold(ab), "` (",
ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""),
ab_name(ab_coerced, tolower = TRUE), ") using guideline ", bold(guideline_coerced), " ... ")),
appendLF = FALSE)
result <- exec_as.rsi(method = "disk",
x = x,
mo = mo_coerced,
ab = ab_coerced,
guideline = guideline_coerced,
uti = uti) # exec_as.rsi will return message(blue(" OK."))
result
} }
#' @rdname as.rsi
#' @importFrom crayon red blue bold
#' @export
as.rsi.data.frame <- function(x, col_mo = NULL, guideline = "EUCAST", uti = NULL, ...) {
# try to find columns based on type
# -- mo
if (is.null(col_mo)) {
col_mo <- search_type_in_df(x = x, type = "mo")
}
if (is.null(col_mo)) {
stop("`col_mo` must be set.", call. = FALSE)
}
# -- UTIs
col_uti <- uti
if (is.null(col_uti)) {
col_uti <- search_type_in_df(x = x, type = "uti")
}
if (!is.null(col_uti)) {
if (is.logical(col_uti)) {
# already a logical vector as input
if (length(col_uti) == 1) {
uti <- rep(col_uti, NROW(x))
} else {
uti <- col_uti
}
} else {
# column found, transform to logical
uti <- as.logical(x[, col_uti, drop = TRUE])
}
} else {
# look for specimen column and make logicals of the urines
col_specimen <- suppressMessages(search_type_in_df(x = x, type = "specimen"))
if (!is.null(col_specimen)) {
uti <- x[, col_specimen, drop = TRUE] %like% "urin"
values <- sort(unique(x[uti, col_specimen, drop = TRUE]))
if (length(values) > 1) {
plural <- c("s", "", "")
} else {
plural <- c("", "s", "a ")
}
message(blue(paste0("NOTE: Assuming value", plural[1], " ",
paste(paste0('"', values, '"'), collapse = ", "),
" in column `", bold(col_specimen),
"` reflect", plural[2], " ", plural[3], "urinary tract infection", plural[1], ".\n Use `as.rsi(uti = FALSE)` to prevent this.")))
} else {
# no data about UTI's found
uti <- FALSE
}
}
i <- 0
ab_cols <- colnames(x)[sapply(x, function(y) {
i <<- i + 1
check <- is.mic(y) | is.disk(y)
ab <- colnames(x)[i]
ab_coerced <- suppressWarnings(as.ab(ab))
if (is.na(ab_coerced)) {
# not even a valid AB code
return(FALSE)
} else if (!check & all_valid_mics(y)) {
message(blue(paste0("NOTE: Assuming column `", ab, "` (",
ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""),
ab_name(ab_coerced, tolower = TRUE), ") contains MIC values.")))
return(TRUE)
} else if (!check & all_valid_disks(y)) {
message(blue(paste0("NOTE: Assuming column `", ab, "` (",
ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""),
ab_name(ab_coerced, tolower = TRUE), ") contains disk zones.")))
return(TRUE)
} else {
return(check)
}
})]
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 antimicrobial columns.", call. = FALSE)
}
# set type per column
types <- character(length(ab_cols))
types[sapply(x[, ab_cols], is.mic)] <- "mic"
types[types == "" & sapply(x[, ab_cols], all_valid_mics)] <- "mic"
types[sapply(x[, ab_cols], is.disk)] <- "disk"
types[types == "" & sapply(x[, ab_cols], all_valid_disks)] <- "disk"
for (i in seq_len(length(ab_cols))) {
if (types[i] == "mic") {
x[, ab_cols[i]] <- as.rsi.mic(x = x %>% pull(ab_cols[i]),
mo = x %>% pull(col_mo),
ab = ab_cols[i],
guideline = guideline,
uti = uti)
} else if (types[i] == "disk") {
x[, ab_cols[i]] <- as.rsi.disk(x = x %>% pull(ab_cols[i]),
mo = x %>% pull(col_mo),
ab = ab_cols[i],
guideline = guideline,
uti = uti)
}
}
x
}
#' @importFrom dplyr %>% filter pull
get_guideline <- function(guideline) { get_guideline <- function(guideline) {
guideline_param <- toupper(guideline) guideline_param <- toupper(guideline)
if (guideline_param %in% c("CLSI", "EUCAST")) { if (guideline_param %in% c("CLSI", "EUCAST")) {
@@ -216,19 +405,20 @@ get_guideline <- function(guideline) {
} }
guideline_param guideline_param
} }
exec_as.rsi <- function(method, x, mo, ab, guideline) { #' @importFrom dplyr %>% case_when desc arrange filter n_distinct
#' @importFrom crayon green red bold
exec_as.rsi <- function(method, x, mo, ab, guideline, uti) {
if (method == "mic") { if (method == "mic") {
x <- as.double(as.mic(x)) # when as.rsi.mic is called directly x <- as.mic(x) # when as.rsi.mic is called directly
method_param <- "MIC"
} else if (method == "disk") { } else if (method == "disk") {
x <- as.double(as.disk(x)) # when as.rsi.disk is called directly x <- as.disk(x) # when as.rsi.disk is called directly
method_param <- "DISK"
} }
mo <- as.mo(mo) warned <- FALSE
ab <- as.ab(ab) method_param <- toupper(method)
mo_genus <- as.mo(mo_genus(mo)) mo_genus <- as.mo(mo_genus(mo))
mo_family <- as.mo(mo_family(mo)) mo_family <- as.mo(mo_family(mo))
@@ -243,8 +433,9 @@ exec_as.rsi <- function(method, x, mo, ab, guideline) {
} }
new_rsi <- rep(NA_character_, length(x)) new_rsi <- rep(NA_character_, length(x))
ab_param <- ab
trans <- rsi_translation %>% trans <- rsi_translation %>%
filter(guideline == guideline_coerced & method == method_param) %>% filter(guideline == guideline_coerced & method == method_param & ab == ab_param) %>%
mutate(lookup = paste(mo, ab)) mutate(lookup = paste(mo, ab))
lookup_mo <- paste(mo, ab) lookup_mo <- paste(mo, ab)
@@ -255,110 +446,62 @@ exec_as.rsi <- function(method, x, mo, ab, guideline) {
lookup_lancefield <- paste(mo_lancefield, ab) lookup_lancefield <- paste(mo_lancefield, ab)
lookup_other <- paste(mo_other, ab) lookup_other <- paste(mo_other, ab)
if (all(trans$uti == TRUE, na.rm = TRUE) & all(uti == FALSE)) {
message(red("WARNING."))
warning("Interpretation of ", bold(ab_name(ab, tolower = TRUE)), " for some microorganisms is only available for (uncomplicated) urinary tract infections (UTI).\n Use parameter 'uti' to set which isolates are from urine. See ?as.rsi.", call. = FALSE)
warned <- TRUE
}
for (i in seq_len(length(x))) { for (i in seq_len(length(x))) {
get_record <- trans %>% get_record <- trans %>%
# no UTI for now
filter(lookup %in% c(lookup_mo[i], filter(lookup %in% c(lookup_mo[i],
lookup_genus[i], lookup_genus[i],
lookup_family[i], lookup_family[i],
lookup_order[i], lookup_order[i],
lookup_becker[i], lookup_becker[i],
lookup_lancefield[i], lookup_lancefield[i],
lookup_other[i])) %>% lookup_other[i]))
# be as specific as possible (i.e. prefer species over genus):
arrange(desc(nchar(mo))) %>% if (isTRUE(uti[i])) {
.[1L, ] get_record <- get_record %>%
# be as specific as possible (i.e. prefer species over genus):
# desc(uti) = TRUE on top and FALSE on bottom
arrange(desc(uti), desc(nchar(mo))) %>% # 'uti' is a column in rsi_translation
.[1L, ]
} else {
get_record <- get_record %>%
filter(uti == FALSE) %>% # 'uti' is a column in rsi_translation
arrange(desc(nchar(mo))) %>%
.[1L, ]
}
if (NROW(get_record) > 0) { if (NROW(get_record) > 0) {
if (is.na(x[i])) { if (is.na(x[i])) {
new_rsi[i] <- NA_character_ new_rsi[i] <- NA_character_
} else if (method == "mic") { } else if (method == "mic") {
new_rsi[i] <- case_when(isTRUE(x[i] <= get_record$breakpoint_S) ~ "S", mic_input <- x[i]
isTRUE(x[i] >= get_record$breakpoint_R) ~ "R", mic_S <- as.mic(get_record$breakpoint_S)
mic_R <- as.mic(get_record$breakpoint_R)
new_rsi[i] <- case_when(isTRUE(which(levels(mic_input) == mic_input) <= which(levels(mic_S) == mic_S)) ~ "S",
isTRUE(which(levels(mic_input) == mic_input) >= which(levels(mic_R) == mic_R)) ~ "R",
!is.na(get_record$breakpoint_S) & !is.na(get_record$breakpoint_R) ~ "I", !is.na(get_record$breakpoint_S) & !is.na(get_record$breakpoint_R) ~ "I",
TRUE ~ NA_character_) TRUE ~ NA_character_)
} else if (method == "disk") { } else if (method == "disk") {
new_rsi[i] <- case_when(isTRUE(x[i] >= get_record$breakpoint_S) ~ "S", new_rsi[i] <- case_when(isTRUE(as.double(x[i]) >= as.double(get_record$breakpoint_S)) ~ "S",
isTRUE(x[i] <= get_record$breakpoint_R) ~ "R", isTRUE(as.double(x[i]) <= as.double(get_record$breakpoint_R)) ~ "R",
!is.na(get_record$breakpoint_S) & !is.na(get_record$breakpoint_R) ~ "I", !is.na(get_record$breakpoint_S) & !is.na(get_record$breakpoint_R) ~ "I",
TRUE ~ NA_character_) TRUE ~ NA_character_)
} }
} }
} }
if (warned == FALSE) {
message(green("OK."))
}
structure(.Data = factor(new_rsi, levels = c("S", "I", "R"), ordered = TRUE), structure(.Data = factor(new_rsi, levels = c("S", "I", "R"), ordered = TRUE),
class = c("rsi", "ordered", "factor")) class = c("rsi", "ordered", "factor"))
} }
#' @rdname as.rsi
#' @importFrom crayon red blue bold
#' @export
as.rsi.data.frame <- function(x, col_mo = NULL, guideline = "EUCAST", ...) {
x <- 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 antimicrobial columns.", call. = FALSE)
}
# try to find columns based on type
# -- mo
if (is.null(col_mo)) {
col_mo <- search_type_in_df(x = x, type = "mo")
}
if (is.null(col_mo)) {
stop("`col_mo` must be set.", call. = FALSE)
}
guideline_coerced <- get_guideline(guideline)
if (guideline_coerced != guideline) {
message(blue(paste0("Note: Using guideline ", bold(guideline_coerced), " as input for `guideline`.")))
}
# transform all MICs
ab_cols <- colnames(x)[sapply(x, is.mic)]
if (length(ab_cols) > 0) {
for (i in seq_len(length(ab_cols))) {
ab_col_coerced <- suppressWarnings(as.ab(ab_cols[i]))
if (is.na(ab_col_coerced)) {
message(red(paste0("Unknown drug: `", bold(ab_cols[i]), "`. Rename this column to a drug name or code, and check the output with as.ab().")))
next
}
message(blue(paste0("Interpreting MIC values of column `", bold(ab_cols[i]), "` (",
ifelse(ab_col_coerced != ab_cols[i], paste0(ab_col_coerced, ", "), ""),
ab_name(ab_col_coerced, tolower = TRUE), ")...")),
appendLF = FALSE)
x[, ab_cols[i]] <- exec_as.rsi(method = "mic",
x = x %>% pull(ab_cols[i]),
mo = x %>% pull(col_mo),
ab = ab_col_coerced,
guideline = guideline_coerced)
message(blue(" OK."))
}
}
# transform all disks
ab_cols <- colnames(x)[sapply(x, is.disk)]
if (length(ab_cols) > 0) {
for (i in seq_len(length(ab_cols))) {
ab_col_coerced <- suppressWarnings(as.ab(ab_cols[i]))
if (is.na(ab_col_coerced)) {
message(red(paste0("Unknown drug: `", bold(ab_cols[i]), "`. Rename this column to a drug name or code, and check the output with as.ab().")))
next
}
message(blue(paste0("Interpreting disk zones of column `", bold(ab_cols[i]), "` (",
ifelse(ab_col_coerced != ab_cols[i], paste0(ab_col_coerced, ", "), ""),
ab_name(ab_col_coerced, tolower = TRUE), ")...")),
appendLF = FALSE)
x[, ab_cols[i]] <- exec_as.rsi(method = "disk",
x = x %>% pull(ab_cols[i]),
mo = x %>% pull(col_mo),
ab = ab_col_coerced,
guideline = guideline_coerced)
message(blue(" OK."))
}
}
x
}
#' @rdname as.rsi #' @rdname as.rsi
#' @export #' @export
is.rsi <- function(x) { is.rsi <- function(x) {

View File

@@ -62,7 +62,7 @@
"CDR" "J01DD15" 6915944 "Cefdinir" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "c(\"cdn\", \"cdr\", \"din\", \"cd\", \"cfd\")" "c(\"Cefdinir\", \"Cefdinirum\", \"Cefdinyl\", \"Cefdirnir\", \"Ceftinex\", \"Cefzon\", \"Omnicef\")" 0.6 "g" "CDR" "J01DD15" 6915944 "Cefdinir" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "c(\"cdn\", \"cdr\", \"din\", \"cd\", \"cfd\")" "c(\"Cefdinir\", \"Cefdinirum\", \"Cefdinyl\", \"Cefdirnir\", \"Ceftinex\", \"Cefzon\", \"Omnicef\")" 0.6 "g"
"DIT" "J01DD16" 9870843 "Cefditoren" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "cdn" "Cefditoren" 0.4 "g" "DIT" "J01DD16" 9870843 "Cefditoren" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "cdn" "Cefditoren" 0.4 "g"
"DIX" 6437877 "Cefditoren pivoxil" "Cephalosporins (3rd gen.)" "c(\"Cefditoren\", \"Cefditoren PI voxil\", \"Cefditoren pivoxil\", \"Cefditoren Pivoxil\", \"Cefditorin\", \"CEFDITORIN PIVOXIL\", \"Meiact\", \"Spectracef\")" "DIX" 6437877 "Cefditoren pivoxil" "Cephalosporins (3rd gen.)" "c(\"Cefditoren\", \"Cefditoren PI voxil\", \"Cefditoren pivoxil\", \"Cefditoren Pivoxil\", \"Cefditorin\", \"CEFDITORIN PIVOXIL\", \"Meiact\", \"Spectracef\")"
"FEP" "J01DE01" 5479537 "Cefepime" "Cephalosporins (4th gen.)" "Other beta-lactam antibacterials" "Fourth-generation cephalosporins" "c(\"cpe\", \"fep\", \"pm\", \"cpm\", \"cfep\", \"xpm\")" "c(\"Axepim\", \"Cefepima\", \"Cefepime\", \"Cefepimum\", \"Cepimax\", \"Cepimex\", \"Maxcef\", \"Maxipime\")" 2 "g" "38363-8" "FEP" "J01DE01" 5479537 "Cefepime" "Cephalosporins (4th gen.)" "Other beta-lactam antibacterials" "Fourth-generation cephalosporins" "c(\"cpe\", \"fep\", \"pm\", \"cpm\", \"cfep\", \"xpm\", \"cfpi\")" "c(\"Axepim\", \"Cefepima\", \"Cefepime\", \"Cefepimum\", \"Cepimax\", \"Cepimex\", \"Maxcef\", \"Maxipime\")" 2 "g" "38363-8"
"CPC" 9567559 "Cefepime/clavulanic acid" "Cephalosporins (4th gen.)" "xpml" "" "CPC" 9567559 "Cefepime/clavulanic acid" "Cephalosporins (4th gen.)" "xpml" ""
"FPT" 9567558 "Cefepime/tazobactam" "Cephalosporins (4th gen.)" "" "FPT" 9567558 "Cefepime/tazobactam" "Cephalosporins (4th gen.)" ""
"FPZ" "Cefepime/zidebactam" "Other antibacterials" "" "FPZ" "Cefepime/zidebactam" "Other antibacterials" ""
@@ -81,14 +81,14 @@
"CSL" "J01DD62" "Cefoperazone/sulbactam" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "" 4 "g" "CSL" "J01DD62" "Cefoperazone/sulbactam" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "" 4 "g"
"CND" "J01DC11" 43507 "Ceforanide" "Cephalosporins (2nd gen.)" "Other beta-lactam antibacterials" "Second-generation cephalosporins" "c(\"Ceforanide\", \"Ceforanido\", \"Ceforanidum\", \"Precef\", \"Radacef\")" 4 "g" "CND" "J01DC11" 43507 "Ceforanide" "Cephalosporins (2nd gen.)" "Other beta-lactam antibacterials" "Second-generation cephalosporins" "c(\"Ceforanide\", \"Ceforanido\", \"Ceforanidum\", \"Precef\", \"Radacef\")" 4 "g"
"CSE" 9830519 "Cefoselis" "Cephalosporins (4th gen.)" "c(\"Cefoselis\", \"Cefoselis sulfate\", \"Winsef\")" "CSE" 9830519 "Cefoselis" "Cephalosporins (4th gen.)" "c(\"Cefoselis\", \"Cefoselis sulfate\", \"Winsef\")"
"CTX" "J01DD01" 5742673 "Cefotaxime" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "c(\"cft\", \"ctx\", \"tax\", \"fot\", \"ct\", \"cfot\", \"xct\")" "c(\"Cefotaxim\", \"Cefotaxim Hikma\", \"Cefotaxima\", \"Cefotaxime\", \"Cefotaxime acid\", \"Cefotaximum\", \"Cephotaxime\", \"Claforan\", \"Omnatax\")" 4 "g" "c(\"25238-7\", \"3446-2\", \"80961-6\")" "CTX" "J01DD01" 5742673 "Cefotaxime" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "c(\"cft\", \"ctx\", \"tax\", \"fot\", \"ct\", \"cfot\", \"xct\", \"cftx\")" "c(\"Cefotaxim\", \"Cefotaxim Hikma\", \"Cefotaxima\", \"Cefotaxime\", \"Cefotaxime acid\", \"Cefotaximum\", \"Cephotaxime\", \"Claforan\", \"Omnatax\")" 4 "g" "c(\"25238-7\", \"3446-2\", \"80961-6\")"
"CTC" 9575353 "Cefotaxime/clavulanic acid" "Cephalosporins (3rd gen.)" "xctl" "" "CTC" 9575353 "Cefotaxime/clavulanic acid" "Cephalosporins (3rd gen.)" "xctl" ""
"CTS" 9574753 "Cefotaxime/sulbactam" "Cephalosporins (3rd gen.)" "" "CTS" 9574753 "Cefotaxime/sulbactam" "Cephalosporins (3rd gen.)" ""
"CTT" "J01DC05" 53025 "Cefotetan" "Cephalosporins (2nd gen.)" "Other beta-lactam antibacterials" "Second-generation cephalosporins" "c(\"ctn\", \"ctt\", \"cte\", \"tans\", \"cn\")" "c(\"Apacef\", \"Cefotetan\", \"Cefotetan free acid\", \"Cefotetanum\")" 4 "g" "c(\"25239-5\", \"3447-0\")" "CTT" "J01DC05" 53025 "Cefotetan" "Cephalosporins (2nd gen.)" "Other beta-lactam antibacterials" "Second-generation cephalosporins" "c(\"ctn\", \"ctt\", \"cte\", \"tans\", \"cn\")" "c(\"Apacef\", \"Cefotetan\", \"Cefotetan free acid\", \"Cefotetanum\")" 4 "g" "c(\"25239-5\", \"3447-0\")"
"CTF" "J01DC07" 43708 "Cefotiam" "Cephalosporins (2nd gen.)" "Other beta-lactam antibacterials" "Second-generation cephalosporins" "c(\"Cefotiam\", \"Cefotiam?\", \"Cefotiamum\", \"Ceradolan\", \"Ceradon\", \"Haloapor\")" 1.2 "g" 4 "g" "CTF" "J01DC07" 43708 "Cefotiam" "Cephalosporins (2nd gen.)" "Other beta-lactam antibacterials" "Second-generation cephalosporins" "c(\"Cefotiam\", \"Cefotiam?\", \"Cefotiamum\", \"Ceradolan\", \"Ceradon\", \"Haloapor\")" 1.2 "g" 4 "g"
"CHE" 125846 "Cefotiam hexetil" "Cephalosporins (3rd gen.)" "c(\"Cefotiam cilexetil\", \"Pansporin T\")" "CHE" 125846 "Cefotiam hexetil" "Cephalosporins (3rd gen.)" "c(\"Cefotiam cilexetil\", \"Pansporin T\")"
"FOV" 9578573 "Cefovecin" "Cephalosporins (3rd gen.)" "" "FOV" 9578573 "Cefovecin" "Cephalosporins (3rd gen.)" ""
"FOX" "J01DC01" 441199 "Cefoxitin" "Cephalosporins (2nd gen.)" "Other beta-lactam antibacterials" "Second-generation cephalosporins" "c(\"cfx\", \"fox\", \"cx\", \"fx\", \"cfox\")" "c(\"Cefoxitin\", \"Cefoxitina\", \"Cefoxitine\", \"Cefoxitinum\", \"Cefoxotin\", \"CEPHOXITIN\", \"Mefoxin\", \"Mefoxitin\", \"Rephoxitin\")" 6 "g" "c(\"25240-3\", \"3448-8\")" "FOX" "J01DC01" 441199 "Cefoxitin" "Cephalosporins (2nd gen.)" "Other beta-lactam antibacterials" "Second-generation cephalosporins" "c(\"cfx\", \"fox\", \"cx\", \"fx\", \"cfox\", \"cfxt\")" "c(\"Cefoxitin\", \"Cefoxitina\", \"Cefoxitine\", \"Cefoxitinum\", \"Cefoxotin\", \"CEPHOXITIN\", \"Mefoxin\", \"Mefoxitin\", \"Rephoxitin\")" 6 "g" "c(\"25240-3\", \"3448-8\")"
"ZOP" 9571080 "Cefozopran" "Cephalosporins (4th gen.)" "Cefozopran" "ZOP" 9571080 "Cefozopran" "Cephalosporins (4th gen.)" "Cefozopran"
"CFZ" 68597 "Cefpimizole" "Cephalosporins (3rd gen.)" "c(\"Cefpimizol\", \"Cefpimizole\", \"Cefpimizole sodium\", \"Cefpimizolum\")" "CFZ" 68597 "Cefpimizole" "Cephalosporins (3rd gen.)" "c(\"Cefpimizol\", \"Cefpimizole\", \"Cefpimizole sodium\", \"Cefpimizolum\")"
"CPM" "J01DD11" 636405 "Cefpiramide" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "c(\"Cefpiramide\", \"Cefpiramide acid\", \"Cefpiramido\", \"Cefpiramidum\")" 2 "g" "CPM" "J01DD11" 636405 "Cefpiramide" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "c(\"Cefpiramide\", \"Cefpiramide acid\", \"Cefpiramido\", \"Cefpiramidum\")" 2 "g"
@@ -103,7 +103,7 @@
"CSU" 68718 "Cefsumide" "Cephalosporins (unclassified gen.)" "c(\"Cefsumide\", \"Cefsumido\", \"Cefsumidum\")" "CSU" 68718 "Cefsumide" "Cephalosporins (unclassified gen.)" "c(\"Cefsumide\", \"Cefsumido\", \"Cefsumidum\")"
"CPT" "J01DI02" 56841980 "Ceftaroline" "Cephalosporins (5th gen.)" "c(\"Teflaro\", \"Zinforo\")" "CPT" "J01DI02" 56841980 "Ceftaroline" "Cephalosporins (5th gen.)" "c(\"Teflaro\", \"Zinforo\")"
"CPA" "Ceftaroline/avibactam" "Cephalosporins (5th gen.)" "" "CPA" "Ceftaroline/avibactam" "Cephalosporins (5th gen.)" ""
"CAZ" "J01DD02" 5481173 "Ceftazidime" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "c(\"caz\", \"taz\", \"tz\", \"cfta\", \"xtz\", \"cefta\")" "c(\"Ceftazidim\", \"Ceftazidima\", \"Ceftazidime\", \"CEFTAZIDIME\", \"Ceftazidimum\", \"Ceptaz\", \"Fortaz\", \"Fortum\", \"Pentacef\", \"Tazicef\", \"Tazidime\")" 4 "g" "c(\"21151-6\", \"3449-6\", \"80960-8\")" "CAZ" "J01DD02" 5481173 "Ceftazidime" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "c(\"caz\", \"taz\", \"tz\", \"cfta\", \"xtz\", \"cefta\", \"cftz\")" "c(\"Ceftazidim\", \"Ceftazidima\", \"Ceftazidime\", \"CEFTAZIDIME\", \"Ceftazidimum\", \"Ceptaz\", \"Fortaz\", \"Fortum\", \"Pentacef\", \"Tazicef\", \"Tazidime\")" 4 "g" "c(\"21151-6\", \"3449-6\", \"80960-8\")"
"CZA" "Ceftazidime/avibactam" "Cephalosporins (3rd gen.)" "" "CZA" "Ceftazidime/avibactam" "Cephalosporins (3rd gen.)" ""
"CCV" "J01DD52" 9575352 "Ceftazidime/clavulanic acid" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "xtzl" "" "CCV" "J01DD52" 9575352 "Ceftazidime/clavulanic acid" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "xtzl" ""
"CEM" 6537431 "Cefteram" "Cephalosporins (3rd gen.)" "c(\"Cefteram\", \"Cefterame\", \"Cefteramum\", \"Ceftetrame\")" "CEM" 6537431 "Cefteram" "Cephalosporins (3rd gen.)" "c(\"Cefteram\", \"Cefterame\", \"Cefteramum\", \"Ceftetrame\")"
@@ -118,7 +118,7 @@
"CEI" "J01DI54" "Ceftolozane/enzyme inhibitor" "Cephalosporins (5th gen.)" "Other beta-lactam antibacterials" "Other cephalosporins" "" "CEI" "J01DI54" "Ceftolozane/enzyme inhibitor" "Cephalosporins (5th gen.)" "Other beta-lactam antibacterials" "Other cephalosporins" ""
"CZT" "Ceftolozane/tazobactam" "Cephalosporins (5th gen.)" "" "CZT" "Ceftolozane/tazobactam" "Cephalosporins (5th gen.)" ""
"CRO" "J01DD04" 5479530 "Ceftriaxone" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "c(\"cax\", \"cro\", \"ctr\", \"frx\", \"axo\", \"tx\", \"cftr\")" "c(\"Biotrakson\", \"Cefatriaxone\", \"Cefatriaxone hydrate\", \"Ceftriaxon\", \"Ceftriaxona\", \"Ceftriaxone\", \"CEFTRIAXONE SODIUM\", \"Ceftriaxonum\", \"Ceftriazone\", \"Cephtriaxone\", \"Longacef\", \"Rocefin\", \"Rocephalin\", \"Rocephin\", \"Rocephine\", \"Rophex\")" 2 "g" "c(\"25244-5\", \"3451-2\", \"80957-4\")" "CRO" "J01DD04" 5479530 "Ceftriaxone" "Cephalosporins (3rd gen.)" "Other beta-lactam antibacterials" "Third-generation cephalosporins" "c(\"cax\", \"cro\", \"ctr\", \"frx\", \"axo\", \"tx\", \"cftr\")" "c(\"Biotrakson\", \"Cefatriaxone\", \"Cefatriaxone hydrate\", \"Ceftriaxon\", \"Ceftriaxona\", \"Ceftriaxone\", \"CEFTRIAXONE SODIUM\", \"Ceftriaxonum\", \"Ceftriazone\", \"Cephtriaxone\", \"Longacef\", \"Rocefin\", \"Rocephalin\", \"Rocephin\", \"Rocephine\", \"Rophex\")" 2 "g" "c(\"25244-5\", \"3451-2\", \"80957-4\")"
"CXM" "J01DC02" 5479529 "Cefuroxime" "Cephalosporins (2nd gen.)" "Other beta-lactam antibacterials" "Second-generation cephalosporins" "c(\"crm\", \"cxm\", \"cfx\", \"rox\", \"fur\", \"xm\", \"cfur\")" "c(\"Biofuroksym\", \"Cefuril\", \"Cefuroxim\", \"Cefuroxime\", \"Cefuroximine\", \"Cefuroximo\", \"Cefuroximum\", \"Cephuroxime\", \"Kefurox\", \"Sharox\", \"Zinacef\", \"Zinacef Danmark\")" 0.5 "g" 3 "g" "c(\"25245-2\", \"3452-0\", \"80608-3\", \"80617-4\")" "CXM" "J01DC02" 5479529 "Cefuroxime" "Cephalosporins (2nd gen.)" "Other beta-lactam antibacterials" "Second-generation cephalosporins" "c(\"crm\", \"cxm\", \"cfx\", \"rox\", \"fur\", \"xm\", \"cfur\", \"cfrx\")" "c(\"Biofuroksym\", \"Cefuril\", \"Cefuroxim\", \"Cefuroxime\", \"Cefuroximine\", \"Cefuroximo\", \"Cefuroximum\", \"Cephuroxime\", \"Kefurox\", \"Sharox\", \"Zinacef\", \"Zinacef Danmark\")" 0.5 "g" 3 "g" "c(\"25245-2\", \"3452-0\", \"80608-3\", \"80617-4\")"
"CXA" 6321416 "Cefuroxime axetil" "Cephalosporins (2nd gen.)" "c(\"Altacef\", \"Bioracef\", \"Cefaks\", \"Cefazine\", \"Ceftin\", \"Cefuroximaxetil\", \"Cefuroxime axetil\", \"Celocid\", \"Cepazine\", \"Cethixim\", \"Cetoxil\", \"Coliofossim\", \"Elobact\", \"Forcef\", \"Furoxime\", \"Kalcef\", \"Maxitil\", \"Medoxm\", \"Nivador\", \"Zinnat\")" "CXA" 6321416 "Cefuroxime axetil" "Cephalosporins (2nd gen.)" "c(\"Altacef\", \"Bioracef\", \"Cefaks\", \"Cefazine\", \"Ceftin\", \"Cefuroximaxetil\", \"Cefuroxime axetil\", \"Celocid\", \"Cepazine\", \"Cethixim\", \"Cetoxil\", \"Coliofossim\", \"Elobact\", \"Forcef\", \"Furoxime\", \"Kalcef\", \"Maxitil\", \"Medoxm\", \"Nivador\", \"Zinnat\")"
"CFM2" "J01RA03" "Cefuroxime/metronidazole" "Other antibacterials" "Combinations of antibacterials" "Combinations of antibacterials" "" "CFM2" "J01RA03" "Cefuroxime/metronidazole" "Other antibacterials" "Combinations of antibacterials" "Combinations of antibacterials" ""
"ZON" 6336505 "Cefuzonam" "Other antibacterials" "c(\"Cefuzonam\", \"Cefuzonam sodium\", \"Cefuzoname\", \"Cefuzonamum\")" "ZON" 6336505 "Cefuzonam" "Other antibacterials" "c(\"Cefuzonam\", \"Cefuzonam sodium\", \"Cefuzoname\", \"Cefuzonamum\")"
@@ -490,7 +490,7 @@
"TMP" "J01EA01" 5578 "Trimethoprim" "Trimethoprims" "Sulfonamides and trimethoprim" "Trimethoprim and derivatives" "c(\"t\", \"tmp\", \"tr\", \"w\", \"trim\")" "c(\"Abaprim\", \"Alprim\", \"Anitrim\", \"Antrima\", \"Antrimox\", \"Bacdan\", \"Bacidal\", \"Bacide\", \"Bacterial\", \"Bacticel\", \"Bactifor\", \"Bactin\", \"Bactoprim\", \"Bactramin\", \"Bactrim\", \"Bencole\", \"Bethaprim\", \"Biosulten\", \"Briscotrim\", \"Chemotrin\", \"Colizole\", \"Colizole DS\", \"Conprim\", \"Cotrimel\", \"CoTrimoxizole\", \"Deprim\", \"Dosulfin\", \"Duocide\", \"Esbesul\", \"Espectrin\", \"Euctrim\", \"Exbesul\", \"Fermagex\", \"Fortrim\", \"Idotrim\", \"Ikaprim\", \"Instalac\", \"Kombinax\", \"Lagatrim\", \"Lagatrim Forte\", \"Lastrim\", \"Lescot\", "TMP" "J01EA01" 5578 "Trimethoprim" "Trimethoprims" "Sulfonamides and trimethoprim" "Trimethoprim and derivatives" "c(\"t\", \"tmp\", \"tr\", \"w\", \"trim\")" "c(\"Abaprim\", \"Alprim\", \"Anitrim\", \"Antrima\", \"Antrimox\", \"Bacdan\", \"Bacidal\", \"Bacide\", \"Bacterial\", \"Bacticel\", \"Bactifor\", \"Bactin\", \"Bactoprim\", \"Bactramin\", \"Bactrim\", \"Bencole\", \"Bethaprim\", \"Biosulten\", \"Briscotrim\", \"Chemotrin\", \"Colizole\", \"Colizole DS\", \"Conprim\", \"Cotrimel\", \"CoTrimoxizole\", \"Deprim\", \"Dosulfin\", \"Duocide\", \"Esbesul\", \"Espectrin\", \"Euctrim\", \"Exbesul\", \"Fermagex\", \"Fortrim\", \"Idotrim\", \"Ikaprim\", \"Instalac\", \"Kombinax\", \"Lagatrim\", \"Lagatrim Forte\", \"Lastrim\", \"Lescot\",
\"Methoprim\", \"Metoprim\", \"Monoprim\", \"Monotrim\", \"Monotrimin\", \"Novotrimel\", \"Omstat\", \"Oraprim\", \"Pancidim\", \"Polytrim\", \"Priloprim\", \"Primosept\", \"Primsol\", \"Proloprim\", \"Protrin\", \"Purbal\", \"Resprim\", \"Resprim Forte\", \"Roubac\", \"Roubal\", \"Salvatrim\", \"Septrin DS\", \"Septrin Forte\", \"Septrin S\", \"Setprin\", \"Sinotrim\", \"Stopan\", \"Streptoplus\", \"Sugaprim\", \"Sulfamar\", \"Sulfamethoprim\", \"Sulfoxaprim\", \"Sulthrim\", \"Sultrex\", \"Syraprim\", \"Tiempe\", \"Tmp Smx\", \"Toprim\", \"Trimanyl\", \"Trimethioprim\", \"Trimethopim\", \"Methoprim\", \"Metoprim\", \"Monoprim\", \"Monotrim\", \"Monotrimin\", \"Novotrimel\", \"Omstat\", \"Oraprim\", \"Pancidim\", \"Polytrim\", \"Priloprim\", \"Primosept\", \"Primsol\", \"Proloprim\", \"Protrin\", \"Purbal\", \"Resprim\", \"Resprim Forte\", \"Roubac\", \"Roubal\", \"Salvatrim\", \"Septrin DS\", \"Septrin Forte\", \"Septrin S\", \"Setprin\", \"Sinotrim\", \"Stopan\", \"Streptoplus\", \"Sugaprim\", \"Sulfamar\", \"Sulfamethoprim\", \"Sulfoxaprim\", \"Sulthrim\", \"Sultrex\", \"Syraprim\", \"Tiempe\", \"Tmp Smx\", \"Toprim\", \"Trimanyl\", \"Trimethioprim\", \"Trimethopim\",
\"Trimethoprim\", \"TRIMETHOPRIM\", \"Trimethoprime\", \"Trimethoprimum\", \"Trimethopriom\", \"Trimetoprim\", \"Trimetoprima\", \"Trimexazole\", \"Trimexol\", \"Trimezol\", \"Trimogal\", \"Trimono\", \"Trimopan\", \"Trimpex\", \"Triprim\", \"Trisul\", \"Trisulcom\", \"Trisulfam\", \"Trisural\", \"Uretrim\", \"Urobactrim\", \"Utetrin\", \"Velaten\", \"Wellcoprim\", \"Wellcoprin\", \"Xeroprim\", \"Zamboprim\")" 0.4 "g" 0.4 "g" "c(\"11005-6\", \"17747-7\", \"25273-4\", \"32342-8\", \"4079-0\", \"4080-8\", \"4081-6\", \"55584-7\", \"80552-3\", \"80973-1\")" \"Trimethoprim\", \"TRIMETHOPRIM\", \"Trimethoprime\", \"Trimethoprimum\", \"Trimethopriom\", \"Trimetoprim\", \"Trimetoprima\", \"Trimexazole\", \"Trimexol\", \"Trimezol\", \"Trimogal\", \"Trimono\", \"Trimopan\", \"Trimpex\", \"Triprim\", \"Trisul\", \"Trisulcom\", \"Trisulfam\", \"Trisural\", \"Uretrim\", \"Urobactrim\", \"Utetrin\", \"Velaten\", \"Wellcoprim\", \"Wellcoprin\", \"Xeroprim\", \"Zamboprim\")" 0.4 "g" 0.4 "g" "c(\"11005-6\", \"17747-7\", \"25273-4\", \"32342-8\", \"4079-0\", \"4080-8\", \"4081-6\", \"55584-7\", \"80552-3\", \"80973-1\")"
"SXT" "J01EE01" 358641 "Trimethoprim/sulfamethoxazole" "Trimethoprims" "Sulfonamides and trimethoprim" "Combinations of sulfonamides and trimethoprim, incl. derivatives" "c(\"t/s\", \"sxt\", \"ts\", \"cot\", \"trsu\")" "c(\"Bactrim\", \"Bactrimel\", \"Belcomycine\", \"Colimycin\", \"Colimycin sulphate\", \"Colisticin\", \"Colistimethate\", \"Colistimethate Sodium\", \"Colistin sulfate\", \"Colistin sulphate\", \"Colomycin\", \"Coly-Mycin\", \"Cotrimazole\", \"Cotrimoxazole\", \"Polymyxin E\", \"Polymyxin E. Sulfate\", \"Promixin\", \"Septra\", \"Totazina\")" "SXT" "J01EE01" 358641 "Trimethoprim/sulfamethoxazole" "Trimethoprims" "Sulfonamides and trimethoprim" "Combinations of sulfonamides and trimethoprim, incl. derivatives" "c(\"t/s\", \"sxt\", \"ts\", \"cot\", \"trsu\", \"trsx\")" "c(\"Bactrim\", \"Bactrimel\", \"Belcomycine\", \"Colimycin\", \"Colimycin sulphate\", \"Colisticin\", \"Colistimethate\", \"Colistimethate Sodium\", \"Colistin sulfate\", \"Colistin sulphate\", \"Colomycin\", \"Coly-Mycin\", \"Cotrimazole\", \"Cotrimoxazole\", \"Polymyxin E\", \"Polymyxin E. Sulfate\", \"Promixin\", \"Septra\", \"Totazina\")"
"TRL" "J01FA08" 202225 "Troleandomycin" "Macrolides/lincosamides" "Macrolides, lincosamides and streptogramins" "Macrolides" "c(\"ACETYLOLEANDOMYCIN\", \"Aovine\", \"Cyclamycin\", \"Evramicina\", \"Matromicina\", \"Matromycin T\", \"Oleandocetine\", \"T.A.O.\", \"Treolmicina\", \"Tribiocillina\", \"Triocetin\", \"Triolan\", \"Troleandomicina\", \"Troleandomycin\", \"Troleandomycine\", \"Troleandomycinum\", \"Viamicina\", \"Wytrion\")" 1 "g" "TRL" "J01FA08" 202225 "Troleandomycin" "Macrolides/lincosamides" "Macrolides, lincosamides and streptogramins" "Macrolides" "c(\"ACETYLOLEANDOMYCIN\", \"Aovine\", \"Cyclamycin\", \"Evramicina\", \"Matromicina\", \"Matromycin T\", \"Oleandocetine\", \"T.A.O.\", \"Treolmicina\", \"Tribiocillina\", \"Triocetin\", \"Triolan\", \"Troleandomicina\", \"Troleandomycin\", \"Troleandomycine\", \"Troleandomycinum\", \"Viamicina\", \"Wytrion\")" 1 "g"
"TRO" 55886 "Trospectomycin" "Other antibacterials" "c(\"Trospectinomycin\", \"Trospectomicina\", \"Trospectomycin\", \"Trospectomycine\", \"Trospectomycinum\")" "TRO" 55886 "Trospectomycin" "Other antibacterials" "c(\"Trospectinomycin\", \"Trospectomicina\", \"Trospectomycin\", \"Trospectomycine\", \"Trospectomycinum\")"
"TVA" "J01MA13" 62959 "Trovafloxacin" "Quinolones" "Quinolone antibacterials" "Fluoroquinolones" "c(\"Trovafloxacin\", \"Trovan\")" 0.2 "g" 0.2 "g" "TVA" "J01MA13" 62959 "Trovafloxacin" "Quinolones" "Quinolone antibacterials" "Fluoroquinolones" "c(\"Trovafloxacin\", \"Trovan\")" 0.2 "g" 0.2 "g"

View File

@@ -83,9 +83,23 @@ read_EUCAST <- function(sheet, file = "data-raw/v_10.0_Breakpoint_Tables.xlsx")
x x
} }
MICs_with_trailing_superscript <- c(0.0011:0.0019, 11:19, 21:29, 0.51:0.59, 41:49, MICs_with_trailing_superscript <- c(seq(from = 0.0011, to = 0.0019, by = 0.0001),
81:89, 0.031:0.039, 0.061:0.069, 0.251:0.259, seq(from = 0.031, to = 0.039, by = 0.001),
0.1251:0.1259, 161:169, 321:329) seq(from = 0.061, to = 0.069, by = 0.001),
seq(from = 0.1251, to = 0.1259, by = 0.0001),
seq(from = 0.251, to = 0.259, by = 0.001),
seq(from = 0.51, to = 0.59, by = 0.01),
seq(from = 11, to = 19, by = 1),
seq(from = 161, to = 169, by = 01),
seq(from = 21, to = 29, by = 1),
seq(from = 321, to = 329, by = 1),
seq(from = 41, to = 49, by = 1),
seq(from = 81, to = 89, by = 1))
has_superscript <- function(x) {
# because due to floating point error 0.1252 is not in:
# seq(from = 0.1251, to = 0.1259, by = 0.0001)
sapply(x, function(x) any(near(x, MICs_with_trailing_superscript)))
}
has_zone_diameters <- rep(any(unlist(raw_data) %like% "zone diameter"), nrow(raw_data)) has_zone_diameters <- rep(any(unlist(raw_data) %like% "zone diameter"), nrow(raw_data))
@@ -101,7 +115,8 @@ read_EUCAST <- function(sheet, file = "data-raw/v_10.0_Breakpoint_Tables.xlsx")
filter(!is.na(drug), filter(!is.na(drug),
!(is.na(MIC_S) & is.na(MIC_R) & is.na(disk_S) & is.na(disk_R)), !(is.na(MIC_S) & is.na(MIC_R) & is.na(disk_S) & is.na(disk_R)),
!MIC_S %like% "(MIC|S ≤|note)", !MIC_S %like% "(MIC|S ≤|note)",
drug != MIC_S) %>% !MIC_S %like% "^[-]",
drug != MIC_S,) %>%
mutate(administration = case_when(drug %like% "[( ]oral" ~ "oral", mutate(administration = case_when(drug %like% "[( ]oral" ~ "oral",
drug %like% "[( ]iv" ~ "iv", drug %like% "[( ]iv" ~ "iv",
TRUE ~ NA_character_), TRUE ~ NA_character_),
@@ -120,12 +135,15 @@ read_EUCAST <- function(sheet, file = "data-raw/v_10.0_Breakpoint_Tables.xlsx")
disk_S = clean_integer(disk_S), disk_S = clean_integer(disk_S),
disk_R = clean_integer(disk_R), disk_R = clean_integer(disk_R),
# invalid MIC values have a superscript text, delete those # invalid MIC values have a superscript text, delete those
MIC_S = ifelse(MIC_S %in% MICs_with_trailing_superscript, MIC_S = ifelse(has_superscript(MIC_S),
substr(MIC_S, 1, nchar(MIC_S) - 1), substr(MIC_S, 1, nchar(MIC_S) - 1),
MIC_S), MIC_S),
MIC_R = ifelse(MIC_R %in% MICs_with_trailing_superscript, MIC_R = ifelse(has_superscript(MIC_R),
substr(MIC_R, 1, nchar(MIC_R) - 1), substr(MIC_R, 1, nchar(MIC_R) - 1),
MIC_R) MIC_R),
# and some are just awful
MIC_S = ifelse(MIC_S == 43.4, 4, MIC_S),
MIC_R = ifelse(MIC_R == 43.4, 4, MIC_R),
) %>% ) %>%
# clean drug names # clean drug names
mutate(drug = gsub(" ?[(, ].*$", "", drug), mutate(drug = gsub(" ?[(, ].*$", "", drug),

View File

@@ -317,6 +317,13 @@ antibiotics <- filter(antibiotics, ab != "PME")
antibiotics[which(antibiotics$ab == "PVM1"), "ab"] <- "PME" antibiotics[which(antibiotics$ab == "PVM1"), "ab"] <- "PME"
# Remove Sinecatechins # Remove Sinecatechins
antibiotics <- filter(antibiotics, ab != "SNC") antibiotics <- filter(antibiotics, ab != "SNC")
# GLIMS codes
antibiotics[which(antibiotics$ab == as.ab("cefuroxim")), "abbreviations"][[1]] <- list(c(antibiotics[which(antibiotics$ab == as.ab("cefuroxim")), "abbreviations"][[1]], "cfrx"))
antibiotics[which(antibiotics$ab == as.ab("cefotaxim")), "abbreviations"][[1]] <- list(c(antibiotics[which(antibiotics$ab == as.ab("cefotaxim")), "abbreviations"][[1]], "cftx"))
antibiotics[which(antibiotics$ab == as.ab("ceftazidime")), "abbreviations"][[1]] <- list(c(antibiotics[which(antibiotics$ab == as.ab("ceftazidime")), "abbreviations"][[1]], "cftz"))
antibiotics[which(antibiotics$ab == as.ab("cefepime")), "abbreviations"][[1]] <- list(c(antibiotics[which(antibiotics$ab == as.ab("cefepime")), "abbreviations"][[1]], "cfpi"))
antibiotics[which(antibiotics$ab == as.ab("cefoxitin")), "abbreviations"][[1]] <- list(c(antibiotics[which(antibiotics$ab == as.ab("cefoxitin")), "abbreviations"][[1]], "cfxt"))
antibiotics[which(antibiotics$ab == as.ab("cotrimoxazol")), "abbreviations"][[1]] <- list(c(antibiotics[which(antibiotics$ab == as.ab("cotrimoxazol")), "abbreviations"][[1]], "trsx"))
# ESBL E-test codes: # ESBL E-test codes:
antibiotics[which(antibiotics$ab == "CCV"), "abbreviations"][[1]] <- list(c("xtzl")) 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")) antibiotics[which(antibiotics$ab == "CAZ"), "abbreviations"][[1]] <- list(c(antibiotics[which(antibiotics$ab == "CAZ"), "abbreviations"][[1]], "xtz", "cefta"))

View File

@@ -21,7 +21,9 @@ rsi_translation <- DRGLST1 %>%
R_disk = as.disk(DISK_R), R_disk = as.disk(DISK_R),
S_mic = as.mic(MIC_S), S_mic = as.mic(MIC_S),
R_mic = as.mic(MIC_R)) %>% R_mic = as.mic(MIC_R)) %>%
filter(!is.na(mo) & !is.na(ab) & !mo %in% c("UNKNOWN", "B_GRAMN", "B_GRAMP", "F_FUNGUS", "F_YEAST")) %>% filter(!is.na(mo),
!is.na(ab),
!mo %in% c("UNKNOWN", "B_GRAMN", "B_GRAMP", "F_FUNGUS", "F_YEAST")) %>%
arrange(desc(guideline), mo, ab) arrange(desc(guideline), mo, ab)
print(mo_failures()) print(mo_failures())

View File

@@ -19,7 +19,7 @@
"EUCAST 2020" "DISK" "iv" "Haemophilus influenzae" "Amoxicillin/clavulanic acid" "H.influenzae" "2-1ug" 15 15 FALSE "EUCAST 2020" "DISK" "iv" "Haemophilus influenzae" "Amoxicillin/clavulanic acid" "H.influenzae" "2-1ug" 15 15 FALSE
"EUCAST 2020" "DISK" "oral" "Haemophilus influenzae" "Amoxicillin/clavulanic acid" "H.influenzae" "2-1ug" 50 15 FALSE "EUCAST 2020" "DISK" "oral" "Haemophilus influenzae" "Amoxicillin/clavulanic acid" "H.influenzae" "2-1ug" 50 15 FALSE
"EUCAST 2020" "MIC" "iv" "Haemophilus influenzae" "Amoxicillin/clavulanic acid" "H.influenzae" 2 2 FALSE "EUCAST 2020" "MIC" "iv" "Haemophilus influenzae" "Amoxicillin/clavulanic acid" "H.influenzae" 2 2 FALSE
"EUCAST 2020" "MIC" "oral" "Haemophilus influenzae" "Amoxicillin/clavulanic acid" "H.influenzae" 0.0015 2 FALSE "EUCAST 2020" "MIC" "oral" "Haemophilus influenzae" "Amoxicillin/clavulanic acid" "H.influenzae" 0.001 2 FALSE
"EUCAST 2020" "MIC" "Lactobacillus" "Amoxicillin/clavulanic acid" "Anaerobes, Grampositive" 4 8 FALSE "EUCAST 2020" "MIC" "Lactobacillus" "Amoxicillin/clavulanic acid" "Anaerobes, Grampositive" 4 8 FALSE
"EUCAST 2020" "MIC" "Mobiluncus" "Amoxicillin/clavulanic acid" "Anaerobes, Gramnegative" 4 8 FALSE "EUCAST 2020" "MIC" "Mobiluncus" "Amoxicillin/clavulanic acid" "Anaerobes, Gramnegative" 4 8 FALSE
"EUCAST 2020" "DISK" "Moraxella catarrhalis" "Amoxicillin/clavulanic acid" "M.catarrhalis" "2-1ug" 19 19 FALSE "EUCAST 2020" "DISK" "Moraxella catarrhalis" "Amoxicillin/clavulanic acid" "M.catarrhalis" "2-1ug" 19 19 FALSE
@@ -70,12 +70,11 @@
"EUCAST 2020" "MIC" "Fusobacterium" "Ampicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE "EUCAST 2020" "MIC" "Fusobacterium" "Ampicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE
"EUCAST 2020" "DISK" "Haemophilus influenzae" "Ampicillin" "H.influenzae" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Haemophilus influenzae" "Ampicillin" "H.influenzae" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Haemophilus influenzae" "Ampicillin" "H.influenzae" 1 1 FALSE "EUCAST 2020" "MIC" "Haemophilus influenzae" "Ampicillin" "H.influenzae" 1 1 FALSE
"EUCAST 2020" "MIC" "Kingella kingae" "Ampicillin" "K.kingae" 0.062 0.062 FALSE "EUCAST 2020" "MIC" "Kingella kingae" "Ampicillin" "K.kingae" 0.06 0.06 FALSE
"EUCAST 2020" "MIC" "Lactobacillus" "Ampicillin" "Anaerobes, Grampositive" 4 8 FALSE "EUCAST 2020" "MIC" "Lactobacillus" "Ampicillin" "Anaerobes, Grampositive" 4 8 FALSE
"EUCAST 2020" "DISK" "iv" "Listeria monocytogenes" "Ampicillin" "L.monocytogenes" "2ug" 16 16 FALSE "EUCAST 2020" "DISK" "iv" "Listeria monocytogenes" "Ampicillin" "L.monocytogenes" "2ug" 16 16 FALSE
"EUCAST 2020" "MIC" "iv" "Listeria monocytogenes" "Ampicillin" "L.monocytogenes" 1 1 FALSE "EUCAST 2020" "MIC" "iv" "Listeria monocytogenes" "Ampicillin" "L.monocytogenes" 1 1 FALSE
"EUCAST 2020" "MIC" "Mobiluncus" "Ampicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE "EUCAST 2020" "MIC" "Mobiluncus" "Ampicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE
"EUCAST 2020" "MIC" "Moraxella catarrhalis" "Ampicillin" "M.catarrhalis" -1 -1 FALSE
"EUCAST 2020" "MIC" "Neisseria meningitidis" "Ampicillin" "N.meningitidis" 0.125 1 FALSE "EUCAST 2020" "MIC" "Neisseria meningitidis" "Ampicillin" "N.meningitidis" 0.125 1 FALSE
"EUCAST 2020" "MIC" "Parabacteroides" "Ampicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE "EUCAST 2020" "MIC" "Parabacteroides" "Ampicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE
"EUCAST 2020" "MIC" "Porphyromonas" "Ampicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE "EUCAST 2020" "MIC" "Porphyromonas" "Ampicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE
@@ -103,10 +102,9 @@
"EUCAST 2020" "MIC" "oral" "Helicobacter pylori" "Amoxicillin" "H.pylori" 0.125 0.125 FALSE "EUCAST 2020" "MIC" "oral" "Helicobacter pylori" "Amoxicillin" "H.pylori" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "iv" "Haemophilus influenzae" "Amoxicillin" "H.influenzae" 2 2 FALSE "EUCAST 2020" "MIC" "iv" "Haemophilus influenzae" "Amoxicillin" "H.influenzae" 2 2 FALSE
"EUCAST 2020" "MIC" "oral" "Haemophilus influenzae" "Amoxicillin" "H.influenzae" 0.001 2 FALSE "EUCAST 2020" "MIC" "oral" "Haemophilus influenzae" "Amoxicillin" "H.influenzae" 0.001 2 FALSE
"EUCAST 2020" "MIC" "Kingella kingae" "Amoxicillin" "K.kingae" 0.1252 0.1252 FALSE "EUCAST 2020" "MIC" "Kingella kingae" "Amoxicillin" "K.kingae" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Lactobacillus" "Amoxicillin" "Anaerobes, Grampositive" 4 8 FALSE "EUCAST 2020" "MIC" "Lactobacillus" "Amoxicillin" "Anaerobes, Grampositive" 4 8 FALSE
"EUCAST 2020" "MIC" "Mobiluncus" "Amoxicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE "EUCAST 2020" "MIC" "Mobiluncus" "Amoxicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE
"EUCAST 2020" "MIC" "Moraxella catarrhalis" "Amoxicillin" "M.catarrhalis" -1 -1 FALSE
"EUCAST 2020" "MIC" "Neisseria meningitidis" "Amoxicillin" "N.meningitidis" 0.125 1 FALSE "EUCAST 2020" "MIC" "Neisseria meningitidis" "Amoxicillin" "N.meningitidis" 0.125 1 FALSE
"EUCAST 2020" "MIC" "Parabacteroides" "Amoxicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE "EUCAST 2020" "MIC" "Parabacteroides" "Amoxicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE
"EUCAST 2020" "MIC" "Porphyromonas" "Amoxicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE "EUCAST 2020" "MIC" "Porphyromonas" "Amoxicillin" "Anaerobes, Gramnegative" 0.5 2 FALSE
@@ -465,29 +463,29 @@
"EUCAST 2020" "MIC" "Haemophilus influenzae" "Ceftolozane/tazobactam" "H.influenzae" 0.5 0.5 FALSE "EUCAST 2020" "MIC" "Haemophilus influenzae" "Ceftolozane/tazobactam" "H.influenzae" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Pseudomonas aeruginosa" "Ceftolozane/tazobactam" "Pseudomonas" "30-10ug" 24 24 FALSE "EUCAST 2020" "DISK" "Pseudomonas aeruginosa" "Ceftolozane/tazobactam" "Pseudomonas" "30-10ug" 24 24 FALSE
"EUCAST 2020" "MIC" "Pseudomonas aeruginosa" "Ceftolozane/tazobactam" "Pseudomonas" 4 4 FALSE "EUCAST 2020" "MIC" "Pseudomonas aeruginosa" "Ceftolozane/tazobactam" "Pseudomonas" 4 4 FALSE
"EUCAST 2020" "MIC" "(unknown name)" "Ceftolozane/tazobactam" "PK PD breakpoints" 43.4 43.4 FALSE "EUCAST 2020" "MIC" "(unknown name)" "Ceftolozane/tazobactam" "PK PD breakpoints" 4 4 FALSE
"EUCAST 2020" "MIC" "Staphylococcus" "Dalbavancin" "Staphylococcus" 0.125 0.1253 FALSE "EUCAST 2020" "MIC" "Staphylococcus" "Dalbavancin" "Staphylococcus" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus agalactiae" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus agalactiae" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus anginosus" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus anginosus" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus anginosus" "Dalbavancin" "Viridans group streptococci" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus anginosus" "Dalbavancin" "Viridans group streptococci" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus dysgalactiae" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus dysgalactiae" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus dysgalactiae dysgalactiae" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus dysgalactiae dysgalactiae" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus dysgalactiae equisimilis" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus dysgalactiae equisimilis" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus equi" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi equi" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus equi equi" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi ruminatorum" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus equi ruminatorum" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi zooepidemicus" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus equi zooepidemicus" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus group A" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus group A" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus group B" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus group B" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus group C" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus group C" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus group D" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus group D" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus group F" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus group F" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus group G" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus group G" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus group H" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus group H" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus group K" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus group K" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus pyogenes" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus pyogenes" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus salivarius" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus salivarius" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus sanguinis" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.1252 FALSE "EUCAST 2020" "MIC" "Streptococcus sanguinis" "Dalbavancin" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "(unknown name)" "Dalbavancin" "PK PD breakpoints" 0.25 0.25 FALSE "EUCAST 2020" "MIC" "(unknown name)" "Dalbavancin" "PK PD breakpoints" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Staphylococcus" "Daptomycin" "Staphylococcus" 1 1 FALSE "EUCAST 2020" "MIC" "Staphylococcus" "Daptomycin" "Staphylococcus" 1 1 FALSE
"EUCAST 2020" "MIC" "Streptococcus agalactiae" "Daptomycin" "Streptococcus A,B,C,G" 1 1 FALSE "EUCAST 2020" "MIC" "Streptococcus agalactiae" "Daptomycin" "Streptococcus A,B,C,G" 1 1 FALSE
@@ -671,7 +669,6 @@
"EUCAST 2020" "MIC" "iv" "Enterobacterales" "Fosfomycin" "Enterobacterales" 32 32 FALSE "EUCAST 2020" "MIC" "iv" "Enterobacterales" "Fosfomycin" "Enterobacterales" 32 32 FALSE
"EUCAST 2020" "MIC" "UTI" "Enterobacterales" "Fosfomycin" "Enterobacterales" 32 32 TRUE "EUCAST 2020" "MIC" "UTI" "Enterobacterales" "Fosfomycin" "Enterobacterales" 32 32 TRUE
"EUCAST 2020" "MIC" "iv" "Staphylococcus" "Fosfomycin" "Staphylococcus" 32 32 FALSE "EUCAST 2020" "MIC" "iv" "Staphylococcus" "Fosfomycin" "Staphylococcus" 32 32 FALSE
"EUCAST 2020" "MIC" "Clostridium difficile" "Fusidic acid" "C.difficile" -3 -3 FALSE
"EUCAST 2020" "DISK" "Staphylococcus" "Fusidic acid" "Staphylococcus" "10ug" 24 24 FALSE "EUCAST 2020" "DISK" "Staphylococcus" "Fusidic acid" "Staphylococcus" "10ug" 24 24 FALSE
"EUCAST 2020" "MIC" "Staphylococcus" "Fusidic acid" "Staphylococcus" 1 1 FALSE "EUCAST 2020" "MIC" "Staphylococcus" "Fusidic acid" "Staphylococcus" 1 1 FALSE
"EUCAST 2020" "DISK" "Systemic" "Enterobacterales" "Gentamicin" "Enterobacterales" "10ug" 17 17 FALSE "EUCAST 2020" "DISK" "Systemic" "Enterobacterales" "Gentamicin" "Enterobacterales" "10ug" 17 17 FALSE
@@ -928,7 +925,6 @@
"EUCAST 2020" "MIC" "Enterobacterales" "Moxifloxacin" "Enterobacterales" 0.25 0.25 FALSE "EUCAST 2020" "MIC" "Enterobacterales" "Moxifloxacin" "Enterobacterales" 0.25 0.25 FALSE
"EUCAST 2020" "DISK" "Corynebacterium" "Moxifloxacin" "Corynebacterium" "5ug" 25 25 FALSE "EUCAST 2020" "DISK" "Corynebacterium" "Moxifloxacin" "Corynebacterium" "5ug" 25 25 FALSE
"EUCAST 2020" "MIC" "Corynebacterium" "Moxifloxacin" "Corynebacterium" 0.5 0.5 FALSE "EUCAST 2020" "MIC" "Corynebacterium" "Moxifloxacin" "Corynebacterium" 0.5 0.5 FALSE
"EUCAST 2020" "MIC" "Clostridium difficile" "Moxifloxacin" "C.difficile" -1 -1 FALSE
"EUCAST 2020" "DISK" "Haemophilus influenzae" "Moxifloxacin" "H.influenzae" "5ug" 28 28 FALSE "EUCAST 2020" "DISK" "Haemophilus influenzae" "Moxifloxacin" "H.influenzae" "5ug" 28 28 FALSE
"EUCAST 2020" "MIC" "Haemophilus influenzae" "Moxifloxacin" "H.influenzae" 0.125 0.125 FALSE "EUCAST 2020" "MIC" "Haemophilus influenzae" "Moxifloxacin" "H.influenzae" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Moraxella catarrhalis" "Moxifloxacin" "M.catarrhalis" "5ug" 26 26 FALSE "EUCAST 2020" "DISK" "Moraxella catarrhalis" "Moxifloxacin" "M.catarrhalis" "5ug" 26 26 FALSE
@@ -1076,28 +1072,28 @@
"EUCAST 2020" "DISK" "Staphylococcus aureus" "Ofloxacin" "Staphylococcus" "5ug" 50 20 FALSE "EUCAST 2020" "DISK" "Staphylococcus aureus" "Ofloxacin" "Staphylococcus" "5ug" 50 20 FALSE
"EUCAST 2020" "MIC" "Staphylococcus aureus" "Ofloxacin" "Staphylococcus" 0.001 1 FALSE "EUCAST 2020" "MIC" "Staphylococcus aureus" "Ofloxacin" "Staphylococcus" 0.001 1 FALSE
"EUCAST 2020" "MIC" "(unknown name)" "Ofloxacin" "PK PD breakpoints" 0.25 0.5 FALSE "EUCAST 2020" "MIC" "(unknown name)" "Ofloxacin" "PK PD breakpoints" 0.25 0.5 FALSE
"EUCAST 2020" "MIC" "Staphylococcus aureus" "Oritavancin" "Staphylococcus" 0.125 0.1253 FALSE "EUCAST 2020" "MIC" "Staphylococcus aureus" "Oritavancin" "Staphylococcus" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "Streptococcus agalactiae" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus agalactiae" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus anginosus" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus anginosus" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus anginosus" "Oritavancin" "Viridans group streptococci" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus anginosus" "Oritavancin" "Viridans group streptococci" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus dysgalactiae" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus dysgalactiae" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus dysgalactiae dysgalactiae" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus dysgalactiae dysgalactiae" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus dysgalactiae equisimilis" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus dysgalactiae equisimilis" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus equi" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi equi" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus equi equi" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi ruminatorum" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus equi ruminatorum" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi zooepidemicus" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus equi zooepidemicus" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus group A" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus group A" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus group B" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus group B" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus group C" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus group C" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus group D" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus group D" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus group F" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus group F" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus group G" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus group G" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus group H" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus group H" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus group K" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus group K" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus pyogenes" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus pyogenes" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus salivarius" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus salivarius" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Streptococcus sanguinis" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.252 FALSE "EUCAST 2020" "MIC" "Streptococcus sanguinis" "Oritavancin" "Streptococcus A,B,C,G" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "(unknown name)" "Oritavancin" "PK PD breakpoints" 0.125 0.125 FALSE "EUCAST 2020" "MIC" "(unknown name)" "Oritavancin" "PK PD breakpoints" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Aerococcus sanguinicola" "Penicillin G" "A.sanguinicola_A.urinae" "1ug" 21 21 FALSE "EUCAST 2020" "DISK" "Aerococcus sanguinicola" "Penicillin G" "A.sanguinicola_A.urinae" "1ug" 21 21 FALSE
"EUCAST 2020" "MIC" "Aerococcus sanguinicola" "Penicillin G" "A.sanguinicola_A.urinae" 0.125 0.125 FALSE "EUCAST 2020" "MIC" "Aerococcus sanguinicola" "Penicillin G" "A.sanguinicola_A.urinae" 0.125 0.125 FALSE
@@ -1192,7 +1188,6 @@
"EUCAST 2020" "MIC" "Fusobacterium" "Piperacillin" "Anaerobes, Gramnegative" 1 1 FALSE "EUCAST 2020" "MIC" "Fusobacterium" "Piperacillin" "Anaerobes, Gramnegative" 1 1 FALSE
"EUCAST 2020" "MIC" "Lactobacillus" "Piperacillin" "Anaerobes, Grampositive" 8 1 FALSE "EUCAST 2020" "MIC" "Lactobacillus" "Piperacillin" "Anaerobes, Grampositive" 8 1 FALSE
"EUCAST 2020" "MIC" "Mobiluncus" "Piperacillin" "Anaerobes, Gramnegative" 1 1 FALSE "EUCAST 2020" "MIC" "Mobiluncus" "Piperacillin" "Anaerobes, Gramnegative" 1 1 FALSE
"EUCAST 2020" "MIC" "Moraxella catarrhalis" "Piperacillin" "M.catarrhalis" -1 -1 FALSE
"EUCAST 2020" "MIC" "Parabacteroides" "Piperacillin" "Anaerobes, Gramnegative" 1 1 FALSE "EUCAST 2020" "MIC" "Parabacteroides" "Piperacillin" "Anaerobes, Gramnegative" 1 1 FALSE
"EUCAST 2020" "MIC" "Porphyromonas" "Piperacillin" "Anaerobes, Gramnegative" 1 1 FALSE "EUCAST 2020" "MIC" "Porphyromonas" "Piperacillin" "Anaerobes, Gramnegative" 1 1 FALSE
"EUCAST 2020" "MIC" "Propionibacterium" "Piperacillin" "Anaerobes, Grampositive" 8 1 FALSE "EUCAST 2020" "MIC" "Propionibacterium" "Piperacillin" "Anaerobes, Grampositive" 8 1 FALSE
@@ -1211,7 +1206,6 @@
"EUCAST 2020" "MIC" "Aerococcus urinae" "Rifampicin" "A.sanguinicola_A.urinae" 0.125 0.125 FALSE "EUCAST 2020" "MIC" "Aerococcus urinae" "Rifampicin" "A.sanguinicola_A.urinae" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Corynebacterium" "Rifampicin" "Corynebacterium" "5ug" 30 25 FALSE "EUCAST 2020" "DISK" "Corynebacterium" "Rifampicin" "Corynebacterium" "5ug" 30 25 FALSE
"EUCAST 2020" "MIC" "Corynebacterium" "Rifampicin" "Corynebacterium" 0.06 0.5 FALSE "EUCAST 2020" "MIC" "Corynebacterium" "Rifampicin" "Corynebacterium" 0.06 0.5 FALSE
"EUCAST 2020" "MIC" "Clostridium difficile" "Rifampicin" "C.difficile" -6 -6 FALSE
"EUCAST 2020" "MIC" "Helicobacter pylori" "Rifampicin" "H.pylori" 1 1 FALSE "EUCAST 2020" "MIC" "Helicobacter pylori" "Rifampicin" "H.pylori" 1 1 FALSE
"EUCAST 2020" "DISK" "Haemophilus influenzae" "Rifampicin" "H.influenzae" "5ug" 18 18 FALSE "EUCAST 2020" "DISK" "Haemophilus influenzae" "Rifampicin" "H.influenzae" "5ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Haemophilus influenzae" "Rifampicin" "H.influenzae" 1 1 FALSE "EUCAST 2020" "MIC" "Haemophilus influenzae" "Rifampicin" "H.influenzae" 1 1 FALSE
@@ -1392,7 +1386,7 @@
"EUCAST 2020" "MIC" "Propionibacterium" "Ticarcillin/clavulanic acid" "Anaerobes, Grampositive" 8 16 FALSE "EUCAST 2020" "MIC" "Propionibacterium" "Ticarcillin/clavulanic acid" "Anaerobes, Grampositive" 8 16 FALSE
"EUCAST 2020" "MIC" "Prevotella" "Ticarcillin/clavulanic acid" "Anaerobes, Gramnegative" 8 16 FALSE "EUCAST 2020" "MIC" "Prevotella" "Ticarcillin/clavulanic acid" "Anaerobes, Gramnegative" 8 16 FALSE
"EUCAST 2020" "DISK" "Pseudomonas" "Ticarcillin/clavulanic acid" "Pseudomonas" "75-10ug" 50 18 FALSE "EUCAST 2020" "DISK" "Pseudomonas" "Ticarcillin/clavulanic acid" "Pseudomonas" "75-10ug" 50 18 FALSE
"EUCAST 2020" "MIC" "Pseudomonas" "Ticarcillin/clavulanic acid" "Pseudomonas" 0.0012 16 FALSE "EUCAST 2020" "MIC" "Pseudomonas" "Ticarcillin/clavulanic acid" "Pseudomonas" 0.001 16 FALSE
"EUCAST 2020" "MIC" "Staphylococcus saccharolyticus" "Ticarcillin/clavulanic acid" "Anaerobes, Grampositive" 8 16 FALSE "EUCAST 2020" "MIC" "Staphylococcus saccharolyticus" "Ticarcillin/clavulanic acid" "Anaerobes, Grampositive" 8 16 FALSE
"EUCAST 2020" "MIC" "(unknown name)" "Ticarcillin/clavulanic acid" "PK PD breakpoints" 8 16 FALSE "EUCAST 2020" "MIC" "(unknown name)" "Ticarcillin/clavulanic acid" "PK PD breakpoints" 8 16 FALSE
"EUCAST 2020" "DISK" "Campylobacter coli" "Tetracycline" "C.jejuni_C.coli" "30ug" 30 30 FALSE "EUCAST 2020" "DISK" "Campylobacter coli" "Tetracycline" "C.jejuni_C.coli" "30ug" 30 30 FALSE
@@ -1505,53 +1499,53 @@
"EUCAST 2020" "DISK" "Citrobacter koseri" "Tigecycline" "Enterobacterales" "15ug" 18 18 FALSE "EUCAST 2020" "DISK" "Citrobacter koseri" "Tigecycline" "Enterobacterales" "15ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Citrobacter koseri" "Tigecycline" "Enterobacterales" 0.5 0.5 FALSE "EUCAST 2020" "MIC" "Citrobacter koseri" "Tigecycline" "Enterobacterales" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Enterococcus faecium" "Tigecycline" "Enterococcus" "15ug" 22 22 FALSE "EUCAST 2020" "DISK" "Enterococcus faecium" "Tigecycline" "Enterococcus" "15ug" 22 22 FALSE
"EUCAST 2020" "MIC" "Enterococcus faecium" "Tigecycline" "Enterococcus" 0.252 0.252 FALSE "EUCAST 2020" "MIC" "Enterococcus faecium" "Tigecycline" "Enterococcus" 0.25 0.25 FALSE
"EUCAST 2020" "DISK" "Enterococcus faecalis" "Tigecycline" "Enterococcus" "15ug" 20 20 FALSE "EUCAST 2020" "DISK" "Enterococcus faecalis" "Tigecycline" "Enterococcus" "15ug" 20 20 FALSE
"EUCAST 2020" "MIC" "Enterococcus faecalis" "Tigecycline" "Enterococcus" 0.252 0.252 FALSE "EUCAST 2020" "MIC" "Enterococcus faecalis" "Tigecycline" "Enterococcus" 0.25 0.25 FALSE
"EUCAST 2020" "DISK" "Escherichia coli" "Tigecycline" "Enterobacterales" "15ug" 18 18 FALSE "EUCAST 2020" "DISK" "Escherichia coli" "Tigecycline" "Enterobacterales" "15ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Escherichia coli" "Tigecycline" "Enterobacterales" 0.5 0.5 FALSE "EUCAST 2020" "MIC" "Escherichia coli" "Tigecycline" "Enterobacterales" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Staphylococcus" "Tigecycline" "Staphylococcus" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Staphylococcus" "Tigecycline" "Staphylococcus" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Staphylococcus" "Tigecycline" "Staphylococcus" 0.53 0.53 FALSE "EUCAST 2020" "MIC" "Staphylococcus" "Tigecycline" "Staphylococcus" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus agalactiae" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus agalactiae" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus agalactiae" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus agalactiae" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus anginosus" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus anginosus" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus anginosus" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus anginosus" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus dysgalactiae" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus dysgalactiae" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus dysgalactiae" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus dysgalactiae" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus dysgalactiae dysgalactiae" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus dysgalactiae dysgalactiae" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus dysgalactiae dysgalactiae" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus dysgalactiae dysgalactiae" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus dysgalactiae equisimilis" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus dysgalactiae equisimilis" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus dysgalactiae equisimilis" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus dysgalactiae equisimilis" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus equi" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus equi" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus equi" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus equi equi" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus equi equi" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi equi" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus equi equi" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus equi ruminatorum" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus equi ruminatorum" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi ruminatorum" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus equi ruminatorum" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus equi zooepidemicus" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus equi zooepidemicus" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi zooepidemicus" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus equi zooepidemicus" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus group A" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus group A" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus group A" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus group A" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus group B" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus group B" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus group B" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus group B" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus group C" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus group C" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus group C" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus group C" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus group D" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus group D" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus group D" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus group D" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus group F" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus group F" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus group F" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus group F" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus group G" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus group G" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus group G" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus group G" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus group H" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus group H" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus group H" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus group H" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus group K" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus group K" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus group K" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus group K" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus pyogenes" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus pyogenes" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus pyogenes" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus pyogenes" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus salivarius" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus salivarius" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus salivarius" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus salivarius" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "Streptococcus sanguinis" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE "EUCAST 2020" "DISK" "Streptococcus sanguinis" "Tigecycline" "Streptococcus A,B,C,G" "15ug" 19 19 FALSE
"EUCAST 2020" "MIC" "Streptococcus sanguinis" "Tigecycline" "Streptococcus A,B,C,G" 0.1253 0.1253 FALSE "EUCAST 2020" "MIC" "Streptococcus sanguinis" "Tigecycline" "Streptococcus A,B,C,G" 0.125 0.125 FALSE
"EUCAST 2020" "MIC" "(unknown name)" "Tigecycline" "PK PD breakpoints" 0.5 0.5 FALSE "EUCAST 2020" "MIC" "(unknown name)" "Tigecycline" "PK PD breakpoints" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Enterobacterales" "Ticarcillin" "Enterobacterales" "75ug" 23 20 FALSE "EUCAST 2020" "DISK" "Enterobacterales" "Ticarcillin" "Enterobacterales" "75ug" 23 20 FALSE
"EUCAST 2020" "MIC" "Enterobacterales" "Ticarcillin" "Enterobacterales" 8 1 FALSE "EUCAST 2020" "MIC" "Enterobacterales" "Ticarcillin" "Enterobacterales" 8 1 FALSE
@@ -1619,7 +1613,7 @@
"EUCAST 2020" "MIC" "Streptococcus salivarius" "Telithromycin" "Streptococcus A,B,C,G" 0.25 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus salivarius" "Telithromycin" "Streptococcus A,B,C,G" 0.25 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus sanguinis" "Telithromycin" "Streptococcus A,B,C,G" "15ug" 20 17 FALSE "EUCAST 2020" "DISK" "Streptococcus sanguinis" "Telithromycin" "Streptococcus A,B,C,G" "15ug" 20 17 FALSE
"EUCAST 2020" "MIC" "Streptococcus sanguinis" "Telithromycin" "Streptococcus A,B,C,G" 0.25 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus sanguinis" "Telithromycin" "Streptococcus A,B,C,G" 0.25 0.5 FALSE
"EUCAST 2020" "MIC" "Staphylococcus" "Telavancin" "Staphylococcus" 0.125 0.1253 FALSE "EUCAST 2020" "MIC" "Staphylococcus" "Telavancin" "Staphylococcus" 0.125 0.125 FALSE
"EUCAST 2020" "DISK" "UTI" "Enterobacterales" "Trimethoprim" "Enterobacterales" "5ug" 15 15 TRUE "EUCAST 2020" "DISK" "UTI" "Enterobacterales" "Trimethoprim" "Enterobacterales" "5ug" 15 15 TRUE
"EUCAST 2020" "MIC" "UTI" "Enterobacterales" "Trimethoprim" "Enterobacterales" 4 4 TRUE "EUCAST 2020" "MIC" "UTI" "Enterobacterales" "Trimethoprim" "Enterobacterales" 4 4 TRUE
"EUCAST 2020" "DISK" "UTI" "Staphylococcus" "Trimethoprim" "Staphylococcus" "5ug" 14 14 TRUE "EUCAST 2020" "DISK" "UTI" "Staphylococcus" "Trimethoprim" "Staphylococcus" "5ug" 14 14 TRUE
@@ -1645,47 +1639,47 @@
"EUCAST 2020" "DISK" "Staphylococcus" "Tedizolid" "Staphylococcus" "2ug" 21 21 FALSE "EUCAST 2020" "DISK" "Staphylococcus" "Tedizolid" "Staphylococcus" "2ug" 21 21 FALSE
"EUCAST 2020" "MIC" "Staphylococcus" "Tedizolid" "Staphylococcus" 0.5 0.5 FALSE "EUCAST 2020" "MIC" "Staphylococcus" "Tedizolid" "Staphylococcus" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus agalactiae" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus agalactiae" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus agalactiae" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus agalactiae" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus anginosus" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus anginosus" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "DISK" "Streptococcus anginosus" "Tedizolid" "Viridans group streptococci" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus anginosus" "Tedizolid" "Viridans group streptococci" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus anginosus" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus anginosus" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "MIC" "Streptococcus anginosus" "Tedizolid" "Viridans group streptococci" 0.25 0.25 FALSE "EUCAST 2020" "MIC" "Streptococcus anginosus" "Tedizolid" "Viridans group streptococci" 0.25 0.25 FALSE
"EUCAST 2020" "DISK" "Streptococcus dysgalactiae" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus dysgalactiae" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus dysgalactiae" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus dysgalactiae" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus dysgalactiae dysgalactiae" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus dysgalactiae dysgalactiae" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus dysgalactiae dysgalactiae" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus dysgalactiae dysgalactiae" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus dysgalactiae equisimilis" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus dysgalactiae equisimilis" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus dysgalactiae equisimilis" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus dysgalactiae equisimilis" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus equi" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus equi" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus equi" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus equi equi" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus equi equi" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi equi" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus equi equi" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus equi ruminatorum" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus equi ruminatorum" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi ruminatorum" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus equi ruminatorum" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus equi zooepidemicus" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus equi zooepidemicus" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus equi zooepidemicus" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus equi zooepidemicus" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus group A" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus group A" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus group A" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus group A" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus group B" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus group B" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus group B" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus group B" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus group C" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus group C" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus group C" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus group C" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus group D" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus group D" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus group D" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus group D" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus group F" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus group F" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus group F" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus group F" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus group G" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus group G" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus group G" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus group G" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus group H" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus group H" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus group H" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus group H" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus group K" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus group K" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus group K" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus group K" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus pyogenes" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus pyogenes" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus pyogenes" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus pyogenes" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus salivarius" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus salivarius" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus salivarius" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus salivarius" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Streptococcus sanguinis" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE "EUCAST 2020" "DISK" "Streptococcus sanguinis" "Tedizolid" "Streptococcus A,B,C,G" "2ug" 18 18 FALSE
"EUCAST 2020" "MIC" "Streptococcus sanguinis" "Tedizolid" "Streptococcus A,B,C,G" 0.52 0.5 FALSE "EUCAST 2020" "MIC" "Streptococcus sanguinis" "Tedizolid" "Streptococcus A,B,C,G" 0.5 0.5 FALSE
"EUCAST 2020" "DISK" "Enterobacterales" "Piperacillin/tazobactam" "Enterobacterales" "30-6ug" 20 17 FALSE "EUCAST 2020" "DISK" "Enterobacterales" "Piperacillin/tazobactam" "Enterobacterales" "30-6ug" 20 17 FALSE
"EUCAST 2020" "MIC" "Enterobacterales" "Piperacillin/tazobactam" "Enterobacterales" 8 16 FALSE "EUCAST 2020" "MIC" "Enterobacterales" "Piperacillin/tazobactam" "Enterobacterales" 8 16 FALSE
"EUCAST 2020" "MIC" "Actinomyces" "Piperacillin/tazobactam" "Anaerobes, Grampositive" 8 16 FALSE "EUCAST 2020" "MIC" "Actinomyces" "Piperacillin/tazobactam" "Anaerobes, Grampositive" 8 16 FALSE
@@ -1699,7 +1693,7 @@
"EUCAST 2020" "MIC" "Eggerthella" "Piperacillin/tazobactam" "Anaerobes, Grampositive" 8 16 FALSE "EUCAST 2020" "MIC" "Eggerthella" "Piperacillin/tazobactam" "Anaerobes, Grampositive" 8 16 FALSE
"EUCAST 2020" "MIC" "Fusobacterium" "Piperacillin/tazobactam" "Anaerobes, Gramnegative" 8 16 FALSE "EUCAST 2020" "MIC" "Fusobacterium" "Piperacillin/tazobactam" "Anaerobes, Gramnegative" 8 16 FALSE
"EUCAST 2020" "DISK" "Haemophilus influenzae" "Piperacillin/tazobactam" "H.influenzae" "30-6ug" 27 27 FALSE "EUCAST 2020" "DISK" "Haemophilus influenzae" "Piperacillin/tazobactam" "H.influenzae" "30-6ug" 27 27 FALSE
"EUCAST 2020" "MIC" "Haemophilus influenzae" "Piperacillin/tazobactam" "H.influenzae" 0.256 0.256 FALSE "EUCAST 2020" "MIC" "Haemophilus influenzae" "Piperacillin/tazobactam" "H.influenzae" 0.25 0.25 FALSE
"EUCAST 2020" "MIC" "Lactobacillus" "Piperacillin/tazobactam" "Anaerobes, Grampositive" 8 16 FALSE "EUCAST 2020" "MIC" "Lactobacillus" "Piperacillin/tazobactam" "Anaerobes, Grampositive" 8 16 FALSE
"EUCAST 2020" "MIC" "Mobiluncus" "Piperacillin/tazobactam" "Anaerobes, Gramnegative" 8 16 FALSE "EUCAST 2020" "MIC" "Mobiluncus" "Piperacillin/tazobactam" "Anaerobes, Gramnegative" 8 16 FALSE
"EUCAST 2020" "MIC" "Parabacteroides" "Piperacillin/tazobactam" "Anaerobes, Gramnegative" 8 16 FALSE "EUCAST 2020" "MIC" "Parabacteroides" "Piperacillin/tazobactam" "Anaerobes, Gramnegative" 8 16 FALSE

Binary file not shown.

Binary file not shown.

View File

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

View File

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

View File

@@ -39,7 +39,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9026</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9029</span>
</span> </span>
</div> </div>
@@ -179,7 +179,7 @@
<h1>How to conduct AMR analysis</h1> <h1>How to conduct AMR analysis</h1>
<h4 class="author">Matthijs S. Berends</h4> <h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">17 February 2020</h4> <h4 class="date">20 February 2020</h4>
<div class="hidden name"><code>AMR.Rmd</code></div> <div class="hidden name"><code>AMR.Rmd</code></div>
@@ -188,7 +188,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 17 February 2020.</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 20 February 2020.</p>
<div id="introduction" class="section level1"> <div id="introduction" class="section level1">
<h1 class="hasAnchor"> <h1 class="hasAnchor">
<a href="#introduction" class="anchor"></a>Introduction</h1> <a href="#introduction" class="anchor"></a>Introduction</h1>
@@ -219,21 +219,21 @@
</tr></thead> </tr></thead>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">2020-02-17</td> <td align="center">2020-02-20</td>
<td align="center">abcd</td> <td align="center">abcd</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2020-02-17</td> <td align="center">2020-02-20</td>
<td align="center">abcd</td> <td align="center">abcd</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">R</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">2020-02-17</td> <td align="center">2020-02-20</td>
<td align="center">efgh</td> <td align="center">efgh</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">R</td> <td align="center">R</td>
@@ -328,52 +328,30 @@
</tr></thead> </tr></thead>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">2017-11-17</td> <td align="center">2010-01-05</td>
<td align="center">D1</td> <td align="center">F4</td>
<td align="center">Hospital A</td>
<td align="center">Staphylococcus aureus</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">2015-03-23</td>
<td align="center">N2</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="odd">
<td align="center">2010-04-13</td>
<td align="center">X4</td>
<td align="center">Hospital B</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="even">
<td align="center">2011-08-11</td>
<td align="center">M8</td>
<td align="center">Hospital A</td> <td align="center">Hospital A</td>
<td align="center">Streptococcus pneumoniae</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>
<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">2012-08-23</td>
<td align="center">J5</td>
<td align="center">Hospital B</td>
<td align="center">Streptococcus pneumoniae</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">M</td> <td align="center">M</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">2015-01-30</td> <td align="center">2016-06-20</td>
<td align="center">Z7</td> <td align="center">S1</td>
<td align="center">Hospital B</td> <td align="center">Hospital B</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">S</td> <td align="center">S</td>
@@ -383,14 +361,36 @@
<td align="center">F</td> <td align="center">F</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2014-12-06</td> <td align="center">2013-05-08</td>
<td align="center">F9</td> <td align="center">J3</td>
<td align="center">Hospital A</td> <td align="center">Hospital A</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td>
</tr>
<tr class="odd">
<td align="center">2011-12-28</td>
<td align="center">T8</td>
<td align="center">Hospital D</td>
<td align="center">Staphylococcus aureus</td>
<td align="center">S</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="even">
<td align="center">2016-11-05</td>
<td align="center">G9</td>
<td align="center">Hospital C</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">M</td> <td align="center">M</td>
</tr> </tr>
</tbody> </tbody>
@@ -423,16 +423,16 @@ Unique: 2</p>
<tr class="odd"> <tr class="odd">
<td align="left">1</td> <td align="left">1</td>
<td align="left">M</td> <td align="left">M</td>
<td align="right">10,441</td> <td align="right">10,402</td>
<td align="right">52.21%</td> <td align="right">52.01%</td>
<td align="right">10,441</td> <td align="right">10,402</td>
<td align="right">52.21%</td> <td align="right">52.01%</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="left">2</td> <td align="left">2</td>
<td align="left">F</td> <td align="left">F</td>
<td align="right">9,559</td> <td align="right">9,598</td>
<td align="right">47.80%</td> <td align="right">47.99%</td>
<td align="right">20,000</td> <td align="right">20,000</td>
<td align="right">100.00%</td> <td align="right">100.00%</td>
</tr> </tr>
@@ -452,8 +452,8 @@ Unique: 2</p>
<span id="cb13-3"><a href="#cb13-3"></a><span class="co"># Other rules by this AMR package</span></span> <span id="cb13-3"><a href="#cb13-3"></a><span class="co"># Other rules by this AMR package</span></span>
<span id="cb13-4"><a href="#cb13-4"></a><span class="co"># Non-EUCAST: inherit amoxicillin results for unavailable ampicillin (no changes)</span></span> <span id="cb13-4"><a href="#cb13-4"></a><span class="co"># Non-EUCAST: inherit amoxicillin results for unavailable ampicillin (no changes)</span></span>
<span id="cb13-5"><a href="#cb13-5"></a><span class="co"># Non-EUCAST: inherit ampicillin results for unavailable amoxicillin (no changes)</span></span> <span id="cb13-5"><a href="#cb13-5"></a><span class="co"># Non-EUCAST: inherit ampicillin results for unavailable amoxicillin (no changes)</span></span>
<span id="cb13-6"><a href="#cb13-6"></a><span class="co"># Non-EUCAST: set amoxicillin/clav acid = S where ampicillin = S (3,072 values changed)</span></span> <span id="cb13-6"><a href="#cb13-6"></a><span class="co"># Non-EUCAST: set amoxicillin/clav acid = S where ampicillin = S (2,986 values changed)</span></span>
<span id="cb13-7"><a href="#cb13-7"></a><span class="co"># Non-EUCAST: set ampicillin = R where amoxicillin/clav acid = R (144 values changed)</span></span> <span id="cb13-7"><a href="#cb13-7"></a><span class="co"># Non-EUCAST: set ampicillin = R where amoxicillin/clav acid = R (157 values changed)</span></span>
<span id="cb13-8"><a href="#cb13-8"></a><span class="co"># Non-EUCAST: set piperacillin = R where piperacillin/tazobactam = R (no changes)</span></span> <span id="cb13-8"><a href="#cb13-8"></a><span class="co"># Non-EUCAST: set piperacillin = R where piperacillin/tazobactam = R (no changes)</span></span>
<span id="cb13-9"><a href="#cb13-9"></a><span class="co"># Non-EUCAST: set piperacillin/tazobactam = S where piperacillin = S (no changes)</span></span> <span id="cb13-9"><a href="#cb13-9"></a><span class="co"># Non-EUCAST: set piperacillin/tazobactam = S where piperacillin = S (no changes)</span></span>
<span id="cb13-10"><a href="#cb13-10"></a><span class="co"># Non-EUCAST: set trimethoprim = R where trimethoprim/sulfa = R (no changes)</span></span> <span id="cb13-10"><a href="#cb13-10"></a><span class="co"># Non-EUCAST: set trimethoprim = R where trimethoprim/sulfa = R (no changes)</span></span>
@@ -479,14 +479,14 @@ Unique: 2</p>
<span id="cb13-30"><a href="#cb13-30"></a><span class="co"># Pasteurella multocida (no changes)</span></span> <span id="cb13-30"><a href="#cb13-30"></a><span class="co"># Pasteurella multocida (no changes)</span></span>
<span id="cb13-31"><a href="#cb13-31"></a><span class="co"># Staphylococcus (no changes)</span></span> <span id="cb13-31"><a href="#cb13-31"></a><span class="co"># Staphylococcus (no changes)</span></span>
<span id="cb13-32"><a href="#cb13-32"></a><span class="co"># Streptococcus groups A, B, C, G (no changes)</span></span> <span id="cb13-32"><a href="#cb13-32"></a><span class="co"># Streptococcus groups A, B, C, G (no changes)</span></span>
<span id="cb13-33"><a href="#cb13-33"></a><span class="co"># Streptococcus pneumoniae (1,007 values changed)</span></span> <span id="cb13-33"><a href="#cb13-33"></a><span class="co"># Streptococcus pneumoniae (1,017 values changed)</span></span>
<span id="cb13-34"><a href="#cb13-34"></a><span class="co"># Viridans group streptococci (no changes)</span></span> <span id="cb13-34"><a href="#cb13-34"></a><span class="co"># Viridans group streptococci (no changes)</span></span>
<span id="cb13-35"><a href="#cb13-35"></a><span class="co"># </span></span> <span id="cb13-35"><a href="#cb13-35"></a><span class="co"># </span></span>
<span id="cb13-36"><a href="#cb13-36"></a><span class="co"># EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)</span></span> <span id="cb13-36"><a href="#cb13-36"></a><span class="co"># EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)</span></span>
<span id="cb13-37"><a href="#cb13-37"></a><span class="co"># Table 01: Intrinsic resistance in Enterobacteriaceae (1,261 values changed)</span></span> <span id="cb13-37"><a href="#cb13-37"></a><span class="co"># Table 01: Intrinsic resistance in Enterobacteriaceae (1,297 values changed)</span></span>
<span id="cb13-38"><a href="#cb13-38"></a><span class="co"># Table 02: Intrinsic resistance in non-fermentative Gram-negative bacteria (no changes)</span></span> <span id="cb13-38"><a href="#cb13-38"></a><span class="co"># Table 02: Intrinsic resistance in non-fermentative Gram-negative bacteria (no changes)</span></span>
<span id="cb13-39"><a href="#cb13-39"></a><span class="co"># Table 03: Intrinsic resistance in other Gram-negative bacteria (no changes)</span></span> <span id="cb13-39"><a href="#cb13-39"></a><span class="co"># Table 03: Intrinsic resistance in other Gram-negative bacteria (no changes)</span></span>
<span id="cb13-40"><a href="#cb13-40"></a><span class="co"># Table 04: Intrinsic resistance in Gram-positive bacteria (2,767 values changed)</span></span> <span id="cb13-40"><a href="#cb13-40"></a><span class="co"># Table 04: Intrinsic resistance in Gram-positive bacteria (2,752 values changed)</span></span>
<span id="cb13-41"><a href="#cb13-41"></a><span class="co"># Table 08: Interpretive rules for B-lactam agents and Gram-positive cocci (no changes)</span></span> <span id="cb13-41"><a href="#cb13-41"></a><span class="co"># Table 08: Interpretive rules for B-lactam agents and Gram-positive cocci (no changes)</span></span>
<span id="cb13-42"><a href="#cb13-42"></a><span class="co"># Table 09: Interpretive rules for B-lactam agents and Gram-negative rods (no changes)</span></span> <span id="cb13-42"><a href="#cb13-42"></a><span class="co"># Table 09: Interpretive rules for B-lactam agents and Gram-negative rods (no changes)</span></span>
<span id="cb13-43"><a href="#cb13-43"></a><span class="co"># Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins (no changes)</span></span> <span id="cb13-43"><a href="#cb13-43"></a><span class="co"># Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins (no changes)</span></span>
@@ -494,15 +494,15 @@ Unique: 2</p>
<span id="cb13-45"><a href="#cb13-45"></a><span class="co"># Table 13: Interpretive rules for quinolones (no changes)</span></span> <span id="cb13-45"><a href="#cb13-45"></a><span class="co"># Table 13: Interpretive rules for quinolones (no changes)</span></span>
<span id="cb13-46"><a href="#cb13-46"></a><span class="co"># </span></span> <span id="cb13-46"><a href="#cb13-46"></a><span class="co"># </span></span>
<span id="cb13-47"><a href="#cb13-47"></a><span class="co"># -------------------------------------------------------------------------------</span></span> <span id="cb13-47"><a href="#cb13-47"></a><span class="co"># -------------------------------------------------------------------------------</span></span>
<span id="cb13-48"><a href="#cb13-48"></a><span class="co"># EUCAST rules affected 6,578 out of 20,000 rows, making a total of 8,251 edits</span></span> <span id="cb13-48"><a href="#cb13-48"></a><span class="co"># EUCAST rules affected 6,502 out of 20,000 rows, making a total of 8,209 edits</span></span>
<span id="cb13-49"><a href="#cb13-49"></a><span class="co"># =&gt; added 0 test results</span></span> <span id="cb13-49"><a href="#cb13-49"></a><span class="co"># =&gt; added 0 test results</span></span>
<span id="cb13-50"><a href="#cb13-50"></a><span class="co"># </span></span> <span id="cb13-50"><a href="#cb13-50"></a><span class="co"># </span></span>
<span id="cb13-51"><a href="#cb13-51"></a><span class="co"># =&gt; changed 8,251 test results</span></span> <span id="cb13-51"><a href="#cb13-51"></a><span class="co"># =&gt; changed 8,209 test results</span></span>
<span id="cb13-52"><a href="#cb13-52"></a><span class="co"># - 122 test results changed from S to I</span></span> <span id="cb13-52"><a href="#cb13-52"></a><span class="co"># - 124 test results changed from S to I</span></span>
<span id="cb13-53"><a href="#cb13-53"></a><span class="co"># - 4,709 test results changed from S to R</span></span> <span id="cb13-53"><a href="#cb13-53"></a><span class="co"># - 4,743 test results changed from S to R</span></span>
<span id="cb13-54"><a href="#cb13-54"></a><span class="co"># - 1,209 test results changed from I to S</span></span> <span id="cb13-54"><a href="#cb13-54"></a><span class="co"># - 1,209 test results changed from I to S</span></span>
<span id="cb13-55"><a href="#cb13-55"></a><span class="co"># - 348 test results changed from I to R</span></span> <span id="cb13-55"><a href="#cb13-55"></a><span class="co"># - 356 test results changed from I to R</span></span>
<span id="cb13-56"><a href="#cb13-56"></a><span class="co"># - 1,863 test results changed from R to S</span></span> <span id="cb13-56"><a href="#cb13-56"></a><span class="co"># - 1,777 test results changed from R to S</span></span>
<span id="cb13-57"><a href="#cb13-57"></a><span class="co"># -------------------------------------------------------------------------------</span></span> <span id="cb13-57"><a href="#cb13-57"></a><span class="co"># -------------------------------------------------------------------------------</span></span>
<span id="cb13-58"><a href="#cb13-58"></a><span class="co"># </span></span> <span id="cb13-58"><a href="#cb13-58"></a><span class="co"># </span></span>
<span id="cb13-59"><a href="#cb13-59"></a><span class="co"># Use eucast_rules(..., verbose = TRUE) (on your original data) to get a data.frame with all specified edits instead.</span></span></code></pre></div> <span id="cb13-59"><a href="#cb13-59"></a><span class="co"># Use eucast_rules(..., verbose = TRUE) (on your original data) to get a data.frame with all specified edits instead.</span></span></code></pre></div>
@@ -530,8 +530,8 @@ Unique: 2</p>
<span id="cb15-3"><a href="#cb15-3"></a><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `bacteria` as input for `col_mo`.</span></span> <span id="cb15-3"><a href="#cb15-3"></a><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `bacteria` as input for `col_mo`.</span></span>
<span id="cb15-4"><a href="#cb15-4"></a><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `date` as input for `col_date`.</span></span> <span id="cb15-4"><a href="#cb15-4"></a><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `date` as input for `col_date`.</span></span>
<span id="cb15-5"><a href="#cb15-5"></a><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></span> <span id="cb15-5"><a href="#cb15-5"></a><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></span>
<span id="cb15-6"><a href="#cb15-6"></a><span class="co"># =&gt; Found 5,663 first isolates (28.3% of total)</span></span></code></pre></div> <span id="cb15-6"><a href="#cb15-6"></a><span class="co"># =&gt; Found 5,695 first isolates (28.5% of total)</span></span></code></pre></div>
<p>So only 28.3% is suitable for resistance analysis! We can now filter on it with the <code><a href="https://dplyr.tidyverse.org/reference/filter.html">filter()</a></code> function, also from the <code>dplyr</code> package:</p> <p>So only 28.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="cb16"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb16-1"><a href="#cb16-1"></a>data_1st &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></span> <div class="sourceCode" id="cb16"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb16-1"><a href="#cb16-1"></a>data_1st &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb16-2"><a href="#cb16-2"></a><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>)</span></code></pre></div> <span id="cb16-2"><a href="#cb16-2"></a><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>)</span></code></pre></div>
<p>For future use, the above two syntaxes can be shortened with the <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> function:</p> <p>For future use, the above two syntaxes can be shortened with the <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> function:</p>
@@ -541,7 +541,7 @@ Unique: 2</p>
<div id="first-weighted-isolates" class="section level2"> <div id="first-weighted-isolates" class="section level2">
<h2 class="hasAnchor"> <h2 class="hasAnchor">
<a href="#first-weighted-isolates" class="anchor"></a>First <em>weighted</em> isolates</h2> <a href="#first-weighted-isolates" class="anchor"></a>First <em>weighted</em> isolates</h2>
<p>We made a slight twist to the CLSI algorithm, to take into account the antimicrobial susceptibility profile. Have a look at all isolates of patient I4, sorted on date:</p> <p>We made a slight twist to the CLSI algorithm, to take into account the antimicrobial susceptibility profile. Have a look at all isolates of patient N2, sorted on date:</p>
<table class="table"> <table class="table">
<thead><tr class="header"> <thead><tr class="header">
<th align="center">isolate</th> <th align="center">isolate</th>
@@ -557,30 +557,30 @@ Unique: 2</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">1</td> <td align="center">1</td>
<td align="center">2010-04-12</td> <td align="center">2010-02-09</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2</td> <td align="center">2</td>
<td align="center">2010-05-10</td> <td align="center">2010-03-02</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">R</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">3</td> <td align="center">3</td>
<td align="center">2010-07-25</td> <td align="center">2010-04-05</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@@ -590,19 +590,19 @@ Unique: 2</p>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">4</td> <td align="center">4</td>
<td align="center">2010-09-13</td> <td align="center">2010-05-19</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">I</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">5</td> <td align="center">5</td>
<td align="center">2010-09-29</td> <td align="center">2010-07-08</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">I</td> <td align="center">I</td>
@@ -612,8 +612,8 @@ Unique: 2</p>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">6</td> <td align="center">6</td>
<td align="center">2010-11-25</td> <td align="center">2010-08-09</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@@ -623,51 +623,51 @@ Unique: 2</p>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">7</td> <td align="center">7</td>
<td align="center">2010-11-25</td> <td align="center">2011-05-26</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
<td align="center">I</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">8</td> <td align="center">8</td>
<td align="center">2010-11-28</td> <td align="center">2011-05-26</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</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">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">9</td> <td align="center">9</td>
<td align="center">2010-12-27</td> <td align="center">2011-06-19</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">10</td> <td align="center">10</td>
<td align="center">2011-01-01</td> <td align="center">2011-07-29</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
<p>Only 1 isolates are marked as first according to CLSI guideline. But when reviewing the antibiogram, it is obvious that some isolates are absolutely different strains and should be included too. This is why we weigh isolates, based on their antibiogram. The <code><a href="../reference/key_antibiotics.html">key_antibiotics()</a></code> function adds a vector with 18 key antibiotics: 6 broad spectrum ones, 6 small spectrum for Gram negatives and 6 small spectrum for Gram positives. These can be defined by the user.</p> <p>Only 2 isolates are marked as first according to CLSI guideline. But when reviewing the antibiogram, it is obvious that some isolates are absolutely different strains and should be included too. This is why we weigh isolates, based on their antibiogram. The <code><a href="../reference/key_antibiotics.html">key_antibiotics()</a></code> function adds a vector with 18 key antibiotics: 6 broad spectrum ones, 6 small spectrum for Gram negatives and 6 small spectrum for Gram positives. These can be defined by the user.</p>
<p>If a column exists with a name like key(…)ab the <code><a href="../reference/first_isolate.html">first_isolate()</a></code> function will automatically use it and determine the first weighted isolates. Mind the NOTEs in below output:</p> <p>If a column exists with a name like key(…)ab the <code><a href="../reference/first_isolate.html">first_isolate()</a></code> function will automatically use it and determine the first weighted isolates. Mind the NOTEs in below output:</p>
<div class="sourceCode" id="cb18"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb18-1"><a href="#cb18-1"></a>data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></span> <div class="sourceCode" id="cb18"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb18-1"><a href="#cb18-1"></a>data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb18-2"><a href="#cb18-2"></a><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></span> <span id="cb18-2"><a href="#cb18-2"></a><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></span>
@@ -678,7 +678,7 @@ Unique: 2</p>
<span id="cb18-7"><a href="#cb18-7"></a><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></span> <span id="cb18-7"><a href="#cb18-7"></a><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></span>
<span id="cb18-8"><a href="#cb18-8"></a><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></span> <span id="cb18-8"><a href="#cb18-8"></a><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></span>
<span id="cb18-9"><a href="#cb18-9"></a><span class="co"># [Criterion] Inclusion based on key antibiotics, ignoring I</span></span> <span id="cb18-9"><a href="#cb18-9"></a><span class="co"># [Criterion] Inclusion based on key antibiotics, ignoring I</span></span>
<span id="cb18-10"><a href="#cb18-10"></a><span class="co"># =&gt; Found 14,979 first weighted isolates (74.9% of total)</span></span></code></pre></div> <span id="cb18-10"><a href="#cb18-10"></a><span class="co"># =&gt; Found 15,096 first weighted isolates (75.5% of total)</span></span></code></pre></div>
<table class="table"> <table class="table">
<thead><tr class="header"> <thead><tr class="header">
<th align="center">isolate</th> <th align="center">isolate</th>
@@ -695,20 +695,32 @@ Unique: 2</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">1</td> <td align="center">1</td>
<td align="center">2010-04-12</td> <td align="center">2010-02-09</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2</td> <td align="center">2</td>
<td align="center">2010-05-10</td> <td align="center">2010-03-02</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</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="odd">
<td align="center">3</td>
<td align="center">2010-04-05</td>
<td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@@ -717,34 +729,10 @@ Unique: 2</p>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="odd">
<td align="center">3</td>
<td align="center">2010-07-25</td>
<td align="center">I4</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td>
</tr>
<tr class="even"> <tr class="even">
<td align="center">4</td> <td align="center">4</td>
<td align="center">2010-09-13</td> <td align="center">2010-05-19</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td>
</tr>
<tr class="odd">
<td align="center">5</td>
<td align="center">2010-09-29</td>
<td align="center">I4</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">I</td> <td align="center">I</td>
@@ -753,10 +741,22 @@ Unique: 2</p>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="odd">
<td align="center">5</td>
<td align="center">2010-07-08</td>
<td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td>
</tr>
<tr class="even"> <tr class="even">
<td align="center">6</td> <td align="center">6</td>
<td align="center">2010-11-25</td> <td align="center">2010-08-09</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@@ -767,23 +767,23 @@ Unique: 2</p>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">7</td> <td align="center">7</td>
<td align="center">2010-11-25</td> <td align="center">2011-05-26</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
<td align="center">I</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">TRUE</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">8</td> <td align="center">8</td>
<td align="center">2010-11-28</td> <td align="center">2011-05-26</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</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">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
@@ -791,35 +791,35 @@ Unique: 2</p>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">9</td> <td align="center">9</td>
<td align="center">2010-12-27</td> <td align="center">2011-06-19</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">10</td> <td align="center">10</td>
<td align="center">2011-01-01</td> <td align="center">2011-07-29</td>
<td align="center">I4</td> <td align="center">N2</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">FALSE</td> <td align="center">TRUE</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
<p>Instead of 1, now 7 isolates are flagged. In total, 74.9% of all isolates are marked first weighted - 46.6% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.</p> <p>Instead of 2, now 9 isolates are flagged. In total, 75.5% of all isolates are marked first weighted - 47.0% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.</p>
<p>As with <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code>, theres a shortcut for this new algorithm too:</p> <p>As with <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code>, theres a shortcut for this new algorithm too:</p>
<div class="sourceCode" id="cb19"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb19-1"><a href="#cb19-1"></a>data_1st &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></span> <div class="sourceCode" id="cb19"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb19-1"><a href="#cb19-1"></a>data_1st &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb19-2"><a href="#cb19-2"></a><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_weighted_isolate</a></span>()</span></code></pre></div> <span id="cb19-2"><a href="#cb19-2"></a><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_weighted_isolate</a></span>()</span></code></pre></div>
<p>So we end up with 14,979 isolates for analysis.</p> <p>So we end up with 15,096 isolates for analysis.</p>
<p>We can remove unneeded columns:</p> <p>We can remove unneeded columns:</p>
<div class="sourceCode" id="cb20"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb20-1"><a href="#cb20-1"></a>data_1st &lt;-<span class="st"> </span>data_1st <span class="op">%&gt;%</span><span class="st"> </span></span> <div class="sourceCode" id="cb20"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb20-1"><a href="#cb20-1"></a>data_1st &lt;-<span class="st"> </span>data_1st <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb20-2"><a href="#cb20-2"></a><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://rdrr.io/r/base/c.html">c</a></span>(first, keyab))</span></code></pre></div> <span id="cb20-2"><a href="#cb20-2"></a><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://rdrr.io/r/base/c.html">c</a></span>(first, keyab))</span></code></pre></div>
@@ -845,56 +845,8 @@ Unique: 2</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td>1</td> <td>1</td>
<td align="center">2017-11-17</td> <td align="center">2010-01-05</td>
<td align="center">D1</td> <td align="center">F4</td>
<td align="center">Hospital A</td>
<td align="center">B_STPHY_AURS</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-positive</td>
<td align="center">Staphylococcus</td>
<td align="center">aureus</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td>2</td>
<td align="center">2015-03-23</td>
<td align="center">N2</td>
<td align="center">Hospital D</td>
<td align="center">B_STPHY_AURS</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td>
<td align="center">Gram-positive</td>
<td align="center">Staphylococcus</td>
<td align="center">aureus</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td>3</td>
<td align="center">2010-04-13</td>
<td align="center">X4</td>
<td align="center">Hospital B</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
<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>4</td>
<td align="center">2011-08-11</td>
<td align="center">M8</td>
<td align="center">Hospital A</td> <td align="center">Hospital A</td>
<td align="center">B_STRPT_PNMN</td> <td align="center">B_STRPT_PNMN</td>
<td align="center">S</td> <td align="center">S</td>
@@ -907,11 +859,27 @@ Unique: 2</p>
<td align="center">pneumoniae</td> <td align="center">pneumoniae</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="odd"> <tr class="even">
<td>6</td> <td>6</td>
<td align="center">2014-12-06</td> <td align="center">2016-11-05</td>
<td align="center">F9</td> <td align="center">G9</td>
<td align="center">Hospital A</td> <td align="center">Hospital C</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">M</td>
<td align="center">Gram-negative</td>
<td align="center">Escherichia</td>
<td align="center">coli</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td>7</td>
<td align="center">2016-05-20</td>
<td align="center">A10</td>
<td align="center">Hospital D</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@@ -924,21 +892,53 @@ Unique: 2</p>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td>7</td> <td>9</td>
<td align="center">2016-02-10</td> <td align="center">2015-10-02</td>
<td align="center">A4</td> <td align="center">R3</td>
<td align="center">Hospital B</td> <td align="center">Hospital C</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">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>10</td>
<td align="center">2016-03-04</td>
<td align="center">B10</td>
<td align="center">Hospital A</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td> <td align="center">M</td>
<td align="center">Gram-negative</td> <td align="center">Gram-negative</td>
<td align="center">Escherichia</td> <td align="center">Escherichia</td>
<td align="center">coli</td> <td align="center">coli</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even">
<td>11</td>
<td align="center">2013-09-10</td>
<td align="center">P4</td>
<td align="center">Hospital B</td>
<td align="center">B_KLBSL_PNMN</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">Klebsiella</td>
<td align="center">pneumoniae</td>
<td align="center">TRUE</td>
</tr>
</tbody> </tbody>
</table> </table>
<p>Time for the analysis!</p> <p>Time for the analysis!</p>
@@ -958,8 +958,8 @@ Unique: 2</p>
<div class="sourceCode" id="cb23"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb23-1"><a href="#cb23-1"></a>data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(genus, species)</span></code></pre></div> <div class="sourceCode" id="cb23"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb23-1"><a href="#cb23-1"></a>data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(genus, species)</span></code></pre></div>
<p><strong>Frequency table</strong></p> <p><strong>Frequency table</strong></p>
<p>Class: character<br> <p>Class: character<br>
Length: 14,979<br> Length: 15,096<br>
Available: 14,979 (100%, NA: 0 = 0%)<br> Available: 15,096 (100%, NA: 0 = 0%)<br>
Unique: 4</p> Unique: 4</p>
<p>Shortest: 16<br> <p>Shortest: 16<br>
Longest: 24</p> Longest: 24</p>
@@ -976,33 +976,33 @@ Longest: 24</p>
<tr class="odd"> <tr class="odd">
<td align="left">1</td> <td align="left">1</td>
<td align="left">Escherichia coli</td> <td align="left">Escherichia coli</td>
<td align="right">7,462</td> <td align="right">7,491</td>
<td align="right">49.82%</td> <td align="right">49.62%</td>
<td align="right">7,462</td> <td align="right">7,491</td>
<td align="right">49.82%</td> <td align="right">49.62%</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="left">2</td> <td align="left">2</td>
<td align="left">Staphylococcus aureus</td> <td align="left">Staphylococcus aureus</td>
<td align="right">3,695</td> <td align="right">3,729</td>
<td align="right">24.67%</td> <td align="right">24.70%</td>
<td align="right">11,157</td> <td align="right">11,220</td>
<td align="right">74.48%</td> <td align="right">74.32%</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="left">3</td> <td align="left">3</td>
<td align="left">Streptococcus pneumoniae</td> <td align="left">Streptococcus pneumoniae</td>
<td align="right">2,321</td> <td align="right">2,340</td>
<td align="right">15.50%</td> <td align="right">15.50%</td>
<td align="right">13,478</td> <td align="right">13,560</td>
<td align="right">89.98%</td> <td align="right">89.83%</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="left">4</td> <td align="left">4</td>
<td align="left">Klebsiella pneumoniae</td> <td align="left">Klebsiella pneumoniae</td>
<td align="right">1,501</td> <td align="right">1,536</td>
<td align="right">10.02%</td> <td align="right">10.17%</td>
<td align="right">14,979</td> <td align="right">15,096</td>
<td align="right">100.00%</td> <td align="right">100.00%</td>
</tr> </tr>
</tbody> </tbody>
@@ -1014,7 +1014,7 @@ Longest: 24</p>
<p>The functions <code><a href="../reference/proportion.html">resistance()</a></code> and <code><a href="../reference/proportion.html">susceptibility()</a></code> can be used to calculate antimicrobial resistance or susceptibility. For more specific analyses, the functions <code><a href="../reference/proportion.html">proportion_S()</a></code>, <code><a href="../reference/proportion.html">proportion_SI()</a></code>, <code><a href="../reference/proportion.html">proportion_I()</a></code>, <code><a href="../reference/proportion.html">proportion_IR()</a></code> and <code><a href="../reference/proportion.html">proportion_R()</a></code> can be used to determine the proportion of a specific antimicrobial outcome.</p> <p>The functions <code><a href="../reference/proportion.html">resistance()</a></code> and <code><a href="../reference/proportion.html">susceptibility()</a></code> can be used to calculate antimicrobial resistance or susceptibility. For more specific analyses, the functions <code><a href="../reference/proportion.html">proportion_S()</a></code>, <code><a href="../reference/proportion.html">proportion_SI()</a></code>, <code><a href="../reference/proportion.html">proportion_I()</a></code>, <code><a href="../reference/proportion.html">proportion_IR()</a></code> and <code><a href="../reference/proportion.html">proportion_R()</a></code> can be used to determine the proportion of a specific antimicrobial outcome.</p>
<p>As per the EUCAST guideline of 2019, we calculate resistance as the proportion of R (<code><a href="../reference/proportion.html">proportion_R()</a></code>, equal to <code><a href="../reference/proportion.html">resistance()</a></code>) and susceptibility as the proportion of S and I (<code><a href="../reference/proportion.html">proportion_SI()</a></code>, equal to <code><a href="../reference/proportion.html">susceptibility()</a></code>). These functions can be used on their own:</p> <p>As per the EUCAST guideline of 2019, we calculate resistance as the proportion of R (<code><a href="../reference/proportion.html">proportion_R()</a></code>, equal to <code><a href="../reference/proportion.html">resistance()</a></code>) and susceptibility as the proportion of S and I (<code><a href="../reference/proportion.html">proportion_SI()</a></code>, equal to <code><a href="../reference/proportion.html">susceptibility()</a></code>). These functions can be used on their own:</p>
<div class="sourceCode" id="cb24"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb24-1"><a href="#cb24-1"></a>data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/proportion.html">resistance</a></span>(AMX)</span> <div class="sourceCode" id="cb24"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb24-1"><a href="#cb24-1"></a>data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/proportion.html">resistance</a></span>(AMX)</span>
<span id="cb24-2"><a href="#cb24-2"></a><span class="co"># [1] 0.4633153</span></span></code></pre></div> <span id="cb24-2"><a href="#cb24-2"></a><span class="co"># [1] 0.4681373</span></span></code></pre></div>
<p>Or can be used in conjuction with <code><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by()</a></code> and <code><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise()</a></code>, both from the <code>dplyr</code> package:</p> <p>Or can be used in conjuction with <code><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by()</a></code> and <code><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise()</a></code>, both from the <code>dplyr</code> package:</p>
<div class="sourceCode" id="cb25"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb25-1"><a href="#cb25-1"></a>data_1st <span class="op">%&gt;%</span><span class="st"> </span></span> <div class="sourceCode" id="cb25"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb25-1"><a href="#cb25-1"></a>data_1st <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb25-2"><a href="#cb25-2"></a><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></span> <span id="cb25-2"><a href="#cb25-2"></a><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></span>
@@ -1027,19 +1027,19 @@ Longest: 24</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">Hospital A</td> <td align="center">Hospital A</td>
<td align="center">0.4589178</td> <td align="center">0.4648446</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Hospital B</td> <td align="center">Hospital B</td>
<td align="center">0.4609652</td> <td align="center">0.4689223</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">Hospital C</td> <td align="center">Hospital C</td>
<td align="center">0.4542615</td> <td align="center">0.4656180</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Hospital D</td> <td align="center">Hospital D</td>
<td align="center">0.4815972</td> <td align="center">0.4734787</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
@@ -1057,23 +1057,23 @@ Longest: 24</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">Hospital A</td> <td align="center">Hospital A</td>
<td align="center">0.4589178</td> <td align="center">0.4648446</td>
<td align="center">4491</td> <td align="center">4537</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Hospital B</td> <td align="center">Hospital B</td>
<td align="center">0.4609652</td> <td align="center">0.4689223</td>
<td align="center">5367</td> <td align="center">5261</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">Hospital C</td> <td align="center">Hospital C</td>
<td align="center">0.4542615</td> <td align="center">0.4656180</td>
<td align="center">2241</td> <td align="center">2225</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Hospital D</td> <td align="center">Hospital D</td>
<td align="center">0.4815972</td> <td align="center">0.4734787</td>
<td align="center">2880</td> <td align="center">3073</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
@@ -1093,27 +1093,27 @@ Longest: 24</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">Escherichia</td> <td align="center">Escherichia</td>
<td align="center">0.9234790</td> <td align="center">0.9255106</td>
<td align="center">0.8998928</td> <td align="center">0.8972100</td>
<td align="center">0.9963817</td> <td align="center">0.9937258</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Klebsiella</td> <td align="center">Klebsiella</td>
<td align="center">0.9347102</td> <td align="center">0.9199219</td>
<td align="center">0.8974017</td> <td align="center">0.8932292</td>
<td align="center">0.9940040</td> <td align="center">0.9934896</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">Staphylococcus</td> <td align="center">Staphylococcus</td>
<td align="center">0.9271989</td> <td align="center">0.9187450</td>
<td align="center">0.9188092</td> <td align="center">0.9133816</td>
<td align="center">0.9929635</td> <td align="center">0.9924913</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Streptococcus</td> <td align="center">Streptococcus</td>
<td align="center">0.6066351</td> <td align="center">0.6128205</td>
<td align="center">0.0000000</td> <td align="center">0.0000000</td>
<td align="center">0.6066351</td> <td align="center">0.6128205</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>

Binary file not shown.

Before

Width:  |  Height:  |  Size: 64 KiB

After

Width:  |  Height:  |  Size: 64 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 51 KiB

After

Width:  |  Height:  |  Size: 51 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 102 KiB

After

Width:  |  Height:  |  Size: 102 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 83 KiB

After

Width:  |  Height:  |  Size: 83 KiB

View File

@@ -39,7 +39,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9025</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9029</span>
</span> </span>
</div> </div>
@@ -179,7 +179,7 @@
<h1>How to apply EUCAST rules</h1> <h1>How to apply EUCAST rules</h1>
<h4 class="author">Matthijs S. Berends</h4> <h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">17 February 2020</h4> <h4 class="date">20 February 2020</h4>
<div class="hidden name"><code>EUCAST.Rmd</code></div> <div class="hidden name"><code>EUCAST.Rmd</code></div>

View File

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

View File

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

View File

@@ -43,7 +43,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a> <a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9027</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.0.0.9000</span>
</span> </span>
</div> </div>
@@ -266,7 +266,7 @@ A methods paper about this package has been preprinted at bioRxiv (DOI: 10.1101/
<a href="#latest-development-version" class="anchor"></a>Latest development version</h4> <a href="#latest-development-version" class="anchor"></a>Latest development version</h4>
<p>The latest and unpublished development version can be installed with (<strong>precaution: may be unstable</strong>):</p> <p>The latest and unpublished development version can be installed with (<strong>precaution: may be unstable</strong>):</p>
<div class="sourceCode" id="cb2"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb2-1"><a href="#cb2-1"></a><span class="kw"><a href="https://rdrr.io/r/utils/install.packages.html">install.packages</a></span>(<span class="st">"devtools"</span>)</span> <div class="sourceCode" id="cb2"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb2-1"><a href="#cb2-1"></a><span class="kw"><a href="https://rdrr.io/r/utils/install.packages.html">install.packages</a></span>(<span class="st">"devtools"</span>)</span>
<span id="cb2-2"><a href="#cb2-2"></a>devtools<span class="op">::</span><span class="kw"><a href="https://rdrr.io/pkg/devtools/man/remote-reexports.html">install_gitlab</a></span>(<span class="st">"msberends/AMR"</span>)</span></code></pre></div> <span id="cb2-2"><a href="#cb2-2"></a>devtools<span class="op">::</span><span class="kw"><a href="https://devtools.r-lib.org//reference/remote-reexports.html">install_gitlab</a></span>(<span class="st">"msberends/AMR"</span>)</span></code></pre></div>
</div> </div>
</div> </div>
<div id="get-started" class="section level3"> <div id="get-started" class="section level3">

View File

@@ -78,7 +78,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9027</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.0.0.9000</span>
</span> </span>
</div> </div>
@@ -219,14 +219,38 @@
</div> </div>
<div id="amr-0909027" class="section level1"> <div id="amr-1009000" class="section level1">
<h1 class="page-header"> <h1 class="page-header">
<a href="#amr-0909027" class="anchor"></a>AMR 0.9.0.9027<small> Unreleased </small> <a href="#amr-1009000" class="anchor"></a>AMR 1.0.0.9000<small> Unreleased </small>
</h1> </h1>
<div id="last-updated-17-feb-2020" class="section level2"> <div id="last-updated-20-feb-2020" class="section level2">
<h2 class="hasAnchor"> <h2 class="hasAnchor">
<a href="#last-updated-17-feb-2020" class="anchor"></a><small>Last updated: 17-Feb-2020</small> <a href="#last-updated-20-feb-2020" class="anchor"></a><small>Last updated: 20-Feb-2020</small>
</h2> </h2>
<div id="changed" class="section level3">
<h3 class="hasAnchor">
<a href="#changed" class="anchor"></a>Changed</h3>
<ul>
<li><p>Added antibiotic abbreviations for a laboratory manufacturer (GLIMS) for cefuroxime, cefotaxime, ceftazidime, cefepime, cefoxitin and trimethoprim/sulfamethoxazole</p></li>
<li><p>Fixed floating point error for some MIC compa in EUCAST 2020 guideline</p></li>
<li>
<p>Interpretation from MIC values to R/SI can now be used with <code><a href="https://dplyr.tidyverse.org/reference/mutate_all.html">mutate_at()</a></code> of the dplyr package:</p>
<div class="sourceCode" id="cb1"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb1-1"><a href="#cb1-1"></a>yourdata <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb1-2"><a href="#cb1-2"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate_all.html">mutate_at</a></span>(<span class="kw"><a href="https://dplyr.tidyverse.org/reference/vars.html">vars</a></span>(antibiotic1<span class="op">:</span>antibiotic25), as.rsi, <span class="dt">mo =</span> <span class="st">"E. coli"</span>)</span>
<span id="cb1-3"><a href="#cb1-3"></a></span>
<span id="cb1-4"><a href="#cb1-4"></a>yourdata <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb1-5"><a href="#cb1-5"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate_all.html">mutate_at</a></span>(<span class="kw"><a href="https://dplyr.tidyverse.org/reference/vars.html">vars</a></span>(antibiotic1<span class="op">:</span>antibiotic25), as.rsi, <span class="dt">mo =</span> .<span class="op">$</span>mybacteria)</span></code></pre></div>
</li>
<li><p>Added <code>uti</code> (as abbreviation of urinary tract infections) as parameter to <code><a href="../reference/as.rsi.html">as.rsi()</a></code>, so interpretation of MIC values and disk zones can be made dependent on isolates specifically from UTIs</p></li>
</ul>
</div>
</div>
</div>
<div id="amr-100" class="section level1">
<h1 class="page-header">
<a href="#amr-100" class="anchor"></a>AMR 1.0.0<small> 2020-02-17 </small>
</h1>
<p>This software is now out of beta and considered stable. Nonetheless, this package will be developed continually.</p>
<div id="new" class="section level3"> <div id="new" class="section level3">
<h3 class="hasAnchor"> <h3 class="hasAnchor">
<a href="#new" class="anchor"></a>New</h3> <a href="#new" class="anchor"></a>New</h3>
@@ -237,21 +261,21 @@
<ul> <ul>
<li> <li>
<p>Support for LOINC codes in the <code>antibiotics</code> data set. Use <code><a href="../reference/ab_property.html">ab_loinc()</a></code> to retrieve LOINC codes, or use a LOINC code for input in any <code>ab_*</code> function:</p> <p>Support for LOINC codes in the <code>antibiotics</code> data set. Use <code><a href="../reference/ab_property.html">ab_loinc()</a></code> to retrieve LOINC codes, or use a LOINC code for input in any <code>ab_*</code> function:</p>
<div class="sourceCode" id="cb1"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb1-1"><a href="#cb1-1"></a><span class="kw"><a href="../reference/ab_property.html">ab_loinc</a></span>(<span class="st">"ampicillin"</span>)</span> <div class="sourceCode" id="cb2"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb2-1"><a href="#cb2-1"></a><span class="kw"><a href="../reference/ab_property.html">ab_loinc</a></span>(<span class="st">"ampicillin"</span>)</span>
<span id="cb1-2"><a href="#cb1-2"></a><span class="co">#&gt; [1] "21066-6" "3355-5" "33562-0" "33919-2" "43883-8" "43884-6" "87604-5"</span></span> <span id="cb2-2"><a href="#cb2-2"></a><span class="co">#&gt; [1] "21066-6" "3355-5" "33562-0" "33919-2" "43883-8" "43884-6" "87604-5"</span></span>
<span id="cb1-3"><a href="#cb1-3"></a><span class="kw"><a href="../reference/ab_property.html">ab_name</a></span>(<span class="st">"21066-6"</span>)</span> <span id="cb2-3"><a href="#cb2-3"></a><span class="kw"><a href="../reference/ab_property.html">ab_name</a></span>(<span class="st">"21066-6"</span>)</span>
<span id="cb1-4"><a href="#cb1-4"></a><span class="co">#&gt; [1] "Ampicillin"</span></span> <span id="cb2-4"><a href="#cb2-4"></a><span class="co">#&gt; [1] "Ampicillin"</span></span>
<span id="cb1-5"><a href="#cb1-5"></a><span class="kw"><a href="../reference/ab_property.html">ab_atc</a></span>(<span class="st">"21066-6"</span>)</span> <span id="cb2-5"><a href="#cb2-5"></a><span class="kw"><a href="../reference/ab_property.html">ab_atc</a></span>(<span class="st">"21066-6"</span>)</span>
<span id="cb1-6"><a href="#cb1-6"></a><span class="co">#&gt; [1] "J01CA01"</span></span></code></pre></div> <span id="cb2-6"><a href="#cb2-6"></a><span class="co">#&gt; [1] "J01CA01"</span></span></code></pre></div>
</li> </li>
<li> <li>
<p>Support for SNOMED CT codes in the <code>microorganisms</code> data set. Use <code><a href="../reference/mo_property.html">mo_snomed()</a></code> to retrieve SNOMED codes, or use a SNOMED code for input in any <code>mo_*</code> function:</p> <p>Support for SNOMED CT codes in the <code>microorganisms</code> data set. Use <code><a href="../reference/mo_property.html">mo_snomed()</a></code> to retrieve SNOMED codes, or use a SNOMED code for input in any <code>mo_*</code> function:</p>
<div class="sourceCode" id="cb2"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb2-1"><a href="#cb2-1"></a><span class="kw"><a href="../reference/mo_property.html">mo_snomed</a></span>(<span class="st">"S. aureus"</span>)</span> <div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb3-1"><a href="#cb3-1"></a><span class="kw"><a href="../reference/mo_property.html">mo_snomed</a></span>(<span class="st">"S. aureus"</span>)</span>
<span id="cb2-2"><a href="#cb2-2"></a><span class="co">#&gt; [1] 115329001 3092008 113961008</span></span> <span id="cb3-2"><a href="#cb3-2"></a><span class="co">#&gt; [1] 115329001 3092008 113961008</span></span>
<span id="cb2-3"><a href="#cb2-3"></a><span class="kw"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="dv">115329001</span>)</span> <span id="cb3-3"><a href="#cb3-3"></a><span class="kw"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="dv">115329001</span>)</span>
<span id="cb2-4"><a href="#cb2-4"></a><span class="co">#&gt; [1] "Staphylococcus aureus"</span></span> <span id="cb3-4"><a href="#cb3-4"></a><span class="co">#&gt; [1] "Staphylococcus aureus"</span></span>
<span id="cb2-5"><a href="#cb2-5"></a><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="dv">115329001</span>)</span> <span id="cb3-5"><a href="#cb3-5"></a><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="dv">115329001</span>)</span>
<span id="cb2-6"><a href="#cb2-6"></a><span class="co">#&gt; [1] "Gram-positive"</span></span></code></pre></div> <span id="cb3-6"><a href="#cb3-6"></a><span class="co">#&gt; [1] "Gram-positive"</span></span></code></pre></div>
</li> </li>
</ul> </ul>
</li> </li>
@@ -296,7 +320,6 @@
<li>Removed unnecessary <code>AMR::</code> calls</li> <li>Removed unnecessary <code>AMR::</code> calls</li>
</ul> </ul>
</div> </div>
</div>
</div> </div>
<div id="amr-090" class="section level1"> <div id="amr-090" class="section level1">
<h1 class="page-header"> <h1 class="page-header">
@@ -310,9 +333,9 @@
<ul> <ul>
<li> <li>
<p>If you were dependent on the old Enterobacteriaceae family e.g. by using in your code:</p> <p>If you were dependent on the old Enterobacteriaceae family e.g. by using in your code:</p>
<div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb3-1"><a href="#cb3-1"></a><span class="cf">if</span> (<span class="kw"><a href="../reference/mo_property.html">mo_family</a></span>(somebugs) <span class="op">==</span><span class="st"> "Enterobacteriaceae"</span>) ...</span></code></pre></div> <div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb4-1"><a href="#cb4-1"></a><span class="cf">if</span> (<span class="kw"><a href="../reference/mo_property.html">mo_family</a></span>(somebugs) <span class="op">==</span><span class="st"> "Enterobacteriaceae"</span>) ...</span></code></pre></div>
<p>then please adjust this to:</p> <p>then please adjust this to:</p>
<div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb4-1"><a href="#cb4-1"></a><span class="cf">if</span> (<span class="kw"><a href="../reference/mo_property.html">mo_order</a></span>(somebugs) <span class="op">==</span><span class="st"> "Enterobacterales"</span>) ...</span></code></pre></div> <div class="sourceCode" id="cb5"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb5-1"><a href="#cb5-1"></a><span class="cf">if</span> (<span class="kw"><a href="../reference/mo_property.html">mo_order</a></span>(somebugs) <span class="op">==</span><span class="st"> "Enterobacterales"</span>) ...</span></code></pre></div>
</li> </li>
</ul> </ul>
</li> </li>
@@ -324,12 +347,12 @@
<ul> <ul>
<li> <li>
<p>Functions <code><a href="../reference/proportion.html">susceptibility()</a></code> and <code><a href="../reference/proportion.html">resistance()</a></code> as aliases of <code><a href="../reference/proportion.html">proportion_SI()</a></code> and <code><a href="../reference/proportion.html">proportion_R()</a></code>, respectively. These functions were added to make it more clear that “I” should be considered susceptible and not resistant.</p> <p>Functions <code><a href="../reference/proportion.html">susceptibility()</a></code> and <code><a href="../reference/proportion.html">resistance()</a></code> as aliases of <code><a href="../reference/proportion.html">proportion_SI()</a></code> and <code><a href="../reference/proportion.html">proportion_R()</a></code>, respectively. These functions were added to make it more clear that “I” should be considered susceptible and not resistant.</p>
<div class="sourceCode" id="cb5"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb5-1"><a href="#cb5-1"></a><span class="kw"><a href="https://rdrr.io/r/base/library.html">library</a></span>(dplyr)</span> <div class="sourceCode" id="cb6"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb6-1"><a href="#cb6-1"></a><span class="kw"><a href="https://rdrr.io/r/base/library.html">library</a></span>(dplyr)</span>
<span id="cb5-2"><a href="#cb5-2"></a>example_isolates <span class="op">%&gt;%</span></span> <span id="cb6-2"><a href="#cb6-2"></a>example_isolates <span class="op">%&gt;%</span></span>
<span id="cb5-3"><a href="#cb5-3"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(<span class="dt">bug =</span> <span class="kw"><a href="../reference/mo_property.html">mo_name</a></span>(mo)) <span class="op">%&gt;%</span><span class="st"> </span></span> <span id="cb6-3"><a href="#cb6-3"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(<span class="dt">bug =</span> <span class="kw"><a href="../reference/mo_property.html">mo_name</a></span>(mo)) <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb5-4"><a href="#cb5-4"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise</a></span>(<span class="dt">amoxicillin =</span> <span class="kw"><a href="../reference/proportion.html">resistance</a></span>(AMX),</span> <span id="cb6-4"><a href="#cb6-4"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise</a></span>(<span class="dt">amoxicillin =</span> <span class="kw"><a href="../reference/proportion.html">resistance</a></span>(AMX),</span>
<span id="cb5-5"><a href="#cb5-5"></a> <span class="dt">amox_clav =</span> <span class="kw"><a href="../reference/proportion.html">resistance</a></span>(AMC)) <span class="op">%&gt;%</span></span> <span id="cb6-5"><a href="#cb6-5"></a> <span class="dt">amox_clav =</span> <span class="kw"><a href="../reference/proportion.html">resistance</a></span>(AMC)) <span class="op">%&gt;%</span></span>
<span id="cb5-6"><a href="#cb5-6"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(<span class="op">!</span><span class="kw"><a href="https://rdrr.io/r/base/NA.html">is.na</a></span>(amoxicillin) <span class="op">|</span><span class="st"> </span><span class="op">!</span><span class="kw"><a href="https://rdrr.io/r/base/NA.html">is.na</a></span>(amox_clav))</span></code></pre></div> <span id="cb6-6"><a href="#cb6-6"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(<span class="op">!</span><span class="kw"><a href="https://rdrr.io/r/base/NA.html">is.na</a></span>(amoxicillin) <span class="op">|</span><span class="st"> </span><span class="op">!</span><span class="kw"><a href="https://rdrr.io/r/base/NA.html">is.na</a></span>(amox_clav))</span></code></pre></div>
</li> </li>
<li> <li>
<p>Support for a new MDRO guideline: Magiorakos AP, Srinivasan A <em>et al.</em> “Multidrug-resistant, extensively drug-resistant and pandrug-resistant bacteria: an international expert proposal for interim standard definitions for acquired resistance.” Clinical Microbiology and Infection (2012).</p> <p>Support for a new MDRO guideline: Magiorakos AP, Srinivasan A <em>et al.</em> “Multidrug-resistant, extensively drug-resistant and pandrug-resistant bacteria: an international expert proposal for interim standard definitions for acquired resistance.” Clinical Microbiology and Infection (2012).</p>
@@ -351,16 +374,16 @@
<li><p>More intelligent way of coping with some consonants like “l” and “r”</p></li> <li><p>More intelligent way of coping with some consonants like “l” and “r”</p></li>
<li> <li>
<p>Added a score (a certainty percentage) to <code><a href="../reference/as.mo.html">mo_uncertainties()</a></code>, that is calculated using the <a href="https://en.wikipedia.org/wiki/Levenshtein_distance">Levenshtein distance</a>:</p> <p>Added a score (a certainty percentage) to <code><a href="../reference/as.mo.html">mo_uncertainties()</a></code>, that is calculated using the <a href="https://en.wikipedia.org/wiki/Levenshtein_distance">Levenshtein distance</a>:</p>
<div class="sourceCode" id="cb6"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb6-1"><a href="#cb6-1"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="kw"><a href="https://rdrr.io/r/base/c.html">c</a></span>(<span class="st">"Stafylococcus aureus"</span>,</span> <div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb7-1"><a href="#cb7-1"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="kw"><a href="https://rdrr.io/r/base/c.html">c</a></span>(<span class="st">"Stafylococcus aureus"</span>,</span>
<span id="cb6-2"><a href="#cb6-2"></a> <span class="st">"staphylokok aureuz"</span>))</span> <span id="cb7-2"><a href="#cb7-2"></a> <span class="st">"staphylokok aureuz"</span>))</span>
<span id="cb6-3"><a href="#cb6-3"></a><span class="co">#&gt; Warning: </span></span> <span id="cb7-3"><a href="#cb7-3"></a><span class="co">#&gt; Warning: </span></span>
<span id="cb6-4"><a href="#cb6-4"></a><span class="co">#&gt; Results of two values were guessed with uncertainty. Use mo_uncertainties() to review them.</span></span> <span id="cb7-4"><a href="#cb7-4"></a><span class="co">#&gt; Results of two values were guessed with uncertainty. Use mo_uncertainties() to review them.</span></span>
<span id="cb6-5"><a href="#cb6-5"></a><span class="co">#&gt; Class 'mo'</span></span> <span id="cb7-5"><a href="#cb7-5"></a><span class="co">#&gt; Class 'mo'</span></span>
<span id="cb6-6"><a href="#cb6-6"></a><span class="co">#&gt; [1] B_STPHY_AURS B_STPHY_AURS</span></span> <span id="cb7-6"><a href="#cb7-6"></a><span class="co">#&gt; [1] B_STPHY_AURS B_STPHY_AURS</span></span>
<span id="cb6-7"><a href="#cb6-7"></a></span> <span id="cb7-7"><a href="#cb7-7"></a></span>
<span id="cb6-8"><a href="#cb6-8"></a><span class="kw"><a href="../reference/as.mo.html">mo_uncertainties</a></span>()</span> <span id="cb7-8"><a href="#cb7-8"></a><span class="kw"><a href="../reference/as.mo.html">mo_uncertainties</a></span>()</span>
<span id="cb6-9"><a href="#cb6-9"></a><span class="co">#&gt; "Stafylococcus aureus" -&gt; Staphylococcus aureus (B_STPHY_AURS, score: 95.2%)</span></span> <span id="cb7-9"><a href="#cb7-9"></a><span class="co">#&gt; "Stafylococcus aureus" -&gt; Staphylococcus aureus (B_STPHY_AURS, score: 95.2%)</span></span>
<span id="cb6-10"><a href="#cb6-10"></a><span class="co">#&gt; "staphylokok aureuz" -&gt; Staphylococcus aureus (B_STPHY_AURS, score: 85.7%)</span></span></code></pre></div> <span id="cb7-10"><a href="#cb7-10"></a><span class="co">#&gt; "staphylokok aureuz" -&gt; Staphylococcus aureus (B_STPHY_AURS, score: 85.7%)</span></span></code></pre></div>
</li> </li>
</ul> </ul>
</li> </li>
@@ -408,22 +431,22 @@
<ul> <ul>
<li> <li>
<p>Determination of first isolates now <strong>excludes</strong> all unknown microorganisms at default, i.e. microbial code <code>"UNKNOWN"</code>. They can be included with the new parameter <code>include_unknown</code>:</p> <p>Determination of first isolates now <strong>excludes</strong> all unknown microorganisms at default, i.e. microbial code <code>"UNKNOWN"</code>. They can be included with the new parameter <code>include_unknown</code>:</p>
<div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb7-1"><a href="#cb7-1"></a><span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(..., <span class="dt">include_unknown =</span> <span class="ot">TRUE</span>)</span></code></pre></div> <div class="sourceCode" id="cb8"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb8-1"><a href="#cb8-1"></a><span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(..., <span class="dt">include_unknown =</span> <span class="ot">TRUE</span>)</span></code></pre></div>
<p>For WHONET users, this means that all records/isolates with organism code <code>"con"</code> (<em>contamination</em>) will be excluded at default, since <code>as.mo("con") = "UNKNOWN"</code>. The function always shows a note with the number of unknown microorganisms that were included or excluded.</p> <p>For WHONET users, this means that all records/isolates with organism code <code>"con"</code> (<em>contamination</em>) will be excluded at default, since <code>as.mo("con") = "UNKNOWN"</code>. The function always shows a note with the number of unknown microorganisms that were included or excluded.</p>
</li> </li>
<li> <li>
<p>For code consistency, classes <code>ab</code> and <code>mo</code> will now be preserved in any subsetting or assignment. For the sake of data integrity, this means that invalid assignments will now result in <code>NA</code>:</p> <p>For code consistency, classes <code>ab</code> and <code>mo</code> will now be preserved in any subsetting or assignment. For the sake of data integrity, this means that invalid assignments will now result in <code>NA</code>:</p>
<div class="sourceCode" id="cb8"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb8-1"><a href="#cb8-1"></a><span class="co"># how it works in base R:</span></span> <div class="sourceCode" id="cb9"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb9-1"><a href="#cb9-1"></a><span class="co"># how it works in base R:</span></span>
<span id="cb8-2"><a href="#cb8-2"></a>x &lt;-<span class="st"> </span><span class="kw"><a href="https://rdrr.io/r/base/factor.html">factor</a></span>(<span class="st">"A"</span>)</span> <span id="cb9-2"><a href="#cb9-2"></a>x &lt;-<span class="st"> </span><span class="kw"><a href="https://rdrr.io/r/base/factor.html">factor</a></span>(<span class="st">"A"</span>)</span>
<span id="cb8-3"><a href="#cb8-3"></a>x[<span class="dv">1</span>] &lt;-<span class="st"> "B"</span></span> <span id="cb9-3"><a href="#cb9-3"></a>x[<span class="dv">1</span>] &lt;-<span class="st"> "B"</span></span>
<span id="cb8-4"><a href="#cb8-4"></a><span class="co">#&gt; Warning message:</span></span> <span id="cb9-4"><a href="#cb9-4"></a><span class="co">#&gt; Warning message:</span></span>
<span id="cb8-5"><a href="#cb8-5"></a><span class="co">#&gt; invalid factor level, NA generated</span></span> <span id="cb9-5"><a href="#cb9-5"></a><span class="co">#&gt; invalid factor level, NA generated</span></span>
<span id="cb8-6"><a href="#cb8-6"></a></span> <span id="cb9-6"><a href="#cb9-6"></a></span>
<span id="cb8-7"><a href="#cb8-7"></a><span class="co"># how it now works similarly for classes 'mo' and 'ab':</span></span> <span id="cb9-7"><a href="#cb9-7"></a><span class="co"># how it now works similarly for classes 'mo' and 'ab':</span></span>
<span id="cb8-8"><a href="#cb8-8"></a>x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. coli"</span>)</span> <span id="cb9-8"><a href="#cb9-8"></a>x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. coli"</span>)</span>
<span id="cb8-9"><a href="#cb8-9"></a>x[<span class="dv">1</span>] &lt;-<span class="st"> "testvalue"</span></span> <span id="cb9-9"><a href="#cb9-9"></a>x[<span class="dv">1</span>] &lt;-<span class="st"> "testvalue"</span></span>
<span id="cb8-10"><a href="#cb8-10"></a><span class="co">#&gt; Warning message:</span></span> <span id="cb9-10"><a href="#cb9-10"></a><span class="co">#&gt; Warning message:</span></span>
<span id="cb8-11"><a href="#cb8-11"></a><span class="co">#&gt; invalid microorganism code, NA generated</span></span></code></pre></div> <span id="cb9-11"><a href="#cb9-11"></a><span class="co">#&gt; invalid microorganism code, NA generated</span></span></code></pre></div>
<p>This is important, because a value like <code>"testvalue"</code> could never be understood by e.g. <code><a href="../reference/mo_property.html">mo_name()</a></code>, although the class would suggest a valid microbial code.</p> <p>This is important, because a value like <code>"testvalue"</code> could never be understood by e.g. <code><a href="../reference/mo_property.html">mo_name()</a></code>, although the class would suggest a valid microbial code.</p>
</li> </li>
<li><p>Function <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> has moved to a new package, <a href="https://github.com/msberends/clean"><code>clean</code></a> (<a href="https://cran.r-project.org/package=clean">CRAN link</a>), since creating frequency tables actually does not fit the scope of this package. The <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> function still works, since it is re-exported from the <code>clean</code> package (which will be installed automatically upon updating this <code>AMR</code> package).</p></li> <li><p>Function <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> has moved to a new package, <a href="https://github.com/msberends/clean"><code>clean</code></a> (<a href="https://cran.r-project.org/package=clean">CRAN link</a>), since creating frequency tables actually does not fit the scope of this package. The <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> function still works, since it is re-exported from the <code>clean</code> package (which will be installed automatically upon updating this <code>AMR</code> package).</p></li>
@@ -436,62 +459,62 @@
<ul> <ul>
<li> <li>
<p>Function <code><a href="../reference/bug_drug_combinations.html">bug_drug_combinations()</a></code> to quickly get a <code>data.frame</code> with the results of all bug-drug combinations in a data set. The column containing microorganism codes is guessed automatically and its input is transformed with <code><a href="../reference/mo_property.html">mo_shortname()</a></code> at default:</p> <p>Function <code><a href="../reference/bug_drug_combinations.html">bug_drug_combinations()</a></code> to quickly get a <code>data.frame</code> with the results of all bug-drug combinations in a data set. The column containing microorganism codes is guessed automatically and its input is transformed with <code><a href="../reference/mo_property.html">mo_shortname()</a></code> at default:</p>
<div class="sourceCode" id="cb9"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb9-1"><a href="#cb9-1"></a>x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/bug_drug_combinations.html">bug_drug_combinations</a></span>(example_isolates)</span> <div class="sourceCode" id="cb10"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb10-1"><a href="#cb10-1"></a>x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/bug_drug_combinations.html">bug_drug_combinations</a></span>(example_isolates)</span>
<span id="cb9-2"><a href="#cb9-2"></a><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `mo` as input for `col_mo`.</span></span> <span id="cb10-2"><a href="#cb10-2"></a><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `mo` as input for `col_mo`.</span></span>
<span id="cb9-3"><a href="#cb9-3"></a>x[<span class="dv">1</span><span class="op">:</span><span class="dv">4</span>, ]</span> <span id="cb10-3"><a href="#cb10-3"></a>x[<span class="dv">1</span><span class="op">:</span><span class="dv">4</span>, ]</span>
<span id="cb9-4"><a href="#cb9-4"></a><span class="co">#&gt; mo ab S I R total</span></span> <span id="cb10-4"><a href="#cb10-4"></a><span class="co">#&gt; mo ab S I R total</span></span>
<span id="cb9-5"><a href="#cb9-5"></a><span class="co">#&gt; 1 A. baumannii AMC 0 0 3 3</span></span> <span id="cb10-5"><a href="#cb10-5"></a><span class="co">#&gt; 1 A. baumannii AMC 0 0 3 3</span></span>
<span id="cb9-6"><a href="#cb9-6"></a><span class="co">#&gt; 2 A. baumannii AMK 0 0 0 0</span></span> <span id="cb10-6"><a href="#cb10-6"></a><span class="co">#&gt; 2 A. baumannii AMK 0 0 0 0</span></span>
<span id="cb9-7"><a href="#cb9-7"></a><span class="co">#&gt; 3 A. baumannii AMP 0 0 3 3</span></span> <span id="cb10-7"><a href="#cb10-7"></a><span class="co">#&gt; 3 A. baumannii AMP 0 0 3 3</span></span>
<span id="cb9-8"><a href="#cb9-8"></a><span class="co">#&gt; 4 A. baumannii AMX 0 0 3 3</span></span> <span id="cb10-8"><a href="#cb10-8"></a><span class="co">#&gt; 4 A. baumannii AMX 0 0 3 3</span></span>
<span id="cb9-9"><a href="#cb9-9"></a><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Use 'format()' on this result to get a publicable/printable format.</span></span> <span id="cb10-9"><a href="#cb10-9"></a><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Use 'format()' on this result to get a publicable/printable format.</span></span>
<span id="cb9-10"><a href="#cb9-10"></a></span> <span id="cb10-10"><a href="#cb10-10"></a></span>
<span id="cb9-11"><a href="#cb9-11"></a><span class="co"># change the transformation with the FUN argument to anything you like:</span></span> <span id="cb10-11"><a href="#cb10-11"></a><span class="co"># change the transformation with the FUN argument to anything you like:</span></span>
<span id="cb9-12"><a href="#cb9-12"></a>x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/bug_drug_combinations.html">bug_drug_combinations</a></span>(example_isolates, <span class="dt">FUN =</span> mo_gramstain)</span> <span id="cb10-12"><a href="#cb10-12"></a>x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/bug_drug_combinations.html">bug_drug_combinations</a></span>(example_isolates, <span class="dt">FUN =</span> mo_gramstain)</span>
<span id="cb9-13"><a href="#cb9-13"></a><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `mo` as input for `col_mo`.</span></span> <span id="cb10-13"><a href="#cb10-13"></a><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `mo` as input for `col_mo`.</span></span>
<span id="cb9-14"><a href="#cb9-14"></a>x[<span class="dv">1</span><span class="op">:</span><span class="dv">4</span>, ]</span> <span id="cb10-14"><a href="#cb10-14"></a>x[<span class="dv">1</span><span class="op">:</span><span class="dv">4</span>, ]</span>
<span id="cb9-15"><a href="#cb9-15"></a><span class="co">#&gt; mo ab S I R total</span></span> <span id="cb10-15"><a href="#cb10-15"></a><span class="co">#&gt; mo ab S I R total</span></span>
<span id="cb9-16"><a href="#cb9-16"></a><span class="co">#&gt; 1 Gram-negative AMC 469 89 174 732</span></span> <span id="cb10-16"><a href="#cb10-16"></a><span class="co">#&gt; 1 Gram-negative AMC 469 89 174 732</span></span>
<span id="cb9-17"><a href="#cb9-17"></a><span class="co">#&gt; 2 Gram-negative AMK 251 0 2 253</span></span> <span id="cb10-17"><a href="#cb10-17"></a><span class="co">#&gt; 2 Gram-negative AMK 251 0 2 253</span></span>
<span id="cb9-18"><a href="#cb9-18"></a><span class="co">#&gt; 3 Gram-negative AMP 227 0 405 632</span></span> <span id="cb10-18"><a href="#cb10-18"></a><span class="co">#&gt; 3 Gram-negative AMP 227 0 405 632</span></span>
<span id="cb9-19"><a href="#cb9-19"></a><span class="co">#&gt; 4 Gram-negative AMX 227 0 405 632</span></span> <span id="cb10-19"><a href="#cb10-19"></a><span class="co">#&gt; 4 Gram-negative AMX 227 0 405 632</span></span>
<span id="cb9-20"><a href="#cb9-20"></a><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Use 'format()' on this result to get a publicable/printable format.</span></span></code></pre></div> <span id="cb10-20"><a href="#cb10-20"></a><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Use 'format()' on this result to get a publicable/printable format.</span></span></code></pre></div>
<p>You can format this to a printable format, ready for reporting or exporting to e.g. Excel with the base R <code><a href="https://rdrr.io/r/base/format.html">format()</a></code> function:</p> <p>You can format this to a printable format, ready for reporting or exporting to e.g. Excel with the base R <code><a href="https://rdrr.io/r/base/format.html">format()</a></code> function:</p>
<div class="sourceCode" id="cb10"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb10-1"><a href="#cb10-1"></a><span class="kw"><a href="https://rdrr.io/r/base/format.html">format</a></span>(x, <span class="dt">combine_IR =</span> <span class="ot">FALSE</span>)</span></code></pre></div> <div class="sourceCode" id="cb11"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb11-1"><a href="#cb11-1"></a><span class="kw"><a href="https://rdrr.io/r/base/format.html">format</a></span>(x, <span class="dt">combine_IR =</span> <span class="ot">FALSE</span>)</span></code></pre></div>
</li> </li>
<li> <li>
<p>Additional way to calculate co-resistance, i.e. when using multiple antimicrobials as input for <code>portion_*</code> functions or <code>count_*</code> functions. This can be used to determine the empiric susceptibility of a combination therapy. A new parameter <code>only_all_tested</code> (<strong>which defaults to <code>FALSE</code></strong>) replaces the old <code>also_single_tested</code> and can be used to select one of the two methods to count isolates and calculate portions. The difference can be seen in this example table (which is also on the <code>portion</code> and <code>count</code> help pages), where the %SI is being determined:</p> <p>Additional way to calculate co-resistance, i.e. when using multiple antimicrobials as input for <code>portion_*</code> functions or <code>count_*</code> functions. This can be used to determine the empiric susceptibility of a combination therapy. A new parameter <code>only_all_tested</code> (<strong>which defaults to <code>FALSE</code></strong>) replaces the old <code>also_single_tested</code> and can be used to select one of the two methods to count isolates and calculate portions. The difference can be seen in this example table (which is also on the <code>portion</code> and <code>count</code> help pages), where the %SI is being determined:</p>
<div class="sourceCode" id="cb11"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb11-1"><a href="#cb11-1"></a><span class="co"># --------------------------------------------------------------------</span></span> <div class="sourceCode" id="cb12"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb12-1"><a href="#cb12-1"></a><span class="co"># --------------------------------------------------------------------</span></span>
<span id="cb11-2"><a href="#cb11-2"></a><span class="co"># only_all_tested = FALSE only_all_tested = TRUE</span></span> <span id="cb12-2"><a href="#cb12-2"></a><span class="co"># only_all_tested = FALSE only_all_tested = TRUE</span></span>
<span id="cb11-3"><a href="#cb11-3"></a><span class="co"># ----------------------- -----------------------</span></span> <span id="cb12-3"><a href="#cb12-3"></a><span class="co"># ----------------------- -----------------------</span></span>
<span id="cb11-4"><a href="#cb11-4"></a><span class="co"># Drug A Drug B include as include as include as include as</span></span> <span id="cb12-4"><a href="#cb12-4"></a><span class="co"># Drug A Drug B include as include as include as include as</span></span>
<span id="cb11-5"><a href="#cb11-5"></a><span class="co"># numerator denominator numerator denominator</span></span> <span id="cb12-5"><a href="#cb12-5"></a><span class="co"># numerator denominator numerator denominator</span></span>
<span id="cb11-6"><a href="#cb11-6"></a><span class="co"># -------- -------- ---------- ----------- ---------- -----------</span></span> <span id="cb12-6"><a href="#cb12-6"></a><span class="co"># -------- -------- ---------- ----------- ---------- -----------</span></span>
<span id="cb11-7"><a href="#cb11-7"></a><span class="co"># S or I S or I X X X X</span></span> <span id="cb12-7"><a href="#cb12-7"></a><span class="co"># S or I S or I X X X X</span></span>
<span id="cb11-8"><a href="#cb11-8"></a><span class="co"># R S or I X X X X</span></span> <span id="cb12-8"><a href="#cb12-8"></a><span class="co"># R S or I X X X X</span></span>
<span id="cb11-9"><a href="#cb11-9"></a><span class="co"># &lt;NA&gt; S or I X X - -</span></span> <span id="cb12-9"><a href="#cb12-9"></a><span class="co"># &lt;NA&gt; S or I X X - -</span></span>
<span id="cb11-10"><a href="#cb11-10"></a><span class="co"># S or I R X X X X</span></span> <span id="cb12-10"><a href="#cb12-10"></a><span class="co"># S or I R X X X X</span></span>
<span id="cb11-11"><a href="#cb11-11"></a><span class="co"># R R - X - X</span></span> <span id="cb12-11"><a href="#cb12-11"></a><span class="co"># R R - X - X</span></span>
<span id="cb11-12"><a href="#cb11-12"></a><span class="co"># &lt;NA&gt; R - - - -</span></span> <span id="cb12-12"><a href="#cb12-12"></a><span class="co"># &lt;NA&gt; R - - - -</span></span>
<span id="cb11-13"><a href="#cb11-13"></a><span class="co"># S or I &lt;NA&gt; X X - -</span></span> <span id="cb12-13"><a href="#cb12-13"></a><span class="co"># S or I &lt;NA&gt; X X - -</span></span>
<span id="cb11-14"><a href="#cb11-14"></a><span class="co"># R &lt;NA&gt; - - - -</span></span> <span id="cb12-14"><a href="#cb12-14"></a><span class="co"># R &lt;NA&gt; - - - -</span></span>
<span id="cb11-15"><a href="#cb11-15"></a><span class="co"># &lt;NA&gt; &lt;NA&gt; - - - -</span></span> <span id="cb12-15"><a href="#cb12-15"></a><span class="co"># &lt;NA&gt; &lt;NA&gt; - - - -</span></span>
<span id="cb11-16"><a href="#cb11-16"></a><span class="co"># --------------------------------------------------------------------</span></span></code></pre></div> <span id="cb12-16"><a href="#cb12-16"></a><span class="co"># --------------------------------------------------------------------</span></span></code></pre></div>
<p>Since this is a major change, usage of the old <code>also_single_tested</code> will throw an informative error that it has been replaced by <code>only_all_tested</code>.</p> <p>Since this is a major change, usage of the old <code>also_single_tested</code> will throw an informative error that it has been replaced by <code>only_all_tested</code>.</p>
</li> </li>
<li> <li>
<p><code>tibble</code> printing support for classes <code>rsi</code>, <code>mic</code>, <code>disk</code>, <code>ab</code> <code>mo</code>. When using <code>tibble</code>s containing antimicrobial columns, values <code>S</code> will print in green, values <code>I</code> will print in yellow and values <code>R</code> will print in red. Microbial IDs (class <code>mo</code>) will emphasise on the genus and species, not on the kingdom.</p> <p><code>tibble</code> printing support for classes <code>rsi</code>, <code>mic</code>, <code>disk</code>, <code>ab</code> <code>mo</code>. When using <code>tibble</code>s containing antimicrobial columns, values <code>S</code> will print in green, values <code>I</code> will print in yellow and values <code>R</code> will print in red. Microbial IDs (class <code>mo</code>) will emphasise on the genus and species, not on the kingdom.</p>
<div class="sourceCode" id="cb12"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb12-1"><a href="#cb12-1"></a><span class="co"># (run this on your own console, as this page does not support colour printing)</span></span> <div class="sourceCode" id="cb13"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb13-1"><a href="#cb13-1"></a><span class="co"># (run this on your own console, as this page does not support colour printing)</span></span>
<span id="cb12-2"><a href="#cb12-2"></a><span class="kw"><a href="https://rdrr.io/r/base/library.html">library</a></span>(dplyr)</span> <span id="cb13-2"><a href="#cb13-2"></a><span class="kw"><a href="https://rdrr.io/r/base/library.html">library</a></span>(dplyr)</span>
<span id="cb12-3"><a href="#cb12-3"></a>example_isolates <span class="op">%&gt;%</span></span> <span id="cb13-3"><a href="#cb13-3"></a>example_isolates <span class="op">%&gt;%</span></span>
<span id="cb12-4"><a href="#cb12-4"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(mo<span class="op">:</span>AMC) <span class="op">%&gt;%</span><span class="st"> </span></span> <span id="cb13-4"><a href="#cb13-4"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(mo<span class="op">:</span>AMC) <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb12-5"><a href="#cb12-5"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/reexports.html">as_tibble</a></span>()</span></code></pre></div> <span id="cb13-5"><a href="#cb13-5"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/reexports.html">as_tibble</a></span>()</span></code></pre></div>
</li> </li>
</ul> </ul>
</div> </div>
<div id="changed" class="section level3"> <div id="changed-1" class="section level3">
<h3 class="hasAnchor"> <h3 class="hasAnchor">
<a href="#changed" class="anchor"></a>Changed</h3> <a href="#changed-1" class="anchor"></a>Changed</h3>
<ul> <ul>
<li>Many algorithm improvements for <code><a href="../reference/as.mo.html">as.mo()</a></code> (of which some led to additions to the <code>microorganisms</code> data set). Many thanks to all contributors that helped improving the algorithms. <li>Many algorithm improvements for <code><a href="../reference/as.mo.html">as.mo()</a></code> (of which some led to additions to the <code>microorganisms</code> data set). Many thanks to all contributors that helped improving the algorithms.
<ul> <ul>
@@ -562,14 +585,14 @@
<ul> <ul>
<li> <li>
<p>Function <code><a href="../reference/proportion.html">rsi_df()</a></code> to transform a <code>data.frame</code> to a data set containing only the microbial interpretation (S, I, R), the antibiotic, the percentage of S/I/R and the number of available isolates. This is a convenient combination of the existing functions <code><a href="../reference/count.html">count_df()</a></code> and <code><a href="../reference/AMR-deprecated.html">portion_df()</a></code> to immediately show resistance percentages and number of available isolates:</p> <p>Function <code><a href="../reference/proportion.html">rsi_df()</a></code> to transform a <code>data.frame</code> to a data set containing only the microbial interpretation (S, I, R), the antibiotic, the percentage of S/I/R and the number of available isolates. This is a convenient combination of the existing functions <code><a href="../reference/count.html">count_df()</a></code> and <code><a href="../reference/AMR-deprecated.html">portion_df()</a></code> to immediately show resistance percentages and number of available isolates:</p>
<div class="sourceCode" id="cb13"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb13-1"><a href="#cb13-1"></a>septic_patients <span class="op">%&gt;%</span></span> <div class="sourceCode" id="cb14"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb14-1"><a href="#cb14-1"></a>septic_patients <span class="op">%&gt;%</span></span>
<span id="cb13-2"><a href="#cb13-2"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(AMX, CIP) <span class="op">%&gt;%</span></span> <span id="cb14-2"><a href="#cb14-2"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(AMX, CIP) <span class="op">%&gt;%</span></span>
<span id="cb13-3"><a href="#cb13-3"></a><span class="st"> </span><span class="kw"><a href="../reference/proportion.html">rsi_df</a></span>()</span> <span id="cb14-3"><a href="#cb14-3"></a><span class="st"> </span><span class="kw"><a href="../reference/proportion.html">rsi_df</a></span>()</span>
<span id="cb13-4"><a href="#cb13-4"></a><span class="co"># antibiotic interpretation value isolates</span></span> <span id="cb14-4"><a href="#cb14-4"></a><span class="co"># antibiotic interpretation value isolates</span></span>
<span id="cb13-5"><a href="#cb13-5"></a><span class="co"># 1 Amoxicillin SI 0.4442636 546</span></span> <span id="cb14-5"><a href="#cb14-5"></a><span class="co"># 1 Amoxicillin SI 0.4442636 546</span></span>
<span id="cb13-6"><a href="#cb13-6"></a><span class="co"># 2 Amoxicillin R 0.5557364 683</span></span> <span id="cb14-6"><a href="#cb14-6"></a><span class="co"># 2 Amoxicillin R 0.5557364 683</span></span>
<span id="cb13-7"><a href="#cb13-7"></a><span class="co"># 3 Ciprofloxacin SI 0.8381831 1181</span></span> <span id="cb14-7"><a href="#cb14-7"></a><span class="co"># 3 Ciprofloxacin SI 0.8381831 1181</span></span>
<span id="cb13-8"><a href="#cb13-8"></a><span class="co"># 4 Ciprofloxacin R 0.1618169 228</span></span></code></pre></div> <span id="cb14-8"><a href="#cb14-8"></a><span class="co"># 4 Ciprofloxacin R 0.1618169 228</span></span></code></pre></div>
</li> </li>
<li> <li>
<p>Support for all scientifically published pathotypes of <em>E. coli</em> to date (that we could find). Supported are:</p> <p>Support for all scientifically published pathotypes of <em>E. coli</em> to date (that we could find). Supported are:</p>
@@ -587,20 +610,20 @@
<li>UPEC (Uropathogenic <em>E. coli</em>)</li> <li>UPEC (Uropathogenic <em>E. coli</em>)</li>
</ul> </ul>
<p>All these lead to the microbial ID of <em>E. coli</em>:</p> <p>All these lead to the microbial ID of <em>E. coli</em>:</p>
<div class="sourceCode" id="cb14"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb14-1"><a href="#cb14-1"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"UPEC"</span>)</span> <div class="sourceCode" id="cb15"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb15-1"><a href="#cb15-1"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"UPEC"</span>)</span>
<span id="cb14-2"><a href="#cb14-2"></a><span class="co"># B_ESCHR_COL</span></span> <span id="cb15-2"><a href="#cb15-2"></a><span class="co"># B_ESCHR_COL</span></span>
<span id="cb14-3"><a href="#cb14-3"></a><span class="kw"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="st">"UPEC"</span>)</span> <span id="cb15-3"><a href="#cb15-3"></a><span class="kw"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="st">"UPEC"</span>)</span>
<span id="cb14-4"><a href="#cb14-4"></a><span class="co"># "Escherichia coli"</span></span> <span id="cb15-4"><a href="#cb15-4"></a><span class="co"># "Escherichia coli"</span></span>
<span id="cb14-5"><a href="#cb14-5"></a><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"EHEC"</span>)</span> <span id="cb15-5"><a href="#cb15-5"></a><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"EHEC"</span>)</span>
<span id="cb14-6"><a href="#cb14-6"></a><span class="co"># "Gram-negative"</span></span></code></pre></div> <span id="cb15-6"><a href="#cb15-6"></a><span class="co"># "Gram-negative"</span></span></code></pre></div>
</li> </li>
<li><p>Function <code><a href="../reference/mo_property.html">mo_info()</a></code> as an analogy to <code><a href="../reference/ab_property.html">ab_info()</a></code>. The <code><a href="../reference/mo_property.html">mo_info()</a></code> prints a list with the full taxonomy, authors, and the URL to the online database of a microorganism</p></li> <li><p>Function <code><a href="../reference/mo_property.html">mo_info()</a></code> as an analogy to <code><a href="../reference/ab_property.html">ab_info()</a></code>. The <code><a href="../reference/mo_property.html">mo_info()</a></code> prints a list with the full taxonomy, authors, and the URL to the online database of a microorganism</p></li>
<li><p>Function <code><a href="../reference/mo_property.html">mo_synonyms()</a></code> to get all previously accepted taxonomic names of a microorganism</p></li> <li><p>Function <code><a href="../reference/mo_property.html">mo_synonyms()</a></code> to get all previously accepted taxonomic names of a microorganism</p></li>
</ul> </ul>
</div> </div>
<div id="changed-1" class="section level4"> <div id="changed-2" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#changed-1" class="anchor"></a>Changed</h4> <a href="#changed-2" class="anchor"></a>Changed</h4>
<ul> <ul>
<li>Column names of output <code><a href="../reference/count.html">count_df()</a></code> and <code><a href="../reference/AMR-deprecated.html">portion_df()</a></code> are now lowercase</li> <li>Column names of output <code><a href="../reference/count.html">count_df()</a></code> and <code><a href="../reference/AMR-deprecated.html">portion_df()</a></code> are now lowercase</li>
<li>Fixed bug in translation of microorganism names</li> <li>Fixed bug in translation of microorganism names</li>
@@ -647,9 +670,9 @@
<li>Added guidelines of the WHO to determine multi-drug resistance (MDR) for TB (<code><a href="../reference/mdro.html">mdr_tb()</a></code>) and added a new vignette about MDR. Read this tutorial <a href="https://msberends.gitlab.io/AMR/articles/MDR.html">here on our website</a>.</li> <li>Added guidelines of the WHO to determine multi-drug resistance (MDR) for TB (<code><a href="../reference/mdro.html">mdr_tb()</a></code>) and added a new vignette about MDR. Read this tutorial <a href="https://msberends.gitlab.io/AMR/articles/MDR.html">here on our website</a>.</li>
</ul> </ul>
</div> </div>
<div id="changed-2" class="section level4"> <div id="changed-3" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#changed-2" class="anchor"></a>Changed</h4> <a href="#changed-3" class="anchor"></a>Changed</h4>
<ul> <ul>
<li><p>Fixed a critical bug in <code><a href="../reference/first_isolate.html">first_isolate()</a></code> where missing species would lead to incorrect FALSEs. This bug was not present in AMR v0.5.0, but was in v0.6.0 and v0.6.1.</p></li> <li><p>Fixed a critical bug in <code><a href="../reference/first_isolate.html">first_isolate()</a></code> where missing species would lead to incorrect FALSEs. This bug was not present in AMR v0.5.0, but was in v0.6.0 and v0.6.1.</p></li>
<li><p>Fixed a bug in <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> where antibiotics from WHONET software would not be recognised</p></li> <li><p>Fixed a bug in <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> where antibiotics from WHONET software would not be recognised</p></li>
@@ -694,14 +717,14 @@
<li><p>when all values are unique it now shows a message instead of a warning</p></li> <li><p>when all values are unique it now shows a message instead of a warning</p></li>
<li> <li>
<p>support for boxplots:</p> <p>support for boxplots:</p>
<div class="sourceCode" id="cb15"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb15-1"><a href="#cb15-1"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span></span> <div class="sourceCode" id="cb16"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb16-1"><a href="#cb16-1"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb15-2"><a href="#cb15-2"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(age) <span class="op">%&gt;%</span><span class="st"> </span></span> <span id="cb16-2"><a href="#cb16-2"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(age) <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb15-3"><a href="#cb15-3"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/r/graphics/boxplot.html">boxplot</a></span>()</span> <span id="cb16-3"><a href="#cb16-3"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/r/graphics/boxplot.html">boxplot</a></span>()</span>
<span id="cb15-4"><a href="#cb15-4"></a><span class="co"># grouped boxplots:</span></span> <span id="cb16-4"><a href="#cb16-4"></a><span class="co"># grouped boxplots:</span></span>
<span id="cb15-5"><a href="#cb15-5"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span></span> <span id="cb16-5"><a href="#cb16-5"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb15-6"><a href="#cb15-6"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></span> <span id="cb16-6"><a href="#cb16-6"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb15-7"><a href="#cb15-7"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(age) <span class="op">%&gt;%</span></span> <span id="cb16-7"><a href="#cb16-7"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(age) <span class="op">%&gt;%</span></span>
<span id="cb15-8"><a href="#cb15-8"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/r/graphics/boxplot.html">boxplot</a></span>()</span></code></pre></div> <span id="cb16-8"><a href="#cb16-8"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/r/graphics/boxplot.html">boxplot</a></span>()</span></code></pre></div>
</li> </li>
</ul> </ul>
</li> </li>
@@ -734,9 +757,9 @@
<h1 class="page-header"> <h1 class="page-header">
<a href="#amr-061" class="anchor"></a>AMR 0.6.1<small> 2019-03-29 </small> <a href="#amr-061" class="anchor"></a>AMR 0.6.1<small> 2019-03-29 </small>
</h1> </h1>
<div id="changed-3" class="section level4"> <div id="changed-4" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#changed-3" class="anchor"></a>Changed</h4> <a href="#changed-4" class="anchor"></a>Changed</h4>
<ul> <ul>
<li>Fixed a critical bug when using <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> with <code>verbose = TRUE</code> <li>Fixed a critical bug when using <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> with <code>verbose = TRUE</code>
</li> </li>
@@ -785,32 +808,32 @@
</li> </li>
<li> <li>
<p>New filters for antimicrobial classes. Use these functions to filter isolates on results in one of more antibiotics from a specific class:</p> <p>New filters for antimicrobial classes. Use these functions to filter isolates on results in one of more antibiotics from a specific class:</p>
<div class="sourceCode" id="cb16"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb16-1"><a href="#cb16-1"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_aminoglycosides</a></span>()</span> <div class="sourceCode" id="cb17"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb17-1"><a href="#cb17-1"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_aminoglycosides</a></span>()</span>
<span id="cb16-2"><a href="#cb16-2"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_carbapenems</a></span>()</span> <span id="cb17-2"><a href="#cb17-2"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_carbapenems</a></span>()</span>
<span id="cb16-3"><a href="#cb16-3"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_cephalosporins</a></span>()</span> <span id="cb17-3"><a href="#cb17-3"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_cephalosporins</a></span>()</span>
<span id="cb16-4"><a href="#cb16-4"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_1st_cephalosporins</a></span>()</span> <span id="cb17-4"><a href="#cb17-4"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_1st_cephalosporins</a></span>()</span>
<span id="cb16-5"><a href="#cb16-5"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_2nd_cephalosporins</a></span>()</span> <span id="cb17-5"><a href="#cb17-5"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_2nd_cephalosporins</a></span>()</span>
<span id="cb16-6"><a href="#cb16-6"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_3rd_cephalosporins</a></span>()</span> <span id="cb17-6"><a href="#cb17-6"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_3rd_cephalosporins</a></span>()</span>
<span id="cb16-7"><a href="#cb16-7"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_4th_cephalosporins</a></span>()</span> <span id="cb17-7"><a href="#cb17-7"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_4th_cephalosporins</a></span>()</span>
<span id="cb16-8"><a href="#cb16-8"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_fluoroquinolones</a></span>()</span> <span id="cb17-8"><a href="#cb17-8"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_fluoroquinolones</a></span>()</span>
<span id="cb16-9"><a href="#cb16-9"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>()</span> <span id="cb17-9"><a href="#cb17-9"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>()</span>
<span id="cb16-10"><a href="#cb16-10"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_macrolides</a></span>()</span> <span id="cb17-10"><a href="#cb17-10"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_macrolides</a></span>()</span>
<span id="cb16-11"><a href="#cb16-11"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_tetracyclines</a></span>()</span></code></pre></div> <span id="cb17-11"><a href="#cb17-11"></a><span class="kw"><a href="../reference/filter_ab_class.html">filter_tetracyclines</a></span>()</span></code></pre></div>
<p>The <code>antibiotics</code> data set will be searched, after which the input data will be checked for column names with a value in any abbreviations, codes or official names found in the <code>antibiotics</code> data set. For example:</p> <p>The <code>antibiotics</code> data set will be searched, after which the input data will be checked for column names with a value in any abbreviations, codes or official names found in the <code>antibiotics</code> data set. For example:</p>
<div class="sourceCode" id="cb17"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb17-1"><a href="#cb17-1"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>(<span class="dt">result =</span> <span class="st">"R"</span>)</span> <div class="sourceCode" id="cb18"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb18-1"><a href="#cb18-1"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>(<span class="dt">result =</span> <span class="st">"R"</span>)</span>
<span id="cb17-2"><a href="#cb17-2"></a><span class="co"># Filtering on glycopeptide antibacterials: any of `vanc` or `teic` is R</span></span> <span id="cb18-2"><a href="#cb18-2"></a><span class="co"># Filtering on glycopeptide antibacterials: any of `vanc` or `teic` is R</span></span>
<span id="cb17-3"><a href="#cb17-3"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>(<span class="dt">result =</span> <span class="st">"R"</span>, <span class="dt">scope =</span> <span class="st">"all"</span>)</span> <span id="cb18-3"><a href="#cb18-3"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>(<span class="dt">result =</span> <span class="st">"R"</span>, <span class="dt">scope =</span> <span class="st">"all"</span>)</span>
<span id="cb17-4"><a href="#cb17-4"></a><span class="co"># Filtering on glycopeptide antibacterials: all of `vanc` and `teic` is R</span></span></code></pre></div> <span id="cb18-4"><a href="#cb18-4"></a><span class="co"># Filtering on glycopeptide antibacterials: all of `vanc` and `teic` is R</span></span></code></pre></div>
</li> </li>
<li> <li>
<p>All <code>ab_*</code> functions are deprecated and replaced by <code>atc_*</code> functions:</p> <p>All <code>ab_*</code> functions are deprecated and replaced by <code>atc_*</code> functions:</p>
<div class="sourceCode" id="cb18"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb18-1"><a href="#cb18-1"></a>ab_property -&gt;<span class="st"> </span><span class="kw">atc_property</span>()</span> <div class="sourceCode" id="cb19"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb19-1"><a href="#cb19-1"></a>ab_property -&gt;<span class="st"> </span><span class="kw">atc_property</span>()</span>
<span id="cb18-2"><a href="#cb18-2"></a>ab_name -&gt;<span class="st"> </span><span class="kw">atc_name</span>()</span> <span id="cb19-2"><a href="#cb19-2"></a>ab_name -&gt;<span class="st"> </span><span class="kw">atc_name</span>()</span>
<span id="cb18-3"><a href="#cb18-3"></a>ab_official -&gt;<span class="st"> </span><span class="kw">atc_official</span>()</span> <span id="cb19-3"><a href="#cb19-3"></a>ab_official -&gt;<span class="st"> </span><span class="kw">atc_official</span>()</span>
<span id="cb18-4"><a href="#cb18-4"></a>ab_trivial_nl -&gt;<span class="st"> </span><span class="kw">atc_trivial_nl</span>()</span> <span id="cb19-4"><a href="#cb19-4"></a>ab_trivial_nl -&gt;<span class="st"> </span><span class="kw">atc_trivial_nl</span>()</span>
<span id="cb18-5"><a href="#cb18-5"></a>ab_certe -&gt;<span class="st"> </span><span class="kw">atc_certe</span>()</span> <span id="cb19-5"><a href="#cb19-5"></a>ab_certe -&gt;<span class="st"> </span><span class="kw">atc_certe</span>()</span>
<span id="cb18-6"><a href="#cb18-6"></a>ab_umcg -&gt;<span class="st"> </span><span class="kw">atc_umcg</span>()</span> <span id="cb19-6"><a href="#cb19-6"></a>ab_umcg -&gt;<span class="st"> </span><span class="kw">atc_umcg</span>()</span>
<span id="cb18-7"><a href="#cb18-7"></a>ab_tradenames -&gt;<span class="st"> </span><span class="kw">atc_tradenames</span>()</span></code></pre></div> <span id="cb19-7"><a href="#cb19-7"></a>ab_tradenames -&gt;<span class="st"> </span><span class="kw">atc_tradenames</span>()</span></code></pre></div>
<p>These functions use <code>as.atc()</code> internally. The old <code>atc_property</code> has been renamed <code><a href="../reference/atc_online.html">atc_online_property()</a></code>. This is done for two reasons: firstly, not all ATC codes are of antibiotics (ab) but can also be of antivirals or antifungals. Secondly, the input must have class <code>atc</code> or must be coerable to this class. Properties of these classes should start with the same class name, analogous to <code><a href="../reference/as.mo.html">as.mo()</a></code> and e.g. <code>mo_genus</code>.</p> <p>These functions use <code>as.atc()</code> internally. The old <code>atc_property</code> has been renamed <code><a href="../reference/atc_online.html">atc_online_property()</a></code>. This is done for two reasons: firstly, not all ATC codes are of antibiotics (ab) but can also be of antivirals or antifungals. Secondly, the input must have class <code>atc</code> or must be coerable to this class. Properties of these classes should start with the same class name, analogous to <code><a href="../reference/as.mo.html">as.mo()</a></code> and e.g. <code>mo_genus</code>.</p>
</li> </li>
<li><p>New functions <code><a href="../reference/mo_source.html">set_mo_source()</a></code> and <code><a href="../reference/mo_source.html">get_mo_source()</a></code> to use your own predefined MO codes as input for <code><a href="../reference/as.mo.html">as.mo()</a></code> and consequently all <code>mo_*</code> functions</p></li> <li><p>New functions <code><a href="../reference/mo_source.html">set_mo_source()</a></code> and <code><a href="../reference/mo_source.html">get_mo_source()</a></code> to use your own predefined MO codes as input for <code><a href="../reference/as.mo.html">as.mo()</a></code> and consequently all <code>mo_*</code> functions</p></li>
@@ -823,28 +846,28 @@
<li><p>New function <code><a href="../reference/age_groups.html">age_groups()</a></code> to split ages into custom or predefined groups (like children or elderly). This allows for easier demographic antimicrobial resistance analysis per age group.</p></li> <li><p>New function <code><a href="../reference/age_groups.html">age_groups()</a></code> to split ages into custom or predefined groups (like children or elderly). This allows for easier demographic antimicrobial resistance analysis per age group.</p></li>
<li> <li>
<p>New function <code><a href="../reference/resistance_predict.html">ggplot_rsi_predict()</a></code> as well as the base R <code><a href="https://rdrr.io/r/graphics/plot.html">plot()</a></code> function can now be used for resistance prediction calculated with <code><a href="../reference/resistance_predict.html">resistance_predict()</a></code>:</p> <p>New function <code><a href="../reference/resistance_predict.html">ggplot_rsi_predict()</a></code> as well as the base R <code><a href="https://rdrr.io/r/graphics/plot.html">plot()</a></code> function can now be used for resistance prediction calculated with <code><a href="../reference/resistance_predict.html">resistance_predict()</a></code>:</p>
<div class="sourceCode" id="cb19"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb19-1"><a href="#cb19-1"></a>x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/resistance_predict.html">resistance_predict</a></span>(septic_patients, <span class="dt">col_ab =</span> <span class="st">"amox"</span>)</span> <div class="sourceCode" id="cb20"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb20-1"><a href="#cb20-1"></a>x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/resistance_predict.html">resistance_predict</a></span>(septic_patients, <span class="dt">col_ab =</span> <span class="st">"amox"</span>)</span>
<span id="cb19-2"><a href="#cb19-2"></a><span class="kw"><a href="https://rdrr.io/r/graphics/plot.html">plot</a></span>(x)</span> <span id="cb20-2"><a href="#cb20-2"></a><span class="kw"><a href="https://rdrr.io/r/graphics/plot.html">plot</a></span>(x)</span>
<span id="cb19-3"><a href="#cb19-3"></a><span class="kw"><a href="../reference/resistance_predict.html">ggplot_rsi_predict</a></span>(x)</span></code></pre></div> <span id="cb20-3"><a href="#cb20-3"></a><span class="kw"><a href="../reference/resistance_predict.html">ggplot_rsi_predict</a></span>(x)</span></code></pre></div>
</li> </li>
<li> <li>
<p>Functions <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> and <code><a href="../reference/first_isolate.html">filter_first_weighted_isolate()</a></code> to shorten and fasten filtering on data sets with antimicrobial results, e.g.:</p> <p>Functions <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> and <code><a href="../reference/first_isolate.html">filter_first_weighted_isolate()</a></code> to shorten and fasten filtering on data sets with antimicrobial results, e.g.:</p>
<div class="sourceCode" id="cb20"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb20-1"><a href="#cb20-1"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(...)</span> <div class="sourceCode" id="cb21"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb21-1"><a href="#cb21-1"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(...)</span>
<span id="cb20-2"><a href="#cb20-2"></a><span class="co"># or</span></span> <span id="cb21-2"><a href="#cb21-2"></a><span class="co"># or</span></span>
<span id="cb20-3"><a href="#cb20-3"></a><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(septic_patients, ...)</span></code></pre></div> <span id="cb21-3"><a href="#cb21-3"></a><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(septic_patients, ...)</span></code></pre></div>
<p>is equal to:</p> <p>is equal to:</p>
<div class="sourceCode" id="cb21"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb21-1"><a href="#cb21-1"></a>septic_patients <span class="op">%&gt;%</span></span> <div class="sourceCode" id="cb22"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb22-1"><a href="#cb22-1"></a>septic_patients <span class="op">%&gt;%</span></span>
<span id="cb21-2"><a href="#cb21-2"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="dt">only_firsts =</span> <span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(septic_patients, ...)) <span class="op">%&gt;%</span></span> <span id="cb22-2"><a href="#cb22-2"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="dt">only_firsts =</span> <span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(septic_patients, ...)) <span class="op">%&gt;%</span></span>
<span id="cb21-3"><a href="#cb21-3"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(only_firsts <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>) <span class="op">%&gt;%</span></span> <span id="cb22-3"><a href="#cb22-3"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(only_firsts <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>) <span class="op">%&gt;%</span></span>
<span id="cb21-4"><a href="#cb21-4"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(<span class="op">-</span>only_firsts)</span></code></pre></div> <span id="cb22-4"><a href="#cb22-4"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(<span class="op">-</span>only_firsts)</span></code></pre></div>
</li> </li>
<li><p>New function <code><a href="../reference/availability.html">availability()</a></code> to check the number of available (non-empty) results in a <code>data.frame</code></p></li> <li><p>New function <code><a href="../reference/availability.html">availability()</a></code> to check the number of available (non-empty) results in a <code>data.frame</code></p></li>
<li><p>New vignettes about how to conduct AMR analysis, predict antimicrobial resistance, use the <em>G</em>-test and more. These are also available (and even easier readable) on our website: <a href="https://msberends.gitlab.io/AMR" class="uri">https://msberends.gitlab.io/AMR</a>.</p></li> <li><p>New vignettes about how to conduct AMR analysis, predict antimicrobial resistance, use the <em>G</em>-test and more. These are also available (and even easier readable) on our website: <a href="https://msberends.gitlab.io/AMR" class="uri">https://msberends.gitlab.io/AMR</a>.</p></li>
</ul> </ul>
</div> </div>
<div id="changed-4" class="section level4"> <div id="changed-5" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#changed-4" class="anchor"></a>Changed</h4> <a href="#changed-5" class="anchor"></a>Changed</h4>
<ul> <ul>
<li>Function <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code>: <li>Function <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code>:
<ul> <ul>
@@ -864,33 +887,33 @@
<ul> <ul>
<li> <li>
<p>Now handles incorrect spelling, like <code>i</code> instead of <code>y</code> and <code>f</code> instead of <code>ph</code>:</p> <p>Now handles incorrect spelling, like <code>i</code> instead of <code>y</code> and <code>f</code> instead of <code>ph</code>:</p>
<div class="sourceCode" id="cb22"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb22-1"><a href="#cb22-1"></a><span class="co"># mo_fullname() uses as.mo() internally</span></span> <div class="sourceCode" id="cb23"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb23-1"><a href="#cb23-1"></a><span class="co"># mo_fullname() uses as.mo() internally</span></span>
<span id="cb22-2"><a href="#cb22-2"></a></span> <span id="cb23-2"><a href="#cb23-2"></a></span>
<span id="cb22-3"><a href="#cb22-3"></a><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"Sthafilokockus aaureuz"</span>)</span> <span id="cb23-3"><a href="#cb23-3"></a><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"Sthafilokockus aaureuz"</span>)</span>
<span id="cb22-4"><a href="#cb22-4"></a><span class="co">#&gt; [1] "Staphylococcus aureus"</span></span> <span id="cb23-4"><a href="#cb23-4"></a><span class="co">#&gt; [1] "Staphylococcus aureus"</span></span>
<span id="cb22-5"><a href="#cb22-5"></a></span> <span id="cb23-5"><a href="#cb23-5"></a></span>
<span id="cb22-6"><a href="#cb22-6"></a><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. klossi"</span>)</span> <span id="cb23-6"><a href="#cb23-6"></a><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. klossi"</span>)</span>
<span id="cb22-7"><a href="#cb22-7"></a><span class="co">#&gt; [1] "Staphylococcus kloosii"</span></span></code></pre></div> <span id="cb23-7"><a href="#cb23-7"></a><span class="co">#&gt; [1] "Staphylococcus kloosii"</span></span></code></pre></div>
</li> </li>
<li> <li>
<p>Uncertainty of the algorithm is now divided into four levels, 0 to 3, where the default <code>allow_uncertain = TRUE</code> is equal to uncertainty level 2. Run <code><a href="../reference/as.mo.html">?as.mo</a></code> for more info about these levels.</p> <p>Uncertainty of the algorithm is now divided into four levels, 0 to 3, where the default <code>allow_uncertain = TRUE</code> is equal to uncertainty level 2. Run <code><a href="../reference/as.mo.html">?as.mo</a></code> for more info about these levels.</p>
<div class="sourceCode" id="cb23"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb23-1"><a href="#cb23-1"></a><span class="co"># equal:</span></span> <div class="sourceCode" id="cb24"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb24-1"><a href="#cb24-1"></a><span class="co"># equal:</span></span>
<span id="cb23-2"><a href="#cb23-2"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="ot">TRUE</span>)</span> <span id="cb24-2"><a href="#cb24-2"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="ot">TRUE</span>)</span>
<span id="cb23-3"><a href="#cb23-3"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="dv">2</span>)</span> <span id="cb24-3"><a href="#cb24-3"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="dv">2</span>)</span>
<span id="cb23-4"><a href="#cb23-4"></a></span> <span id="cb24-4"><a href="#cb24-4"></a></span>
<span id="cb23-5"><a href="#cb23-5"></a><span class="co"># also equal:</span></span> <span id="cb24-5"><a href="#cb24-5"></a><span class="co"># also equal:</span></span>
<span id="cb23-6"><a href="#cb23-6"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="ot">FALSE</span>)</span> <span id="cb24-6"><a href="#cb24-6"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="ot">FALSE</span>)</span>
<span id="cb23-7"><a href="#cb23-7"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="dv">0</span>)</span></code></pre></div> <span id="cb24-7"><a href="#cb24-7"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="dv">0</span>)</span></code></pre></div>
<p>Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a></code> could lead to very unreliable results.</p> <p>Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a></code> could lead to very unreliable results.</p>
</li> </li>
<li><p>Implemented the latest publication of Becker <em>et al.</em> (2019), for categorising coagulase-negative <em>Staphylococci</em></p></li> <li><p>Implemented the latest publication of Becker <em>et al.</em> (2019), for categorising coagulase-negative <em>Staphylococci</em></p></li>
<li><p>All microbial IDs that found are now saved to a local file <code>~/.Rhistory_mo</code>. Use the new function <code>clean_mo_history()</code> to delete this file, which resets the algorithms.</p></li> <li><p>All microbial IDs that found are now saved to a local file <code>~/.Rhistory_mo</code>. Use the new function <code>clean_mo_history()</code> to delete this file, which resets the algorithms.</p></li>
<li> <li>
<p>Incoercible results will now be considered unknown, MO code <code>UNKNOWN</code>. On foreign systems, properties of these will be translated to all languages already previously supported: German, Dutch, French, Italian, Spanish and Portuguese:</p> <p>Incoercible results will now be considered unknown, MO code <code>UNKNOWN</code>. On foreign systems, properties of these will be translated to all languages already previously supported: German, Dutch, French, Italian, Spanish and Portuguese:</p>
<div class="sourceCode" id="cb24"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb24-1"><a href="#cb24-1"></a><span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(<span class="st">"qwerty"</span>, <span class="dt">language =</span> <span class="st">"es"</span>)</span> <div class="sourceCode" id="cb25"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb25-1"><a href="#cb25-1"></a><span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(<span class="st">"qwerty"</span>, <span class="dt">language =</span> <span class="st">"es"</span>)</span>
<span id="cb24-2"><a href="#cb24-2"></a><span class="co"># Warning: </span></span> <span id="cb25-2"><a href="#cb25-2"></a><span class="co"># Warning: </span></span>
<span id="cb24-3"><a href="#cb24-3"></a><span class="co"># one unique value (^= 100.0%) could not be coerced and is considered 'unknown': "qwerty". Use mo_failures() to review it.</span></span> <span id="cb25-3"><a href="#cb25-3"></a><span class="co"># one unique value (^= 100.0%) could not be coerced and is considered 'unknown': "qwerty". Use mo_failures() to review it.</span></span>
<span id="cb24-4"><a href="#cb24-4"></a><span class="co">#&gt; [1] "(género desconocido)"</span></span></code></pre></div> <span id="cb25-4"><a href="#cb25-4"></a><span class="co">#&gt; [1] "(género desconocido)"</span></span></code></pre></div>
</li> </li>
<li><p>Fix for vector containing only empty values</p></li> <li><p>Fix for vector containing only empty values</p></li>
<li><p>Finds better results when input is in other languages</p></li> <li><p>Finds better results when input is in other languages</p></li>
@@ -935,19 +958,19 @@
<ul> <ul>
<li> <li>
<p>Support for tidyverse quasiquotation! Now you can create frequency tables of function outcomes:</p> <p>Support for tidyverse quasiquotation! Now you can create frequency tables of function outcomes:</p>
<div class="sourceCode" id="cb25"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb25-1"><a href="#cb25-1"></a><span class="co"># Determine genus of microorganisms (mo) in `septic_patients` data set:</span></span> <div class="sourceCode" id="cb26"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb26-1"><a href="#cb26-1"></a><span class="co"># Determine genus of microorganisms (mo) in `septic_patients` data set:</span></span>
<span id="cb25-2"><a href="#cb25-2"></a><span class="co"># OLD WAY</span></span> <span id="cb26-2"><a href="#cb26-2"></a><span class="co"># OLD WAY</span></span>
<span id="cb25-3"><a href="#cb25-3"></a>septic_patients <span class="op">%&gt;%</span></span> <span id="cb26-3"><a href="#cb26-3"></a>septic_patients <span class="op">%&gt;%</span></span>
<span id="cb25-4"><a href="#cb25-4"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="dt">genus =</span> <span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo)) <span class="op">%&gt;%</span></span> <span id="cb26-4"><a href="#cb26-4"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="dt">genus =</span> <span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo)) <span class="op">%&gt;%</span></span>
<span id="cb25-5"><a href="#cb25-5"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(genus)</span> <span id="cb26-5"><a href="#cb26-5"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(genus)</span>
<span id="cb25-6"><a href="#cb25-6"></a><span class="co"># NEW WAY</span></span> <span id="cb26-6"><a href="#cb26-6"></a><span class="co"># NEW WAY</span></span>
<span id="cb25-7"><a href="#cb25-7"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span></span> <span id="cb26-7"><a href="#cb26-7"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb25-8"><a href="#cb25-8"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(<span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo))</span> <span id="cb26-8"><a href="#cb26-8"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(<span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo))</span>
<span id="cb25-9"><a href="#cb25-9"></a></span> <span id="cb26-9"><a href="#cb26-9"></a></span>
<span id="cb25-10"><a href="#cb25-10"></a><span class="co"># Even supports grouping variables:</span></span> <span id="cb26-10"><a href="#cb26-10"></a><span class="co"># Even supports grouping variables:</span></span>
<span id="cb25-11"><a href="#cb25-11"></a>septic_patients <span class="op">%&gt;%</span></span> <span id="cb26-11"><a href="#cb26-11"></a>septic_patients <span class="op">%&gt;%</span></span>
<span id="cb25-12"><a href="#cb25-12"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(gender) <span class="op">%&gt;%</span><span class="st"> </span></span> <span id="cb26-12"><a href="#cb26-12"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(gender) <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb25-13"><a href="#cb25-13"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(<span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo))</span></code></pre></div> <span id="cb26-13"><a href="#cb26-13"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(<span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo))</span></code></pre></div>
</li> </li>
<li><p>Header info is now available as a list, with the <code>header</code> function</p></li> <li><p>Header info is now available as a list, with the <code>header</code> function</p></li>
<li><p>The parameter <code>header</code> is now set to <code>TRUE</code> at default, even for markdown</p></li> <li><p>The parameter <code>header</code> is now set to <code>TRUE</code> at default, even for markdown</p></li>
@@ -994,9 +1017,9 @@
<li>Functions <code>mo_authors</code> and <code>mo_year</code> to get specific values about the scientific reference of a taxonomic entry</li> <li>Functions <code>mo_authors</code> and <code>mo_year</code> to get specific values about the scientific reference of a taxonomic entry</li>
</ul> </ul>
</div> </div>
<div id="changed-5" class="section level4"> <div id="changed-6" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#changed-5" class="anchor"></a>Changed</h4> <a href="#changed-6" class="anchor"></a>Changed</h4>
<ul> <ul>
<li><p>Functions <code>MDRO</code>, <code>BRMO</code>, <code>MRGN</code> and <code>EUCAST_exceptional_phenotypes</code> were renamed to <code>mdro</code>, <code>brmo</code>, <code>mrgn</code> and <code>eucast_exceptional_phenotypes</code></p></li> <li><p>Functions <code>MDRO</code>, <code>BRMO</code>, <code>MRGN</code> and <code>EUCAST_exceptional_phenotypes</code> were renamed to <code>mdro</code>, <code>brmo</code>, <code>mrgn</code> and <code>eucast_exceptional_phenotypes</code></p></li>
<li><p><code>EUCAST_rules</code> was renamed to <code>eucast_rules</code>, the old function still exists as a deprecated function</p></li> <li><p><code>EUCAST_rules</code> was renamed to <code>eucast_rules</code>, the old function still exists as a deprecated function</p></li>
@@ -1018,10 +1041,10 @@
<li><p>Fewer than 3 characters as input for <code>as.mo</code> will return NA</p></li> <li><p>Fewer than 3 characters as input for <code>as.mo</code> will return NA</p></li>
<li> <li>
<p>Function <code>as.mo</code> (and all <code>mo_*</code> wrappers) now supports genus abbreviations with “species” attached</p> <p>Function <code>as.mo</code> (and all <code>mo_*</code> wrappers) now supports genus abbreviations with “species” attached</p>
<div class="sourceCode" id="cb26"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb26-1"><a href="#cb26-1"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. species"</span>) <span class="co"># B_ESCHR</span></span> <div class="sourceCode" id="cb27"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb27-1"><a href="#cb27-1"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. species"</span>) <span class="co"># B_ESCHR</span></span>
<span id="cb26-2"><a href="#cb26-2"></a><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"E. spp."</span>) <span class="co"># "Escherichia species"</span></span> <span id="cb27-2"><a href="#cb27-2"></a><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"E. spp."</span>) <span class="co"># "Escherichia species"</span></span>
<span id="cb26-3"><a href="#cb26-3"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S. spp"</span>) <span class="co"># B_STPHY</span></span> <span id="cb27-3"><a href="#cb27-3"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S. spp"</span>) <span class="co"># B_STPHY</span></span>
<span id="cb26-4"><a href="#cb26-4"></a><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. species"</span>) <span class="co"># "Staphylococcus species"</span></span></code></pre></div> <span id="cb27-4"><a href="#cb27-4"></a><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. species"</span>) <span class="co"># "Staphylococcus species"</span></span></code></pre></div>
</li> </li>
<li><p>Added parameter <code>combine_IR</code> (TRUE/FALSE) to functions <code>portion_df</code> and <code>count_df</code>, to indicate that all values of I and R must be merged into one, so the output only consists of S vs. IR (susceptible vs. non-susceptible)</p></li> <li><p>Added parameter <code>combine_IR</code> (TRUE/FALSE) to functions <code>portion_df</code> and <code>count_df</code>, to indicate that all values of I and R must be merged into one, so the output only consists of S vs. IR (susceptible vs. non-susceptible)</p></li>
<li><p>Fix for <code>portion_*(..., as_percent = TRUE)</code> when minimal number of isolates would not be met</p></li> <li><p>Fix for <code>portion_*(..., as_percent = TRUE)</code> when minimal number of isolates would not be met</p></li>
@@ -1033,15 +1056,15 @@
<ul> <ul>
<li> <li>
<p>Support for grouping variables, test with:</p> <p>Support for grouping variables, test with:</p>
<div class="sourceCode" id="cb27"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb27-1"><a href="#cb27-1"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span></span> <div class="sourceCode" id="cb28"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb28-1"><a href="#cb28-1"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb27-2"><a href="#cb27-2"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></span> <span id="cb28-2"><a href="#cb28-2"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb27-3"><a href="#cb27-3"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(gender)</span></code></pre></div> <span id="cb28-3"><a href="#cb28-3"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(gender)</span></code></pre></div>
</li> </li>
<li> <li>
<p>Support for (un)selecting columns:</p> <p>Support for (un)selecting columns:</p>
<div class="sourceCode" id="cb28"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb28-1"><a href="#cb28-1"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span></span> <div class="sourceCode" id="cb29"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb29-1"><a href="#cb29-1"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb28-2"><a href="#cb28-2"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></span> <span id="cb29-2"><a href="#cb29-2"></a><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></span>
<span id="cb28-3"><a href="#cb28-3"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(<span class="op">-</span>count, <span class="op">-</span>cum_count) <span class="co"># only get item, percent, cum_percent</span></span></code></pre></div> <span id="cb29-3"><a href="#cb29-3"></a><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(<span class="op">-</span>count, <span class="op">-</span>cum_count) <span class="co"># only get item, percent, cum_percent</span></span></code></pre></div>
</li> </li>
<li><p>Check for <code><a href="https://hms.tidyverse.org/reference/Deprecated.html">hms::is.hms</a></code></p></li> <li><p>Check for <code><a href="https://hms.tidyverse.org/reference/Deprecated.html">hms::is.hms</a></code></p></li>
<li><p>Now prints in markdown at default in non-interactive sessions</p></li> <li><p>Now prints in markdown at default in non-interactive sessions</p></li>
@@ -1117,18 +1140,18 @@
</li> </li>
</ul> </ul>
<p>They also come with support for German, Dutch, French, Italian, Spanish and Portuguese:</p> <p>They also come with support for German, Dutch, French, Italian, Spanish and Portuguese:</p>
<div class="sourceCode" id="cb29"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb29-1"><a href="#cb29-1"></a><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>)</span> <div class="sourceCode" id="cb30"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb30-1"><a href="#cb30-1"></a><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>)</span>
<span id="cb29-2"><a href="#cb29-2"></a><span class="co"># [1] "Gram negative"</span></span> <span id="cb30-2"><a href="#cb30-2"></a><span class="co"># [1] "Gram negative"</span></span>
<span id="cb29-3"><a href="#cb29-3"></a><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"de"</span>) <span class="co"># German</span></span> <span id="cb30-3"><a href="#cb30-3"></a><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"de"</span>) <span class="co"># German</span></span>
<span id="cb29-4"><a href="#cb29-4"></a><span class="co"># [1] "Gramnegativ"</span></span> <span id="cb30-4"><a href="#cb30-4"></a><span class="co"># [1] "Gramnegativ"</span></span>
<span id="cb29-5"><a href="#cb29-5"></a><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"es"</span>) <span class="co"># Spanish</span></span> <span id="cb30-5"><a href="#cb30-5"></a><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"es"</span>) <span class="co"># Spanish</span></span>
<span id="cb29-6"><a href="#cb29-6"></a><span class="co"># [1] "Gram negativo"</span></span> <span id="cb30-6"><a href="#cb30-6"></a><span class="co"># [1] "Gram negativo"</span></span>
<span id="cb29-7"><a href="#cb29-7"></a><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. group A"</span>, <span class="dt">language =</span> <span class="st">"pt"</span>) <span class="co"># Portuguese</span></span> <span id="cb30-7"><a href="#cb30-7"></a><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. group A"</span>, <span class="dt">language =</span> <span class="st">"pt"</span>) <span class="co"># Portuguese</span></span>
<span id="cb29-8"><a href="#cb29-8"></a><span class="co"># [1] "Streptococcus grupo A"</span></span></code></pre></div> <span id="cb30-8"><a href="#cb30-8"></a><span class="co"># [1] "Streptococcus grupo A"</span></span></code></pre></div>
<p>Furthermore, former taxonomic names will give a note about the current taxonomic name:</p> <p>Furthermore, former taxonomic names will give a note about the current taxonomic name:</p>
<div class="sourceCode" id="cb30"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb30-1"><a href="#cb30-1"></a><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"Esc blattae"</span>)</span> <div class="sourceCode" id="cb31"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb31-1"><a href="#cb31-1"></a><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"Esc blattae"</span>)</span>
<span id="cb30-2"><a href="#cb30-2"></a><span class="co"># Note: 'Escherichia blattae' (Burgess et al., 1973) was renamed 'Shimwellia blattae' (Priest and Barker, 2010)</span></span> <span id="cb31-2"><a href="#cb31-2"></a><span class="co"># Note: 'Escherichia blattae' (Burgess et al., 1973) was renamed 'Shimwellia blattae' (Priest and Barker, 2010)</span></span>
<span id="cb30-3"><a href="#cb30-3"></a><span class="co"># [1] "Gram negative"</span></span></code></pre></div> <span id="cb31-3"><a href="#cb31-3"></a><span class="co"># [1] "Gram negative"</span></span></code></pre></div>
</li> </li>
<li> <li>
<p>Functions <code>count_R</code>, <code>count_IR</code>, <code>count_I</code>, <code>count_SI</code> and <code>count_S</code> to selectively count resistant or susceptible isolates</p> <p>Functions <code>count_R</code>, <code>count_IR</code>, <code>count_I</code>, <code>count_SI</code> and <code>count_S</code> to selectively count resistant or susceptible isolates</p>
@@ -1139,18 +1162,18 @@
<li><p>Function <code>is.rsi.eligible</code> to check for columns that have valid antimicrobial results, but do not have the <code>rsi</code> class yet. Transform the columns of your raw data with: <code>data %&gt;% mutate_if(is.rsi.eligible, as.rsi)</code></p></li> <li><p>Function <code>is.rsi.eligible</code> to check for columns that have valid antimicrobial results, but do not have the <code>rsi</code> class yet. Transform the columns of your raw data with: <code>data %&gt;% mutate_if(is.rsi.eligible, as.rsi)</code></p></li>
<li> <li>
<p>Functions <code>as.mo</code> and <code>is.mo</code> as replacements for <code>as.bactid</code> and <code>is.bactid</code> (since the <code>microoganisms</code> data set not only contains bacteria). These last two functions are deprecated and will be removed in a future release. The <code>as.mo</code> function determines microbial IDs using intelligent rules:</p> <p>Functions <code>as.mo</code> and <code>is.mo</code> as replacements for <code>as.bactid</code> and <code>is.bactid</code> (since the <code>microoganisms</code> data set not only contains bacteria). These last two functions are deprecated and will be removed in a future release. The <code>as.mo</code> function determines microbial IDs using intelligent rules:</p>
<div class="sourceCode" id="cb31"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb31-1"><a href="#cb31-1"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. coli"</span>)</span> <div class="sourceCode" id="cb32"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb32-1"><a href="#cb32-1"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. coli"</span>)</span>
<span id="cb31-2"><a href="#cb31-2"></a><span class="co"># [1] B_ESCHR_COL</span></span> <span id="cb32-2"><a href="#cb32-2"></a><span class="co"># [1] B_ESCHR_COL</span></span>
<span id="cb31-3"><a href="#cb31-3"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"MRSA"</span>)</span> <span id="cb32-3"><a href="#cb32-3"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"MRSA"</span>)</span>
<span id="cb31-4"><a href="#cb31-4"></a><span class="co"># [1] B_STPHY_AUR</span></span> <span id="cb32-4"><a href="#cb32-4"></a><span class="co"># [1] B_STPHY_AUR</span></span>
<span id="cb31-5"><a href="#cb31-5"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S group A"</span>)</span> <span id="cb32-5"><a href="#cb32-5"></a><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S group A"</span>)</span>
<span id="cb31-6"><a href="#cb31-6"></a><span class="co"># [1] B_STRPTC_GRA</span></span></code></pre></div> <span id="cb32-6"><a href="#cb32-6"></a><span class="co"># [1] B_STRPTC_GRA</span></span></code></pre></div>
<p>And with great speed too - on a quite regular Linux server from 2007 it takes us less than 0.02 seconds to transform 25,000 items:</p> <p>And with great speed too - on a quite regular Linux server from 2007 it takes us less than 0.02 seconds to transform 25,000 items:</p>
<div class="sourceCode" id="cb32"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb32-1"><a href="#cb32-1"></a>thousands_of_E_colis &lt;-<span class="st"> </span><span class="kw"><a href="https://rdrr.io/r/base/rep.html">rep</a></span>(<span class="st">"E. coli"</span>, <span class="dv">25000</span>)</span> <div class="sourceCode" id="cb33"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb33-1"><a href="#cb33-1"></a>thousands_of_E_colis &lt;-<span class="st"> </span><span class="kw"><a href="https://rdrr.io/r/base/rep.html">rep</a></span>(<span class="st">"E. coli"</span>, <span class="dv">25000</span>)</span>
<span id="cb32-2"><a href="#cb32-2"></a>microbenchmark<span class="op">::</span><span class="kw"><a href="https://rdrr.io/pkg/microbenchmark/man/microbenchmark.html">microbenchmark</a></span>(<span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(thousands_of_E_colis), <span class="dt">unit =</span> <span class="st">"s"</span>)</span> <span id="cb33-2"><a href="#cb33-2"></a>microbenchmark<span class="op">::</span><span class="kw"><a href="https://rdrr.io/pkg/microbenchmark/man/microbenchmark.html">microbenchmark</a></span>(<span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(thousands_of_E_colis), <span class="dt">unit =</span> <span class="st">"s"</span>)</span>
<span id="cb32-3"><a href="#cb32-3"></a><span class="co"># Unit: seconds</span></span> <span id="cb33-3"><a href="#cb33-3"></a><span class="co"># Unit: seconds</span></span>
<span id="cb32-4"><a href="#cb32-4"></a><span class="co"># min median max neval</span></span> <span id="cb33-4"><a href="#cb33-4"></a><span class="co"># min median max neval</span></span>
<span id="cb32-5"><a href="#cb32-5"></a><span class="co"># 0.01817717 0.01843957 0.03878077 100</span></span></code></pre></div> <span id="cb33-5"><a href="#cb33-5"></a><span class="co"># 0.01817717 0.01843957 0.03878077 100</span></span></code></pre></div>
</li> </li>
<li><p>Added parameter <code>reference_df</code> for <code>as.mo</code>, so users can supply their own microbial IDs, name or codes as a reference table</p></li> <li><p>Added parameter <code>reference_df</code> for <code>as.mo</code>, so users can supply their own microbial IDs, name or codes as a reference table</p></li>
<li> <li>
@@ -1171,19 +1194,19 @@
<li><p>Renamed <code>septic_patients$sex</code> to <code>septic_patients$gender</code></p></li> <li><p>Renamed <code>septic_patients$sex</code> to <code>septic_patients$gender</code></p></li>
</ul> </ul>
</div> </div>
<div id="changed-6" class="section level4"> <div id="changed-7" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#changed-6" class="anchor"></a>Changed</h4> <a href="#changed-7" class="anchor"></a>Changed</h4>
<ul> <ul>
<li><p>Added three antimicrobial agents to the <code>antibiotics</code> data set: Terbinafine (D01BA02), Rifaximin (A07AA11) and Isoconazole (D01AC05)</p></li> <li><p>Added three antimicrobial agents to the <code>antibiotics</code> data set: Terbinafine (D01BA02), Rifaximin (A07AA11) and Isoconazole (D01AC05)</p></li>
<li> <li>
<p>Added 163 trade names to the <code>antibiotics</code> data set, it now contains 298 different trade names in total, e.g.:</p> <p>Added 163 trade names to the <code>antibiotics</code> data set, it now contains 298 different trade names in total, e.g.:</p>
<div class="sourceCode" id="cb33"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb33-1"><a href="#cb33-1"></a><span class="kw">ab_official</span>(<span class="st">"Bactroban"</span>)</span> <div class="sourceCode" id="cb34"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb34-1"><a href="#cb34-1"></a><span class="kw">ab_official</span>(<span class="st">"Bactroban"</span>)</span>
<span id="cb33-2"><a href="#cb33-2"></a><span class="co"># [1] "Mupirocin"</span></span> <span id="cb34-2"><a href="#cb34-2"></a><span class="co"># [1] "Mupirocin"</span></span>
<span id="cb33-3"><a href="#cb33-3"></a><span class="kw"><a href="../reference/ab_property.html">ab_name</a></span>(<span class="kw"><a href="https://rdrr.io/r/base/c.html">c</a></span>(<span class="st">"Bactroban"</span>, <span class="st">"Amoxil"</span>, <span class="st">"Zithromax"</span>, <span class="st">"Floxapen"</span>))</span> <span id="cb34-3"><a href="#cb34-3"></a><span class="kw"><a href="../reference/ab_property.html">ab_name</a></span>(<span class="kw"><a href="https://rdrr.io/r/base/c.html">c</a></span>(<span class="st">"Bactroban"</span>, <span class="st">"Amoxil"</span>, <span class="st">"Zithromax"</span>, <span class="st">"Floxapen"</span>))</span>
<span id="cb33-4"><a href="#cb33-4"></a><span class="co"># [1] "Mupirocin" "Amoxicillin" "Azithromycin" "Flucloxacillin"</span></span> <span id="cb34-4"><a href="#cb34-4"></a><span class="co"># [1] "Mupirocin" "Amoxicillin" "Azithromycin" "Flucloxacillin"</span></span>
<span id="cb33-5"><a href="#cb33-5"></a><span class="kw"><a href="../reference/ab_property.html">ab_atc</a></span>(<span class="kw"><a href="https://rdrr.io/r/base/c.html">c</a></span>(<span class="st">"Bactroban"</span>, <span class="st">"Amoxil"</span>, <span class="st">"Zithromax"</span>, <span class="st">"Floxapen"</span>))</span> <span id="cb34-5"><a href="#cb34-5"></a><span class="kw"><a href="../reference/ab_property.html">ab_atc</a></span>(<span class="kw"><a href="https://rdrr.io/r/base/c.html">c</a></span>(<span class="st">"Bactroban"</span>, <span class="st">"Amoxil"</span>, <span class="st">"Zithromax"</span>, <span class="st">"Floxapen"</span>))</span>
<span id="cb33-6"><a href="#cb33-6"></a><span class="co"># [1] "R01AX06" "J01CA04" "J01FA10" "J01CF05"</span></span></code></pre></div> <span id="cb34-6"><a href="#cb34-6"></a><span class="co"># [1] "R01AX06" "J01CA04" "J01FA10" "J01CF05"</span></span></code></pre></div>
</li> </li>
<li><p>For <code>first_isolate</code>, rows will be ignored when theres no species available</p></li> <li><p>For <code>first_isolate</code>, rows will be ignored when theres no species available</p></li>
<li><p>Function <code>ratio</code> is now deprecated and will be removed in a future release, as it is not really the scope of this package</p></li> <li><p>Function <code>ratio</code> is now deprecated and will be removed in a future release, as it is not really the scope of this package</p></li>
@@ -1193,13 +1216,13 @@
<li><p>Added parameters <code>minimum</code> and <code>as_percent</code> to <code>portion_df</code></p></li> <li><p>Added parameters <code>minimum</code> and <code>as_percent</code> to <code>portion_df</code></p></li>
<li> <li>
<p>Support for quasiquotation in the functions series <code>count_*</code> and <code>portions_*</code>, and <code>n_rsi</code>. This allows to check for more than 2 vectors or columns.</p> <p>Support for quasiquotation in the functions series <code>count_*</code> and <code>portions_*</code>, and <code>n_rsi</code>. This allows to check for more than 2 vectors or columns.</p>
<div class="sourceCode" id="cb34"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb34-1"><a href="#cb34-1"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(amox, cipr) <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>()</span> <div class="sourceCode" id="cb35"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb35-1"><a href="#cb35-1"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(amox, cipr) <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>()</span>
<span id="cb34-2"><a href="#cb34-2"></a><span class="co"># which is the same as:</span></span> <span id="cb35-2"><a href="#cb35-2"></a><span class="co"># which is the same as:</span></span>
<span id="cb34-3"><a href="#cb34-3"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>(amox, cipr)</span> <span id="cb35-3"><a href="#cb35-3"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>(amox, cipr)</span>
<span id="cb34-4"><a href="#cb34-4"></a></span> <span id="cb35-4"><a href="#cb35-4"></a></span>
<span id="cb34-5"><a href="#cb34-5"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">portion_S</a></span>(amcl)</span> <span id="cb35-5"><a href="#cb35-5"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">portion_S</a></span>(amcl)</span>
<span id="cb34-6"><a href="#cb34-6"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">portion_S</a></span>(amcl, gent)</span> <span id="cb35-6"><a href="#cb35-6"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">portion_S</a></span>(amcl, gent)</span>
<span id="cb34-7"><a href="#cb34-7"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">portion_S</a></span>(amcl, gent, pita)</span></code></pre></div> <span id="cb35-7"><a href="#cb35-7"></a>septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">portion_S</a></span>(amcl, gent, pita)</span></code></pre></div>
</li> </li>
<li><p>Edited <code>ggplot_rsi</code> and <code>geom_rsi</code> so they can cope with <code>count_df</code>. The new <code>fun</code> parameter has value <code>portion_df</code> at default, but can be set to <code>count_df</code>.</p></li> <li><p>Edited <code>ggplot_rsi</code> and <code>geom_rsi</code> so they can cope with <code>count_df</code>. The new <code>fun</code> parameter has value <code>portion_df</code> at default, but can be set to <code>count_df</code>.</p></li>
<li><p>Fix for <code>ggplot_rsi</code> when the <code>ggplot2</code> package was not loaded</p></li> <li><p>Fix for <code>ggplot_rsi</code> when the <code>ggplot2</code> package was not loaded</p></li>
@@ -1211,12 +1234,12 @@
<li><p>Added longest en shortest character length in the frequency table (<code>freq</code>) header of class <code>character</code></p></li> <li><p>Added longest en shortest character length in the frequency table (<code>freq</code>) header of class <code>character</code></p></li>
<li> <li>
<p>Support for types (classes) list and matrix for <code>freq</code></p> <p>Support for types (classes) list and matrix for <code>freq</code></p>
<div class="sourceCode" id="cb35"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb35-1"><a href="#cb35-1"></a>my_matrix =<span class="st"> </span><span class="kw"><a href="https://rdrr.io/r/base/with.html">with</a></span>(septic_patients, <span class="kw"><a href="https://rdrr.io/r/base/matrix.html">matrix</a></span>(<span class="kw"><a href="https://rdrr.io/r/base/c.html">c</a></span>(age, gender), <span class="dt">ncol =</span> <span class="dv">2</span>))</span> <div class="sourceCode" id="cb36"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb36-1"><a href="#cb36-1"></a>my_matrix =<span class="st"> </span><span class="kw"><a href="https://rdrr.io/r/base/with.html">with</a></span>(septic_patients, <span class="kw"><a href="https://rdrr.io/r/base/matrix.html">matrix</a></span>(<span class="kw"><a href="https://rdrr.io/r/base/c.html">c</a></span>(age, gender), <span class="dt">ncol =</span> <span class="dv">2</span>))</span>
<span id="cb35-2"><a href="#cb35-2"></a><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(my_matrix)</span></code></pre></div> <span id="cb36-2"><a href="#cb36-2"></a><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(my_matrix)</span></code></pre></div>
<p>For lists, subsetting is possible:</p> <p>For lists, subsetting is possible:</p>
<div class="sourceCode" id="cb36"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb36-1"><a href="#cb36-1"></a>my_list =<span class="st"> </span><span class="kw"><a href="https://rdrr.io/r/base/list.html">list</a></span>(<span class="dt">age =</span> septic_patients<span class="op">$</span>age, <span class="dt">gender =</span> septic_patients<span class="op">$</span>gender)</span> <div class="sourceCode" id="cb37"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb37-1"><a href="#cb37-1"></a>my_list =<span class="st"> </span><span class="kw"><a href="https://rdrr.io/r/base/list.html">list</a></span>(<span class="dt">age =</span> septic_patients<span class="op">$</span>age, <span class="dt">gender =</span> septic_patients<span class="op">$</span>gender)</span>
<span id="cb36-2"><a href="#cb36-2"></a>my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(age)</span> <span id="cb37-2"><a href="#cb37-2"></a>my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(age)</span>
<span id="cb36-3"><a href="#cb36-3"></a>my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(gender)</span></code></pre></div> <span id="cb37-3"><a href="#cb37-3"></a>my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(gender)</span></code></pre></div>
</li> </li>
</ul> </ul>
</div> </div>
@@ -1305,9 +1328,9 @@
</li> </li>
</ul> </ul>
</div> </div>
<div id="changed-7" class="section level4"> <div id="changed-8" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#changed-7" class="anchor"></a>Changed</h4> <a href="#changed-8" class="anchor"></a>Changed</h4>
<ul> <ul>
<li>Improvements for forecasting with <code>resistance_predict</code> and added more examples</li> <li>Improvements for forecasting with <code>resistance_predict</code> and added more examples</li>
<li>More antibiotics added as parameters for EUCAST rules</li> <li>More antibiotics added as parameters for EUCAST rules</li>
@@ -1391,9 +1414,9 @@
<li>New print format for <code>tibble</code>s and <code>data.table</code>s</li> <li>New print format for <code>tibble</code>s and <code>data.table</code>s</li>
</ul> </ul>
</div> </div>
<div id="changed-8" class="section level4"> <div id="changed-9" class="section level4">
<h4 class="hasAnchor"> <h4 class="hasAnchor">
<a href="#changed-8" class="anchor"></a>Changed</h4> <a href="#changed-9" class="anchor"></a>Changed</h4>
<ul> <ul>
<li>Fixed <code>rsi</code> class for vectors that contain only invalid antimicrobial interpretations</li> <li>Fixed <code>rsi</code> class for vectors that contain only invalid antimicrobial interpretations</li>
<li>Renamed dataset <code>ablist</code> to <code>antibiotics</code> <li>Renamed dataset <code>ablist</code> to <code>antibiotics</code>
@@ -1450,7 +1473,8 @@
<div id="tocnav"> <div id="tocnav">
<h2>Contents</h2> <h2>Contents</h2>
<ul class="nav nav-pills nav-stacked"> <ul class="nav nav-pills nav-stacked">
<li><a href="#amr-0909027">0.9.0.9027</a></li> <li><a href="#amr-1009000">1.0.0.9000</a></li>
<li><a href="#amr-100">1.0.0</a></li>
<li><a href="#amr-090">0.9.0</a></li> <li><a href="#amr-090">0.9.0</a></li>
<li><a href="#amr-080">0.8.0</a></li> <li><a href="#amr-080">0.8.0</a></li>
<li><a href="#amr-071">0.7.1</a></li> <li><a href="#amr-071">0.7.1</a></li>

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

@@ -79,7 +79,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9025</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9029</span>
</span> </span>
</div> </div>
@@ -228,13 +228,27 @@
<pre class="usage"><span class='fu'>as.rsi</span>(<span class='no'>x</span>, <span class='no'>...</span>) <pre class="usage"><span class='fu'>as.rsi</span>(<span class='no'>x</span>, <span class='no'>...</span>)
<span class='co'># S3 method for mic</span> <span class='co'># S3 method for mic</span>
<span class='fu'>as.rsi</span>(<span class='no'>x</span>, <span class='no'>mo</span>, <span class='no'>ab</span>, <span class='kw'>guideline</span> <span class='kw'>=</span> <span class='st'>"EUCAST"</span>, <span class='no'>...</span>) <span class='fu'>as.rsi</span>(
<span class='no'>x</span>,
<span class='no'>mo</span>,
<span class='kw'>ab</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/deparse.html'>deparse</a></span>(<span class='fu'><a href='https://rdrr.io/r/base/substitute.html'>substitute</a></span>(<span class='no'>x</span>)),
<span class='kw'>guideline</span> <span class='kw'>=</span> <span class='st'>"EUCAST"</span>,
<span class='kw'>uti</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>,
<span class='no'>...</span>
)
<span class='co'># S3 method for disk</span> <span class='co'># S3 method for disk</span>
<span class='fu'>as.rsi</span>(<span class='no'>x</span>, <span class='no'>mo</span>, <span class='no'>ab</span>, <span class='kw'>guideline</span> <span class='kw'>=</span> <span class='st'>"EUCAST"</span>, <span class='no'>...</span>) <span class='fu'>as.rsi</span>(
<span class='no'>x</span>,
<span class='no'>mo</span>,
<span class='kw'>ab</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/deparse.html'>deparse</a></span>(<span class='fu'><a href='https://rdrr.io/r/base/substitute.html'>substitute</a></span>(<span class='no'>x</span>)),
<span class='kw'>guideline</span> <span class='kw'>=</span> <span class='st'>"EUCAST"</span>,
<span class='kw'>uti</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>,
<span class='no'>...</span>
)
<span class='co'># S3 method for data.frame</span> <span class='co'># S3 method for data.frame</span>
<span class='fu'>as.rsi</span>(<span class='no'>x</span>, <span class='kw'>col_mo</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>guideline</span> <span class='kw'>=</span> <span class='st'>"EUCAST"</span>, <span class='no'>...</span>) <span class='fu'>as.rsi</span>(<span class='no'>x</span>, <span class='kw'>col_mo</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>guideline</span> <span class='kw'>=</span> <span class='st'>"EUCAST"</span>, <span class='kw'>uti</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='no'>...</span>)
<span class='fu'>is.rsi</span>(<span class='no'>x</span>) <span class='fu'>is.rsi</span>(<span class='no'>x</span>)
@@ -263,6 +277,10 @@
<th>guideline</th> <th>guideline</th>
<td><p>defaults to the latest included EUCAST guideline, run <code><a href='https://rdrr.io/r/base/unique.html'>unique(rsi_translation$guideline)</a></code> for all options</p></td> <td><p>defaults to the latest included EUCAST guideline, run <code><a href='https://rdrr.io/r/base/unique.html'>unique(rsi_translation$guideline)</a></code> for all options</p></td>
</tr> </tr>
<tr>
<th>uti</th>
<td><p>(Urinary Tract Infection) A vector with <a href='https://rdrr.io/r/base/logical.html'>logical</a>s (<code>TRUE</code> or <code>FALSE</code>) to specify whether a UTI specific interpretation from the guideline should be chosen. For using <code>as.rsi()</code> on a <a href='https://rdrr.io/r/base/data.frame.html'>data.frame</a>, this can also be a column containing <a href='https://rdrr.io/r/base/logical.html'>logical</a>s or when left blank, the data set will be search for a 'specimen' and rows containing 'urin' in that column will be regarded isolates from a UTI. See <em>Examples</em>.</p></td>
</tr>
<tr> <tr>
<th>col_mo</th> <th>col_mo</th>
<td><p>column name of the IDs of the microorganisms (see <code><a href='as.mo.html'>as.mo()</a></code>), defaults to the first column of class <code><a href='as.mo.html'>mo</a></code>. Values will be coerced using <code><a href='as.mo.html'>as.mo()</a></code>.</p></td> <td><p>column name of the IDs of the microorganisms (see <code><a href='as.mo.html'>as.mo()</a></code>), defaults to the first column of class <code><a href='as.mo.html'>mo</a></code>. Values will be coerced using <code><a href='as.mo.html'>as.mo()</a></code>.</p></td>
@@ -315,7 +333,40 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>stable</s
<h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2> <h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2>
<pre class="examples"><span class='co'># For INTERPRETING disk diffusion and MIC values -----------------------</span> <pre class="examples"><span class='co'># For INTERPRETING disk diffusion and MIC values -----------------------</span>
<span class='co'># single values</span> <span class='co'># a whole data set, even with combined MIC values and disk zones</span>
<span class='no'>df</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/r/base/data.frame.html'>data.frame</a></span>(<span class='kw'>microorganism</span> <span class='kw'>=</span> <span class='st'>"E. coli"</span>,
<span class='kw'>AMP</span> <span class='kw'>=</span> <span class='fu'><a href='as.mic.html'>as.mic</a></span>(<span class='fl'>8</span>),
<span class='kw'>CIP</span> <span class='kw'>=</span> <span class='fu'><a href='as.mic.html'>as.mic</a></span>(<span class='fl'>0.256</span>),
<span class='kw'>GEN</span> <span class='kw'>=</span> <span class='fu'><a href='as.disk.html'>as.disk</a></span>(<span class='fl'>18</span>),
<span class='kw'>TOB</span> <span class='kw'>=</span> <span class='fu'><a href='as.disk.html'>as.disk</a></span>(<span class='fl'>16</span>),
<span class='kw'>NIT</span> <span class='kw'>=</span> <span class='fu'><a href='as.mic.html'>as.mic</a></span>(<span class='fl'>32</span>))
<span class='fu'>as.rsi</span>(<span class='no'>df</span>)
<span class='co'># the dplyr way</span>
<span class='fu'><a href='https://rdrr.io/r/base/library.html'>library</a></span>(<span class='no'>dplyr</span>)
<span class='no'>df</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate_all.html'>mutate_at</a></span>(<span class='fu'><a href='https://dplyr.tidyverse.org/reference/vars.html'>vars</a></span>(<span class='no'>AMP</span>:<span class='no'>TOB</span>), <span class='no'>as.rsi</span>, <span class='kw'>mo</span> <span class='kw'>=</span> <span class='st'>"E. coli"</span>)
<span class='no'>df</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate_all.html'>mutate_at</a></span>(<span class='fu'><a href='https://dplyr.tidyverse.org/reference/vars.html'>vars</a></span>(<span class='no'>AMP</span>:<span class='no'>TOB</span>), <span class='no'>as.rsi</span>, <span class='kw'>mo</span> <span class='kw'>=</span> <span class='no'>.</span>$<span class='no'>microorganism</span>)
<span class='co'># to include information about urinary tract infections (UTI)</span>
<span class='fu'><a href='https://rdrr.io/r/base/data.frame.html'>data.frame</a></span>(<span class='kw'>mo</span> <span class='kw'>=</span> <span class='st'>"E. coli"</span>,
<span class='kw'>NIT</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='st'>"&lt;= 2"</span>, <span class='fl'>32</span>),
<span class='kw'>from_the_bladder</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='fl'>TRUE</span>, <span class='fl'>FALSE</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'>as.rsi</span>(<span class='kw'>uti</span> <span class='kw'>=</span> <span class='st'>"from_the_bladder"</span>)
<span class='fu'><a href='https://rdrr.io/r/base/data.frame.html'>data.frame</a></span>(<span class='kw'>mo</span> <span class='kw'>=</span> <span class='st'>"E. coli"</span>,
<span class='kw'>NIT</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='st'>"&lt;= 2"</span>, <span class='fl'>32</span>),
<span class='kw'>specimen</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='st'>"urine"</span>, <span class='st'>"blood"</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'>as.rsi</span>() <span class='co'># automatically determines urine isolates</span>
<span class='no'>df</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate_all.html'>mutate_at</a></span>(<span class='fu'><a href='https://dplyr.tidyverse.org/reference/vars.html'>vars</a></span>(<span class='no'>AMP</span>:<span class='no'>TOB</span>), <span class='no'>as.rsi</span>, <span class='kw'>mo</span> <span class='kw'>=</span> <span class='st'>"E. coli"</span>, <span class='kw'>uti</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>)
<span class='co'># for single values</span>
<span class='fu'>as.rsi</span>(<span class='kw'>x</span> <span class='kw'>=</span> <span class='fu'><a href='as.mic.html'>as.mic</a></span>(<span class='fl'>2</span>), <span class='fu'>as.rsi</span>(<span class='kw'>x</span> <span class='kw'>=</span> <span class='fu'><a href='as.mic.html'>as.mic</a></span>(<span class='fl'>2</span>),
<span class='kw'>mo</span> <span class='kw'>=</span> <span class='fu'><a href='as.mo.html'>as.mo</a></span>(<span class='st'>"S. pneumoniae"</span>), <span class='kw'>mo</span> <span class='kw'>=</span> <span class='fu'><a href='as.mo.html'>as.mo</a></span>(<span class='st'>"S. pneumoniae"</span>),
<span class='kw'>ab</span> <span class='kw'>=</span> <span class='st'>"AMP"</span>, <span class='kw'>ab</span> <span class='kw'>=</span> <span class='st'>"AMP"</span>,
@@ -326,14 +377,6 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>stable</s
<span class='kw'>ab</span> <span class='kw'>=</span> <span class='st'>"ampicillin"</span>, <span class='co'># and `ab` with as.ab()</span> <span class='kw'>ab</span> <span class='kw'>=</span> <span class='st'>"ampicillin"</span>, <span class='co'># and `ab` with as.ab()</span>
<span class='kw'>guideline</span> <span class='kw'>=</span> <span class='st'>"EUCAST"</span>) <span class='kw'>guideline</span> <span class='kw'>=</span> <span class='st'>"EUCAST"</span>)
<span class='co'># a whole data set, even with combined MIC values and disk zones</span>
<span class='no'>df</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/r/base/data.frame.html'>data.frame</a></span>(<span class='kw'>microorganism</span> <span class='kw'>=</span> <span class='st'>"E. coli"</span>,
<span class='kw'>AMP</span> <span class='kw'>=</span> <span class='fu'><a href='as.mic.html'>as.mic</a></span>(<span class='fl'>8</span>),
<span class='kw'>CIP</span> <span class='kw'>=</span> <span class='fu'><a href='as.mic.html'>as.mic</a></span>(<span class='fl'>0.256</span>),
<span class='kw'>GEN</span> <span class='kw'>=</span> <span class='fu'><a href='as.disk.html'>as.disk</a></span>(<span class='fl'>18</span>),
<span class='kw'>TOB</span> <span class='kw'>=</span> <span class='fu'><a href='as.disk.html'>as.disk</a></span>(<span class='fl'>16</span>))
<span class='fu'>as.rsi</span>(<span class='no'>df</span>)
<span class='co'># For CLEANING existing R/SI values ------------------------------------</span> <span class='co'># For CLEANING existing R/SI values ------------------------------------</span>

View File

@@ -80,7 +80,7 @@ This function requires an internet connection." />
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9025</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9029</span>
</span> </span>
</div> </div>

View File

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

View File

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

View File

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

View File

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

View File

@@ -80,7 +80,7 @@ count_resistant() should be used to count resistant isolates, count_susceptible(
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9025</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9029</span>
</span> </span>
</div> </div>

View File

@@ -80,7 +80,7 @@ To improve the interpretation of the antibiogram before EUCAST rules are applied
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9025</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9029</span>
</span> </span>
</div> </div>

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

@@ -80,7 +80,7 @@ This is the fastest way to have your organisation (or analysis) specific codes p
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9025</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9029</span>
</span> </span>
</div> </div>

View File

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

View File

@@ -80,7 +80,7 @@ resistance() should be used to calculate resistance, susceptibility() should be
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9025</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9029</span>
</span> </span>
</div> </div>

View File

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

View File

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

View File

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

View File

@@ -80,7 +80,7 @@ When negative: the left tail is longer; the mass of the distribution is concentr
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9025</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9029</span>
</span> </span>
</div> </div>

View File

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

View File

@@ -12,11 +12,25 @@
\usage{ \usage{
as.rsi(x, ...) as.rsi(x, ...)
\method{as.rsi}{mic}(x, mo, ab, guideline = "EUCAST", ...) \method{as.rsi}{mic}(
x,
mo,
ab = deparse(substitute(x)),
guideline = "EUCAST",
uti = FALSE,
...
)
\method{as.rsi}{disk}(x, mo, ab, guideline = "EUCAST", ...) \method{as.rsi}{disk}(
x,
mo,
ab = deparse(substitute(x)),
guideline = "EUCAST",
uti = FALSE,
...
)
\method{as.rsi}{data.frame}(x, col_mo = NULL, guideline = "EUCAST", ...) \method{as.rsi}{data.frame}(x, col_mo = NULL, guideline = "EUCAST", uti = NULL, ...)
is.rsi(x) is.rsi(x)
@@ -33,6 +47,8 @@ is.rsi.eligible(x, threshold = 0.05)
\item{guideline}{defaults to the latest included EUCAST guideline, run \code{unique(rsi_translation$guideline)} for all options} \item{guideline}{defaults to the latest included EUCAST guideline, run \code{unique(rsi_translation$guideline)} for all options}
\item{uti}{(Urinary Tract Infection) A vector with \link{logical}s (\code{TRUE} or \code{FALSE}) to specify whether a UTI specific interpretation from the guideline should be chosen. For using \code{\link[=as.rsi]{as.rsi()}} on a \link{data.frame}, this can also be a column containing \link{logical}s or when left blank, the data set will be search for a 'specimen' and rows containing 'urin' in that column will be regarded isolates from a UTI. See \emph{Examples}.}
\item{col_mo}{column name of the IDs of the microorganisms (see \code{\link[=as.mo]{as.mo()}}), defaults to the first column of class \code{\link{mo}}. Values will be coerced using \code{\link[=as.mo]{as.mo()}}.} \item{col_mo}{column name of the IDs of the microorganisms (see \code{\link[=as.mo]{as.mo()}}), defaults to the first column of class \code{\link{mo}}. Values will be coerced using \code{\link[=as.mo]{as.mo()}}.}
\item{threshold}{maximum fraction of invalid antimicrobial interpretations of \code{x}, please see \emph{Examples}} \item{threshold}{maximum fraction of invalid antimicrobial interpretations of \code{x}, please see \emph{Examples}}
@@ -82,8 +98,41 @@ On our website \url{https://msberends.gitlab.io/AMR} you can find \href{https://
\examples{ \examples{
# For INTERPRETING disk diffusion and MIC values ----------------------- # For INTERPRETING disk diffusion and MIC values -----------------------
# a whole data set, even with combined MIC values and disk zones
df <- data.frame(microorganism = "E. coli",
AMP = as.mic(8),
CIP = as.mic(0.256),
GEN = as.disk(18),
TOB = as.disk(16),
NIT = as.mic(32))
as.rsi(df)
# single values # the dplyr way
library(dplyr)
df \%>\%
mutate_at(vars(AMP:TOB), as.rsi, mo = "E. coli")
df \%>\%
mutate_at(vars(AMP:TOB), as.rsi, mo = .$microorganism)
# to include information about urinary tract infections (UTI)
data.frame(mo = "E. coli",
NIT = c("<= 2", 32),
from_the_bladder = c(TRUE, FALSE)) \%>\%
as.rsi(uti = "from_the_bladder")
data.frame(mo = "E. coli",
NIT = c("<= 2", 32),
specimen = c("urine", "blood")) \%>\%
as.rsi() # automatically determines urine isolates
df \%>\%
mutate_at(vars(AMP:TOB), as.rsi, mo = "E. coli", uti = TRUE)
# for single values
as.rsi(x = as.mic(2), as.rsi(x = as.mic(2),
mo = as.mo("S. pneumoniae"), mo = as.mo("S. pneumoniae"),
ab = "AMP", ab = "AMP",
@@ -93,14 +142,6 @@ as.rsi(x = as.disk(18),
mo = "Strep pneu", # `mo` will be coerced with as.mo() mo = "Strep pneu", # `mo` will be coerced with as.mo()
ab = "ampicillin", # and `ab` with as.ab() ab = "ampicillin", # and `ab` with as.ab()
guideline = "EUCAST") guideline = "EUCAST")
# a whole data set, even with combined MIC values and disk zones
df <- data.frame(microorganism = "E. coli",
AMP = as.mic(8),
CIP = as.mic(0.256),
GEN = as.disk(18),
TOB = as.disk(16))
as.rsi(df)
# For CLEANING existing R/SI values ------------------------------------ # For CLEANING existing R/SI values ------------------------------------

View File

@@ -81,6 +81,19 @@ test_that("mic2rsi works", {
as.rsi() %>% as.rsi() %>%
pull(amox_mic) %>% pull(amox_mic) %>%
is.rsi()) is.rsi())
expect_warning(data.frame(mo = "E. coli",
NIT = c("<= 2", 32)) %>%
as.rsi())
expect_message(data.frame(mo = "E. coli",
NIT = c("<= 2", 32),
uti = TRUE) %>%
as.rsi())
expect_message(
data.frame(mo = "E. coli",
NIT = c("<= 2", 32),
specimen = c("urine", "blood")) %>%
as.rsi())
}) })
test_that("disk2rsi works", { test_that("disk2rsi works", {