diff --git a/DESCRIPTION b/DESCRIPTION index 5307cacf..505b2a7a 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 1.0.0 -Date: 2020-02-17 +Version: 1.0.0.9000 +Date: 2020-02-20 Title: Antimicrobial Resistance Analysis Authors@R: c( person(role = c("aut", "cre"), diff --git a/NEWS.md b/NEWS.md index f73c876a..c6353a4b 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,19 @@ +# AMR 1.0.0.9000 +## Last updated: 20-Feb-2020 + +### 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 This software is now out of beta and considered stable. Nonetheless, this package will be developed continually. diff --git a/R/disk.R b/R/disk.R index 515520f5..b0f2e1e4 100644 --- a/R/disk.R +++ b/R/disk.R @@ -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 #' @export #' @importFrom dplyr %>% diff --git a/R/mic.R b/R/mic.R index 78a33853..7c014351 100755 --- a/R/mic.R +++ b/R/mic.R @@ -65,11 +65,14 @@ as.mic <- function(x, na.rm = FALSE) { # comma to period 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") x <- gsub("(<|=|>) +", "\\1", x) # transform => to >= and =< to <= - x <- gsub("=>", ">=", x, fixed = TRUE) x <- gsub("=<", "<=", x, fixed = TRUE) + x <- gsub("=>", ">=", x, fixed = TRUE) # starting dots must start with 0 x <- gsub("^[.]+", "0.", x) # <=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 #' @export #' @importFrom dplyr %>% diff --git a/R/misc.R b/R/misc.R index d3a05203..0b375c1f 100755 --- a/R/misc.R +++ b/R/misc.R @@ -117,7 +117,22 @@ search_type_in_df <- function(x, type) { 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)) { msg <- paste0("NOTE: Using column `", bold(found), "` as input for `col_", type, "`.") if (type %in% c("keyantibiotics", "specimen")) { diff --git a/R/rsi.R b/R/rsi.R index 2ba399ac..de7aa18b 100755 --- a/R/rsi.R +++ b/R/rsi.R @@ -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 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 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 #' @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* @@ -52,13 +53,45 @@ #' @return Ordered factor with new class [`rsi`] #' @aliases rsi #' @export -#' @importFrom dplyr %>% desc arrange filter #' @seealso [as.mic()] #' @inheritSection AMR Read more on our website! #' @examples #' # 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), #' mo = as.mo("S. pneumoniae"), #' ab = "AMP", @@ -68,14 +101,6 @@ #' mo = "Strep pneu", # `mo` will be coerced with as.mo() #' ab = "ampicillin", # and `ab` with as.ab() #' 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 ------------------------------------ @@ -114,6 +139,11 @@ as.rsi.default <- function(x, ...) { x } else if (identical(levels(x), c("S", "I", "R"))) { 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))) { x[x == 1] <- "S" x[x == 2] <- "I" @@ -164,6 +194,7 @@ as.rsi.default <- function(x, ...) { } } +#' @importFrom dplyr %>% input_resembles_mic <- function(x) { mic <- x %>% gsub("[^0-9.,]+", "", .) %>% @@ -178,26 +209,184 @@ input_resembles_mic <- function(x) { } #' @rdname as.rsi -#' @importFrom dplyr case_when #' @export -as.rsi.mic <- function(x, mo, ab, guideline = "EUCAST", ...) { - exec_as.rsi(method = "mic", - x = x, - mo = mo, - ab = ab, - guideline = guideline) +as.rsi.mic <- function(x, mo, ab = deparse(substitute(x)), guideline = "EUCAST", uti = FALSE, ...) { + if (missing(mo)) { + stop('No information was supplied about the microorganisms (missing parameter "mo"). See ?as.rsi.\n\n', + "To transform certain columns with e.g. mutate_at(), use\n", + "`data %>% mutate_at(vars(...), as.rsi, mo = .$x)`, where x is your column with microorganisms.\n\n", + "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 #' @export -as.rsi.disk <- function(x, mo, ab, guideline = "EUCAST", ...) { - exec_as.rsi(method = "disk", - x = x, - mo = mo, - ab = ab, - guideline = guideline) +as.rsi.disk <- function(x, mo, ab = deparse(substitute(x)), guideline = "EUCAST", uti = FALSE, ...) { + if (missing(mo)) { + stop('No information was supplied about the microorganisms (missing parameter "mo"). See ?as.rsi.\n\n', + "To transform certain columns with e.g. mutate_at(), use\n", + "`data %>% mutate_at(vars(...), as.rsi, mo = .$x)`, where x is your column with microorganisms.\n\n", + "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) { guideline_param <- toupper(guideline) if (guideline_param %in% c("CLSI", "EUCAST")) { @@ -216,19 +405,20 @@ get_guideline <- function(guideline) { } 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") { - x <- as.double(as.mic(x)) # when as.rsi.mic is called directly - method_param <- "MIC" + x <- as.mic(x) # when as.rsi.mic is called directly } else if (method == "disk") { - x <- as.double(as.disk(x)) # when as.rsi.disk is called directly - method_param <- "DISK" + x <- as.disk(x) # when as.rsi.disk is called directly } - mo <- as.mo(mo) - ab <- as.ab(ab) + warned <- FALSE + method_param <- toupper(method) mo_genus <- as.mo(mo_genus(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)) + ab_param <- ab 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)) 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_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))) { get_record <- trans %>% + # no UTI for now filter(lookup %in% c(lookup_mo[i], lookup_genus[i], lookup_family[i], lookup_order[i], lookup_becker[i], lookup_lancefield[i], - lookup_other[i])) %>% - # be as specific as possible (i.e. prefer species over genus): - arrange(desc(nchar(mo))) %>% - .[1L, ] + lookup_other[i])) + + if (isTRUE(uti[i])) { + 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 (is.na(x[i])) { new_rsi[i] <- NA_character_ } else if (method == "mic") { - new_rsi[i] <- case_when(isTRUE(x[i] <= get_record$breakpoint_S) ~ "S", - isTRUE(x[i] >= get_record$breakpoint_R) ~ "R", + mic_input <- x[i] + 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", TRUE ~ NA_character_) } else if (method == "disk") { - new_rsi[i] <- case_when(isTRUE(x[i] >= get_record$breakpoint_S) ~ "S", - isTRUE(x[i] <= get_record$breakpoint_R) ~ "R", + new_rsi[i] <- case_when(isTRUE(as.double(x[i]) >= as.double(get_record$breakpoint_S)) ~ "S", + 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", TRUE ~ NA_character_) } } } + if (warned == FALSE) { + message(green("OK.")) + } structure(.Data = factor(new_rsi, levels = c("S", "I", "R"), ordered = TRUE), 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 #' @export is.rsi <- function(x) { diff --git a/data-raw/antibiotics.txt b/data-raw/antibiotics.txt index 83ffb64d..16b58ca2 100644 --- a/data-raw/antibiotics.txt +++ b/data-raw/antibiotics.txt @@ -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" "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\")" -"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" "" "FPT" 9567558 "Cefepime/tazobactam" "Cephalosporins (4th gen.)" "" "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" "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\")" -"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" "" "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\")" "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\")" "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" "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" @@ -103,7 +103,7 @@ "CSU" 68718 "Cefsumide" "Cephalosporins (unclassified gen.)" "c(\"Cefsumide\", \"Cefsumido\", \"Cefsumidum\")" "CPT" "J01DI02" 56841980 "Ceftaroline" "Cephalosporins (5th gen.)" "c(\"Teflaro\", \"Zinforo\")" "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.)" "" "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\")" @@ -118,7 +118,7 @@ "CEI" "J01DI54" "Ceftolozane/enzyme inhibitor" "Cephalosporins (5th gen.)" "Other beta-lactam antibacterials" "Other cephalosporins" "" "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\")" -"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\")" "CFM2" "J01RA03" "Cefuroxime/metronidazole" "Other antibacterials" "Combinations of antibacterials" "Combinations of antibacterials" "" "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\", \"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\")" -"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" "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" diff --git a/data-raw/read_EUCAST.R b/data-raw/read_EUCAST.R index 7c8af6d5..aba5ad33 100644 --- a/data-raw/read_EUCAST.R +++ b/data-raw/read_EUCAST.R @@ -83,9 +83,23 @@ read_EUCAST <- function(sheet, file = "data-raw/v_10.0_Breakpoint_Tables.xlsx") x } - MICs_with_trailing_superscript <- c(0.0011:0.0019, 11:19, 21:29, 0.51:0.59, 41:49, - 81:89, 0.031:0.039, 0.061:0.069, 0.251:0.259, - 0.1251:0.1259, 161:169, 321:329) + MICs_with_trailing_superscript <- c(seq(from = 0.0011, to = 0.0019, by = 0.0001), + seq(from = 0.031, to = 0.039, by = 0.001), + 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)) @@ -101,7 +115,8 @@ read_EUCAST <- function(sheet, file = "data-raw/v_10.0_Breakpoint_Tables.xlsx") filter(!is.na(drug), !(is.na(MIC_S) & is.na(MIC_R) & is.na(disk_S) & is.na(disk_R)), !MIC_S %like% "(MIC|S ≤|note)", - drug != MIC_S) %>% + !MIC_S %like% "^[-]", + drug != MIC_S,) %>% mutate(administration = case_when(drug %like% "[( ]oral" ~ "oral", drug %like% "[( ]iv" ~ "iv", 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_R = clean_integer(disk_R), # 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), 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), - 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 mutate(drug = gsub(" ?[(, ].*$", "", drug), diff --git a/data-raw/reproduction_of_antibiotics.R b/data-raw/reproduction_of_antibiotics.R index db8338f9..73a3b7ae 100644 --- a/data-raw/reproduction_of_antibiotics.R +++ b/data-raw/reproduction_of_antibiotics.R @@ -317,6 +317,13 @@ antibiotics <- filter(antibiotics, ab != "PME") antibiotics[which(antibiotics$ab == "PVM1"), "ab"] <- "PME" # Remove Sinecatechins 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: 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")) diff --git a/data-raw/reproduction_of_rsi_translation.R b/data-raw/reproduction_of_rsi_translation.R index c8374efb..37cbc3ce 100644 --- a/data-raw/reproduction_of_rsi_translation.R +++ b/data-raw/reproduction_of_rsi_translation.R @@ -21,7 +21,9 @@ rsi_translation <- DRGLST1 %>% R_disk = as.disk(DISK_R), S_mic = as.mic(MIC_S), 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) print(mo_failures()) diff --git a/data-raw/rsi_translation.txt b/data-raw/rsi_translation.txt index 7e7283ca..f8e4b2c7 100644 --- a/data-raw/rsi_translation.txt +++ b/data-raw/rsi_translation.txt @@ -19,7 +19,7 @@ "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" "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" "Mobiluncus" "Amoxicillin/clavulanic acid" "Anaerobes, Gramnegative" 4 8 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" "DISK" "Haemophilus influenzae" "Ampicillin" "H.influenzae" "2ug" 18 18 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" "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" "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" "Parabacteroides" "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" "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" "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" "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" "Parabacteroides" "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" "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" "(unknown name)" "Ceftolozane/tazobactam" "PK PD breakpoints" 43.4 43.4 FALSE -"EUCAST 2020" "MIC" "Staphylococcus" "Dalbavancin" "Staphylococcus" 0.125 0.1253 FALSE -"EUCAST 2020" "MIC" "Streptococcus agalactiae" "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.1252 FALSE -"EUCAST 2020" "MIC" "Streptococcus anginosus" "Dalbavancin" "Viridans group streptococci" 0.125 0.1252 FALSE -"EUCAST 2020" "MIC" "Streptococcus 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.1252 FALSE -"EUCAST 2020" "MIC" "Streptococcus dysgalactiae equisimilis" "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.1252 FALSE -"EUCAST 2020" "MIC" "Streptococcus equi equi" "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.1252 FALSE -"EUCAST 2020" "MIC" "Streptococcus equi zooepidemicus" "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.1252 FALSE -"EUCAST 2020" "MIC" "Streptococcus group B" "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.1252 FALSE -"EUCAST 2020" "MIC" "Streptococcus group D" "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.1252 FALSE -"EUCAST 2020" "MIC" "Streptococcus group G" "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.1252 FALSE -"EUCAST 2020" "MIC" "Streptococcus group K" "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.1252 FALSE -"EUCAST 2020" "MIC" "Streptococcus salivarius" "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.1252 FALSE +"EUCAST 2020" "MIC" "(unknown name)" "Ceftolozane/tazobactam" "PK PD breakpoints" 4 4 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.125 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.125 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.125 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.125 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.125 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.125 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.125 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.125 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.125 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.125 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.125 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" "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" "UTI" "Enterobacterales" "Fosfomycin" "Enterobacterales" 32 32 TRUE "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" "MIC" "Staphylococcus" "Fusidic acid" "Staphylococcus" 1 1 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" "DISK" "Corynebacterium" "Moxifloxacin" "Corynebacterium" "5ug" 25 25 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" "MIC" "Haemophilus influenzae" "Moxifloxacin" "H.influenzae" 0.125 0.125 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" "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" "Staphylococcus aureus" "Oritavancin" "Staphylococcus" 0.125 0.1253 FALSE -"EUCAST 2020" "MIC" "Streptococcus agalactiae" "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.252 FALSE -"EUCAST 2020" "MIC" "Streptococcus anginosus" "Oritavancin" "Viridans group streptococci" 0.25 0.252 FALSE -"EUCAST 2020" "MIC" "Streptococcus 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.252 FALSE -"EUCAST 2020" "MIC" "Streptococcus dysgalactiae equisimilis" "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.252 FALSE -"EUCAST 2020" "MIC" "Streptococcus equi equi" "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.252 FALSE -"EUCAST 2020" "MIC" "Streptococcus equi zooepidemicus" "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.252 FALSE -"EUCAST 2020" "MIC" "Streptococcus group B" "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.252 FALSE -"EUCAST 2020" "MIC" "Streptococcus group D" "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.252 FALSE -"EUCAST 2020" "MIC" "Streptococcus group G" "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.252 FALSE -"EUCAST 2020" "MIC" "Streptococcus group K" "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.252 FALSE -"EUCAST 2020" "MIC" "Streptococcus salivarius" "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.252 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.25 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.25 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.25 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.25 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.25 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.25 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.25 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.25 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.25 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.25 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.25 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" "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" "Lactobacillus" "Piperacillin" "Anaerobes, Grampositive" 8 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" "Porphyromonas" "Piperacillin" "Anaerobes, Gramnegative" 1 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" "DISK" "Corynebacterium" "Rifampicin" "Corynebacterium" "5ug" 30 25 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" "DISK" "Haemophilus influenzae" "Rifampicin" "H.influenzae" "5ug" 18 18 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" "Prevotella" "Ticarcillin/clavulanic acid" "Anaerobes, Gramnegative" 8 16 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" "(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 @@ -1505,53 +1499,53 @@ "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" "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" "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" "MIC" "Escherichia coli" "Tigecycline" "Enterobacterales" 0.5 0.5 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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "DISK" "Enterobacterales" "Ticarcillin" "Enterobacterales" "75ug" 23 20 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" "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" "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" "MIC" "UTI" "Enterobacterales" "Trimethoprim" "Enterobacterales" 4 4 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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "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" "MIC" "Enterobacterales" "Piperacillin/tazobactam" "Enterobacterales" 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" "Fusobacterium" "Piperacillin/tazobactam" "Anaerobes, Gramnegative" 8 16 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" "Mobiluncus" "Piperacillin/tazobactam" "Anaerobes, Gramnegative" 8 16 FALSE "EUCAST 2020" "MIC" "Parabacteroides" "Piperacillin/tazobactam" "Anaerobes, Gramnegative" 8 16 FALSE diff --git a/data/antibiotics.rda b/data/antibiotics.rda index 2ae00491..ef5224e3 100755 Binary files a/data/antibiotics.rda and b/data/antibiotics.rda differ diff --git a/data/rsi_translation.rda b/data/rsi_translation.rda index ee5d7d81..a8656356 100644 Binary files a/data/rsi_translation.rda and b/data/rsi_translation.rda differ diff --git a/docs/404.html b/docs/404.html index a2e17c45..a0d0864d 100644 --- a/docs/404.html +++ b/docs/404.html @@ -78,7 +78,7 @@ AMR (for R) - 0.9.0.9027 + 1.0.0.9000 diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index cffd5428..7077d1de 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -78,7 +78,7 @@ AMR (for R) - 0.9.0.9027 + 1.0.0.9000 diff --git a/docs/articles/AMR.html b/docs/articles/AMR.html index c3cef579..00ecff0f 100644 --- a/docs/articles/AMR.html +++ b/docs/articles/AMR.html @@ -39,7 +39,7 @@ AMR (for R) - 0.9.0.9026 + 0.9.0.9029 @@ -179,7 +179,7 @@

How to conduct AMR analysis

Matthijs S. Berends

-

17 February 2020

+

20 February 2020

@@ -188,7 +188,7 @@ -

Note: values on this page will change with every website update since they are based on randomly created values and the page was written in R Markdown. However, the methodology remains unchanged. This page was generated on 17 February 2020.

+

Note: values on this page will change with every website update since they are based on randomly created values and the page was written in R Markdown. However, the methodology remains unchanged. This page was generated on 20 February 2020.

Introduction

@@ -219,21 +219,21 @@ -2020-02-17 +2020-02-20 abcd Escherichia coli S S -2020-02-17 +2020-02-20 abcd Escherichia coli S R -2020-02-17 +2020-02-20 efgh Escherichia coli R @@ -328,52 +328,30 @@ -2017-11-17 -D1 -Hospital A -Staphylococcus aureus -S -I -S -S -M - - -2015-03-23 -N2 -Hospital D -Staphylococcus aureus -R -S -S -S -M - - -2010-04-13 -X4 -Hospital B -Escherichia coli -S -S -S -S -F - - -2011-08-11 -M8 +2010-01-05 +F4 Hospital A Streptococcus pneumoniae S S S +S +M + + +2012-08-23 +J5 +Hospital B +Streptococcus pneumoniae +S R +S +S M -2015-01-30 -Z7 +2016-06-20 +S1 Hospital B Escherichia coli S @@ -383,14 +361,36 @@ F -2014-12-06 -F9 +2013-05-08 +J3 Hospital A Escherichia coli S -R S S +S +M + + +2011-12-28 +T8 +Hospital D +Staphylococcus aureus +S +I +S +S +F + + +2016-11-05 +G9 +Hospital C +Escherichia coli +S +S +R +S M @@ -423,16 +423,16 @@ Unique: 2

1 M -10,441 -52.21% -10,441 -52.21% +10,402 +52.01% +10,402 +52.01% 2 F -9,559 -47.80% +9,598 +47.99% 20,000 100.00% @@ -452,8 +452,8 @@ Unique: 2

# Other rules by this AMR package # Non-EUCAST: inherit amoxicillin results for unavailable ampicillin (no changes) # Non-EUCAST: inherit ampicillin results for unavailable amoxicillin (no changes) -# Non-EUCAST: set amoxicillin/clav acid = S where ampicillin = S (3,072 values changed) -# Non-EUCAST: set ampicillin = R where amoxicillin/clav acid = R (144 values changed) +# Non-EUCAST: set amoxicillin/clav acid = S where ampicillin = S (2,986 values changed) +# Non-EUCAST: set ampicillin = R where amoxicillin/clav acid = R (157 values changed) # Non-EUCAST: set piperacillin = R where piperacillin/tazobactam = R (no changes) # Non-EUCAST: set piperacillin/tazobactam = S where piperacillin = S (no changes) # Non-EUCAST: set trimethoprim = R where trimethoprim/sulfa = R (no changes) @@ -479,14 +479,14 @@ Unique: 2

# Pasteurella multocida (no changes) # Staphylococcus (no changes) # Streptococcus groups A, B, C, G (no changes) -# Streptococcus pneumoniae (1,007 values changed) +# Streptococcus pneumoniae (1,017 values changed) # Viridans group streptococci (no changes) # # EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016) -# Table 01: Intrinsic resistance in Enterobacteriaceae (1,261 values changed) +# Table 01: Intrinsic resistance in Enterobacteriaceae (1,297 values changed) # Table 02: Intrinsic resistance in non-fermentative Gram-negative bacteria (no changes) # Table 03: Intrinsic resistance in other Gram-negative bacteria (no changes) -# Table 04: Intrinsic resistance in Gram-positive bacteria (2,767 values changed) +# Table 04: Intrinsic resistance in Gram-positive bacteria (2,752 values changed) # Table 08: Interpretive rules for B-lactam agents and Gram-positive cocci (no changes) # Table 09: Interpretive rules for B-lactam agents and Gram-negative rods (no changes) # Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins (no changes) @@ -494,15 +494,15 @@ Unique: 2

# Table 13: Interpretive rules for quinolones (no changes) # # ------------------------------------------------------------------------------- -# EUCAST rules affected 6,578 out of 20,000 rows, making a total of 8,251 edits +# EUCAST rules affected 6,502 out of 20,000 rows, making a total of 8,209 edits # => added 0 test results # -# => changed 8,251 test results -# - 122 test results changed from S to I -# - 4,709 test results changed from S to R +# => changed 8,209 test results +# - 124 test results changed from S to I +# - 4,743 test results changed from S to R # - 1,209 test results changed from I to S -# - 348 test results changed from I to R -# - 1,863 test results changed from R to S +# - 356 test results changed from I to R +# - 1,777 test results changed from R to S # ------------------------------------------------------------------------------- # # Use eucast_rules(..., verbose = TRUE) (on your original data) to get a data.frame with all specified edits instead.
@@ -530,8 +530,8 @@ Unique: 2

# NOTE: Using column `bacteria` as input for `col_mo`. # NOTE: Using column `date` as input for `col_date`. # NOTE: Using column `patient_id` as input for `col_patient_id`. -# => Found 5,663 first isolates (28.3% of total) -

So only 28.3% is suitable for resistance analysis! We can now filter on it with the filter() function, also from the dplyr package:

+# => Found 5,695 first isolates (28.5% of total) +

So only 28.5% is suitable for resistance analysis! We can now filter on it with the filter() function, also from the dplyr package:

data_1st <- data %>% 
   filter(first == TRUE)

For future use, the above two syntaxes can be shortened with the filter_first_isolate() function:

@@ -541,7 +541,7 @@ Unique: 2

First weighted isolates

-

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:

+

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:

@@ -557,30 +557,30 @@ Unique: 2

- - + + - - + + - - + + - + - - + + @@ -590,19 +590,19 @@ Unique: 2

- - + + - - + + - - + + @@ -612,8 +612,8 @@ Unique: 2

- - + + @@ -623,51 +623,51 @@ Unique: 2

- - + + - - - - + + + + - - + + - + - - + + - - + + - - + + - +
isolate
12010-04-12I42010-02-09N2 B_ESCHR_COLI RRRSS S TRUE
22010-05-10I42010-03-02N2 B_ESCHR_COLI S S SSR FALSE
32010-07-25I42010-04-05N2 B_ESCHR_COLI S S
42010-09-13I42010-05-19N2 B_ESCHR_COLISSRI S S FALSE
52010-09-29I42010-07-08N2 B_ESCHR_COLI R I
62010-11-25I42010-08-09N2 B_ESCHR_COLI S S
72010-11-25I42011-05-26N2 B_ESCHR_COLIRIR SFALSESSSTRUE
82010-11-28I42011-05-26N2 B_ESCHR_COLI RSR S S FALSE
92010-12-27I42011-06-19N2 B_ESCHR_COLIRR S SRS FALSE
102011-01-01I42011-07-29N2 B_ESCHR_COLI RRS S S FALSE
-

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 key_antibiotics() 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.

+

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 key_antibiotics() 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.

If a column exists with a name like ‘key(…)ab’ the first_isolate() function will automatically use it and determine the first weighted isolates. Mind the NOTEs in below output:

data <- data %>% 
   mutate(keyab = key_antibiotics(.)) %>% 
@@ -678,7 +678,7 @@ Unique: 2

# NOTE: Using column `patient_id` as input for `col_patient_id`. # NOTE: Using column `keyab` as input for `col_keyantibiotics`. Use col_keyantibiotics = FALSE to prevent this. # [Criterion] Inclusion based on key antibiotics, ignoring I -# => Found 14,979 first weighted isolates (74.9% of total)
+# => Found 15,096 first weighted isolates (75.5% of total)
@@ -695,20 +695,32 @@ Unique: 2

- - + + - - + + - - + + + + + + + + + + + + + + @@ -717,34 +729,10 @@ Unique: 2

- - - - - - - - - - - - - - - - - - - - - - - - - - + + @@ -753,10 +741,22 @@ Unique: 2

+ + + + + + + + + + + + - - + + @@ -767,23 +767,23 @@ Unique: 2

- - + + - - - - + + + + - - + + - + @@ -791,35 +791,35 @@ Unique: 2

- - + + - - + + - - + + - + - +
isolate
12010-04-12I42010-02-09N2 B_ESCHR_COLI RRRSS S TRUE TRUE
22010-05-10I42010-03-02N2B_ESCHR_COLISSSRFALSETRUE
32010-04-05N2 B_ESCHR_COLI S S FALSE TRUE
32010-07-25I4B_ESCHR_COLISSSSFALSEFALSE
42010-09-13I4B_ESCHR_COLISSSSFALSEFALSE
52010-09-29I42010-05-19N2 B_ESCHR_COLI R I FALSE TRUE
52010-07-08N2B_ESCHR_COLIRISSFALSEFALSE
62010-11-25I42010-08-09N2 B_ESCHR_COLI S S
72010-11-25I42011-05-26N2 B_ESCHR_COLIRIR SFALSESSSTRUE TRUE
82010-11-28I42011-05-26N2 B_ESCHR_COLI RSR S S FALSE
92010-12-27I42011-06-19N2 B_ESCHR_COLIRR S SRS FALSE TRUE
102011-01-01I42011-07-29N2 B_ESCHR_COLI RRS S S FALSEFALSETRUE
-

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.

+

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.

As with filter_first_isolate(), there’s a shortcut for this new algorithm too:

data_1st <- data %>% 
   filter_first_weighted_isolate()
-

So we end up with 14,979 isolates for analysis.

+

So we end up with 15,096 isolates for analysis.

We can remove unneeded columns:

data_1st <- data_1st %>% 
   select(-c(first, keyab))
@@ -845,56 +845,8 @@ Unique: 2

1 -2017-11-17 -D1 -Hospital A -B_STPHY_AURS -S -S -S -S -M -Gram-positive -Staphylococcus -aureus -TRUE - - -2 -2015-03-23 -N2 -Hospital D -B_STPHY_AURS -R -S -S -S -M -Gram-positive -Staphylococcus -aureus -TRUE - - -3 -2010-04-13 -X4 -Hospital B -B_ESCHR_COLI -S -S -S -S -F -Gram-negative -Escherichia -coli -TRUE - - -4 -2011-08-11 -M8 +2010-01-05 +F4 Hospital A B_STRPT_PNMN S @@ -907,11 +859,27 @@ Unique: 2

pneumoniae TRUE - + 6 -2014-12-06 -F9 -Hospital A +2016-11-05 +G9 +Hospital C +B_ESCHR_COLI +S +S +R +S +M +Gram-negative +Escherichia +coli +TRUE + + +7 +2016-05-20 +A10 +Hospital D B_ESCHR_COLI S S @@ -924,21 +892,53 @@ Unique: 2

TRUE -7 -2016-02-10 -A4 -Hospital B +9 +2015-10-02 +R3 +Hospital C B_ESCHR_COLI R S S S +F +Gram-negative +Escherichia +coli +TRUE + + +10 +2016-03-04 +B10 +Hospital A +B_ESCHR_COLI +R +R +S +S M Gram-negative Escherichia coli TRUE + +11 +2013-09-10 +P4 +Hospital B +B_KLBSL_PNMN +R +S +S +S +F +Gram-negative +Klebsiella +pneumoniae +TRUE +

Time for the analysis!

@@ -958,8 +958,8 @@ Unique: 2

data_1st %>% freq(genus, species)

Frequency table

Class: character
-Length: 14,979
-Available: 14,979 (100%, NA: 0 = 0%)
+Length: 15,096
+Available: 15,096 (100%, NA: 0 = 0%)
Unique: 4

Shortest: 16
Longest: 24

@@ -976,33 +976,33 @@ Longest: 24

1 Escherichia coli -7,462 -49.82% -7,462 -49.82% +7,491 +49.62% +7,491 +49.62% 2 Staphylococcus aureus -3,695 -24.67% -11,157 -74.48% +3,729 +24.70% +11,220 +74.32% 3 Streptococcus pneumoniae -2,321 +2,340 15.50% -13,478 -89.98% +13,560 +89.83% 4 Klebsiella pneumoniae -1,501 -10.02% -14,979 +1,536 +10.17% +15,096 100.00% @@ -1014,7 +1014,7 @@ Longest: 24

The functions resistance() and susceptibility() can be used to calculate antimicrobial resistance or susceptibility. For more specific analyses, the functions proportion_S(), proportion_SI(), proportion_I(), proportion_IR() and proportion_R() can be used to determine the proportion of a specific antimicrobial outcome.

As per the EUCAST guideline of 2019, we calculate resistance as the proportion of R (proportion_R(), equal to resistance()) and susceptibility as the proportion of S and I (proportion_SI(), equal to susceptibility()). These functions can be used on their own:

data_1st %>% resistance(AMX)
-# [1] 0.4633153
+# [1] 0.4681373

Or can be used in conjuction with group_by() and summarise(), both from the dplyr package:

data_1st %>% 
   group_by(hospital) %>% 
@@ -1027,19 +1027,19 @@ Longest: 24

Hospital A -0.4589178 +0.4648446 Hospital B -0.4609652 +0.4689223 Hospital C -0.4542615 +0.4656180 Hospital D -0.4815972 +0.4734787 @@ -1057,23 +1057,23 @@ Longest: 24

Hospital A -0.4589178 -4491 +0.4648446 +4537 Hospital B -0.4609652 -5367 +0.4689223 +5261 Hospital C -0.4542615 -2241 +0.4656180 +2225 Hospital D -0.4815972 -2880 +0.4734787 +3073 @@ -1093,27 +1093,27 @@ Longest: 24

Escherichia -0.9234790 -0.8998928 -0.9963817 +0.9255106 +0.8972100 +0.9937258 Klebsiella -0.9347102 -0.8974017 -0.9940040 +0.9199219 +0.8932292 +0.9934896 Staphylococcus -0.9271989 -0.9188092 -0.9929635 +0.9187450 +0.9133816 +0.9924913 Streptococcus -0.6066351 +0.6128205 0.0000000 -0.6066351 +0.6128205 diff --git a/docs/articles/AMR_files/figure-html/plot 1-1.png b/docs/articles/AMR_files/figure-html/plot 1-1.png index 3f9b9eab..40829f82 100644 Binary files a/docs/articles/AMR_files/figure-html/plot 1-1.png and b/docs/articles/AMR_files/figure-html/plot 1-1.png differ diff --git a/docs/articles/AMR_files/figure-html/plot 3-1.png b/docs/articles/AMR_files/figure-html/plot 3-1.png index 490d3cd4..609c6a48 100644 Binary files a/docs/articles/AMR_files/figure-html/plot 3-1.png and b/docs/articles/AMR_files/figure-html/plot 3-1.png differ diff --git a/docs/articles/AMR_files/figure-html/plot 4-1.png b/docs/articles/AMR_files/figure-html/plot 4-1.png index 4ba81bf0..acd4ab0e 100644 Binary files a/docs/articles/AMR_files/figure-html/plot 4-1.png and b/docs/articles/AMR_files/figure-html/plot 4-1.png differ diff --git a/docs/articles/AMR_files/figure-html/plot 5-1.png b/docs/articles/AMR_files/figure-html/plot 5-1.png index 6e908afb..64306ce9 100644 Binary files a/docs/articles/AMR_files/figure-html/plot 5-1.png and b/docs/articles/AMR_files/figure-html/plot 5-1.png differ diff --git a/docs/articles/EUCAST.html b/docs/articles/EUCAST.html index cdf6f6b7..005496e8 100644 --- a/docs/articles/EUCAST.html +++ b/docs/articles/EUCAST.html @@ -39,7 +39,7 @@ AMR (for R) - 0.9.0.9025 + 0.9.0.9029
@@ -179,7 +179,7 @@

How to apply EUCAST rules

Matthijs S. Berends

-

17 February 2020

+

20 February 2020

diff --git a/docs/articles/index.html b/docs/articles/index.html index 3b9f35fc..68e7c8ae 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -78,7 +78,7 @@ AMR (for R) - 0.9.0.9027 + 1.0.0.9000 diff --git a/docs/authors.html b/docs/authors.html index fe9ef45c..de79af16 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -78,7 +78,7 @@ AMR (for R) - 0.9.0.9027 + 1.0.0.9000 diff --git a/docs/index.html b/docs/index.html index 882df264..7fef5906 100644 --- a/docs/index.html +++ b/docs/index.html @@ -43,7 +43,7 @@ AMR (for R) - 0.9.0.9027 + 1.0.0.9000 @@ -266,7 +266,7 @@ A methods paper about this package has been preprinted at bioRxiv (DOI: 10.1101/ Latest development version

The latest and unpublished development version can be installed with (precaution: may be unstable):

install.packages("devtools")
-devtools::install_gitlab("msberends/AMR")
+devtools::install_gitlab("msberends/AMR")
diff --git a/docs/news/index.html b/docs/news/index.html index 08fca132..98bdf037 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -78,7 +78,7 @@ AMR (for R) - 0.9.0.9027 + 1.0.0.9000
@@ -219,14 +219,38 @@ -
+

-AMR 0.9.0.9027 Unreleased +AMR 1.0.0.9000 Unreleased

-
+

-Last updated: 17-Feb-2020 +Last updated: 20-Feb-2020

+
+

+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:

    +
    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 2020-02-17 +

+

This software is now out of beta and considered stable. Nonetheless, this package will be developed continually.

New

@@ -237,21 +261,21 @@
  • Support for LOINC codes in the antibiotics data set. Use ab_loinc() to retrieve LOINC codes, or use a LOINC code for input in any ab_* function:

    -
    ab_loinc("ampicillin")
    -#> [1] "21066-6" "3355-5"  "33562-0" "33919-2" "43883-8" "43884-6" "87604-5"
    -ab_name("21066-6")
    -#> [1] "Ampicillin"
    -ab_atc("21066-6")
    -#> [1] "J01CA01"
    +
    ab_loinc("ampicillin")
    +#> [1] "21066-6" "3355-5"  "33562-0" "33919-2" "43883-8" "43884-6" "87604-5"
    +ab_name("21066-6")
    +#> [1] "Ampicillin"
    +ab_atc("21066-6")
    +#> [1] "J01CA01"
  • Support for SNOMED CT codes in the microorganisms data set. Use mo_snomed() to retrieve SNOMED codes, or use a SNOMED code for input in any mo_* function:

    -
    mo_snomed("S. aureus")
    -#> [1] 115329001   3092008 113961008
    -mo_name(115329001)
    -#> [1] "Staphylococcus aureus"
    -mo_gramstain(115329001)
    -#> [1] "Gram-positive"
    +
    mo_snomed("S. aureus")
    +#> [1] 115329001   3092008 113961008
    +mo_name(115329001)
    +#> [1] "Staphylococcus aureus"
    +mo_gramstain(115329001)
    +#> [1] "Gram-positive"
@@ -296,7 +320,6 @@
  • Removed unnecessary AMR:: calls
  • -

    @@ -310,9 +333,9 @@
    • If you were dependent on the old Enterobacteriaceae family e.g. by using in your code:

      -
      if (mo_family(somebugs) == "Enterobacteriaceae") ...
      +
      if (mo_family(somebugs) == "Enterobacteriaceae") ...

      then please adjust this to:

      -
      if (mo_order(somebugs) == "Enterobacterales") ...
      +
      if (mo_order(somebugs) == "Enterobacterales") ...
    @@ -324,12 +347,12 @@
    • Functions susceptibility() and resistance() as aliases of proportion_SI() and proportion_R(), respectively. These functions were added to make it more clear that “I” should be considered susceptible and not resistant.

      -
      library(dplyr)
      -example_isolates %>%
      -  group_by(bug = mo_name(mo)) %>% 
      -  summarise(amoxicillin = resistance(AMX),
      -            amox_clav   = resistance(AMC)) %>%
      -  filter(!is.na(amoxicillin) | !is.na(amox_clav))
      +
      library(dplyr)
      +example_isolates %>%
      +  group_by(bug = mo_name(mo)) %>% 
      +  summarise(amoxicillin = resistance(AMX),
      +            amox_clav   = resistance(AMC)) %>%
      +  filter(!is.na(amoxicillin) | !is.na(amox_clav))
    • Support for a new MDRO guideline: Magiorakos AP, Srinivasan A et al. “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).

      @@ -351,16 +374,16 @@
    • More intelligent way of coping with some consonants like “l” and “r”

    • Added a score (a certainty percentage) to mo_uncertainties(), that is calculated using the Levenshtein distance:

      -
      as.mo(c("Stafylococcus aureus",
      -        "staphylokok aureuz"))
      -#> Warning: 
      -#> Results of two values were guessed with uncertainty. Use mo_uncertainties() to review them.
      -#> Class 'mo'
      -#> [1] B_STPHY_AURS B_STPHY_AURS
      -
      -mo_uncertainties()
      -#> "Stafylococcus aureus" -> Staphylococcus aureus (B_STPHY_AURS, score: 95.2%)
      -#> "staphylokok aureuz"   -> Staphylococcus aureus (B_STPHY_AURS, score: 85.7%)
      +
      as.mo(c("Stafylococcus aureus",
      +        "staphylokok aureuz"))
      +#> Warning: 
      +#> Results of two values were guessed with uncertainty. Use mo_uncertainties() to review them.
      +#> Class 'mo'
      +#> [1] B_STPHY_AURS B_STPHY_AURS
      +
      +mo_uncertainties()
      +#> "Stafylococcus aureus" -> Staphylococcus aureus (B_STPHY_AURS, score: 95.2%)
      +#> "staphylokok aureuz"   -> Staphylococcus aureus (B_STPHY_AURS, score: 85.7%)
    @@ -408,22 +431,22 @@
    • Determination of first isolates now excludes all ‘unknown’ microorganisms at default, i.e. microbial code "UNKNOWN". They can be included with the new parameter include_unknown:

      -
      first_isolate(..., include_unknown = TRUE)
      +
      first_isolate(..., include_unknown = TRUE)

      For WHONET users, this means that all records/isolates with organism code "con" (contamination) will be excluded at default, since as.mo("con") = "UNKNOWN". The function always shows a note with the number of ‘unknown’ microorganisms that were included or excluded.

    • For code consistency, classes ab and mo will now be preserved in any subsetting or assignment. For the sake of data integrity, this means that invalid assignments will now result in NA:

      -
      # how it works in base R:
      -x <- factor("A")
      -x[1] <- "B"
      -#> Warning message:
      -#> invalid factor level, NA generated
      -
      -# how it now works similarly for classes 'mo' and 'ab':
      -x <- as.mo("E. coli")
      -x[1] <- "testvalue"
      -#> Warning message:
      -#> invalid microorganism code, NA generated
      +
      # how it works in base R:
      +x <- factor("A")
      +x[1] <- "B"
      +#> Warning message:
      +#> invalid factor level, NA generated
      +
      +# how it now works similarly for classes 'mo' and 'ab':
      +x <- as.mo("E. coli")
      +x[1] <- "testvalue"
      +#> Warning message:
      +#> invalid microorganism code, NA generated

      This is important, because a value like "testvalue" could never be understood by e.g. mo_name(), although the class would suggest a valid microbial code.

    • Function freq() has moved to a new package, clean (CRAN link), since creating frequency tables actually does not fit the scope of this package. The freq() function still works, since it is re-exported from the clean package (which will be installed automatically upon updating this AMR package).

    • @@ -436,62 +459,62 @@
      • Function bug_drug_combinations() to quickly get a data.frame 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 mo_shortname() at default:

        -
        x <- bug_drug_combinations(example_isolates)
        -#> NOTE: Using column `mo` as input for `col_mo`.
        -x[1:4, ]
        -#>             mo  ab S I R total
        -#> 1 A. baumannii AMC 0 0 3     3
        -#> 2 A. baumannii AMK 0 0 0     0
        -#> 3 A. baumannii AMP 0 0 3     3
        -#> 4 A. baumannii AMX 0 0 3     3
        -#> NOTE: Use 'format()' on this result to get a publicable/printable format.
        -
        -# change the transformation with the FUN argument to anything you like:
        -x <- bug_drug_combinations(example_isolates, FUN = mo_gramstain)
        -#> NOTE: Using column `mo` as input for `col_mo`.
        -x[1:4, ]
        -#>              mo  ab   S  I   R total
        -#> 1 Gram-negative AMC 469 89 174   732
        -#> 2 Gram-negative AMK 251  0   2   253
        -#> 3 Gram-negative AMP 227  0 405   632
        -#> 4 Gram-negative AMX 227  0 405   632
        -#> NOTE: Use 'format()' on this result to get a publicable/printable format.
        +
        x <- bug_drug_combinations(example_isolates)
        +#> NOTE: Using column `mo` as input for `col_mo`.
        +x[1:4, ]
        +#>             mo  ab S I R total
        +#> 1 A. baumannii AMC 0 0 3     3
        +#> 2 A. baumannii AMK 0 0 0     0
        +#> 3 A. baumannii AMP 0 0 3     3
        +#> 4 A. baumannii AMX 0 0 3     3
        +#> NOTE: Use 'format()' on this result to get a publicable/printable format.
        +
        +# change the transformation with the FUN argument to anything you like:
        +x <- bug_drug_combinations(example_isolates, FUN = mo_gramstain)
        +#> NOTE: Using column `mo` as input for `col_mo`.
        +x[1:4, ]
        +#>              mo  ab   S  I   R total
        +#> 1 Gram-negative AMC 469 89 174   732
        +#> 2 Gram-negative AMK 251  0   2   253
        +#> 3 Gram-negative AMP 227  0 405   632
        +#> 4 Gram-negative AMX 227  0 405   632
        +#> NOTE: Use 'format()' on this result to get a publicable/printable format.

        You can format this to a printable format, ready for reporting or exporting to e.g. Excel with the base R format() function:

        -
        format(x, combine_IR = FALSE)
        +
        format(x, combine_IR = FALSE)
      • Additional way to calculate co-resistance, i.e. when using multiple antimicrobials as input for portion_* functions or count_* functions. This can be used to determine the empiric susceptibility of a combination therapy. A new parameter only_all_tested (which defaults to FALSE) replaces the old also_single_tested and can be used to select one of the two methods to count isolates and calculate portions. The difference can be seen in this example table (which is also on the portion and count help pages), where the %SI is being determined:

        -
        # --------------------------------------------------------------------
        -#                     only_all_tested = FALSE  only_all_tested = TRUE
        -#                     -----------------------  -----------------------
        -#  Drug A    Drug B   include as  include as   include as  include as
        -#                     numerator   denominator  numerator   denominator
        -# --------  --------  ----------  -----------  ----------  -----------
        -#  S or I    S or I       X            X            X            X
        -#    R       S or I       X            X            X            X
        -#   <NA>     S or I       X            X            -            -
        -#  S or I      R          X            X            X            X
        -#    R         R          -            X            -            X
        -#   <NA>       R          -            -            -            -
        -#  S or I     <NA>        X            X            -            -
        -#    R        <NA>        -            -            -            -
        -#   <NA>      <NA>        -            -            -            -
        -# --------------------------------------------------------------------
        +
        # --------------------------------------------------------------------
        +#                     only_all_tested = FALSE  only_all_tested = TRUE
        +#                     -----------------------  -----------------------
        +#  Drug A    Drug B   include as  include as   include as  include as
        +#                     numerator   denominator  numerator   denominator
        +# --------  --------  ----------  -----------  ----------  -----------
        +#  S or I    S or I       X            X            X            X
        +#    R       S or I       X            X            X            X
        +#   <NA>     S or I       X            X            -            -
        +#  S or I      R          X            X            X            X
        +#    R         R          -            X            -            X
        +#   <NA>       R          -            -            -            -
        +#  S or I     <NA>        X            X            -            -
        +#    R        <NA>        -            -            -            -
        +#   <NA>      <NA>        -            -            -            -
        +# --------------------------------------------------------------------

        Since this is a major change, usage of the old also_single_tested will throw an informative error that it has been replaced by only_all_tested.

      • tibble printing support for classes rsi, mic, disk, ab mo. When using tibbles containing antimicrobial columns, values S will print in green, values I will print in yellow and values R will print in red. Microbial IDs (class mo) will emphasise on the genus and species, not on the kingdom.

        -
        # (run this on your own console, as this page does not support colour printing)
        -library(dplyr)
        -example_isolates %>%
        -  select(mo:AMC) %>% 
        -  as_tibble()
        +
        # (run this on your own console, as this page does not support colour printing)
        +library(dplyr)
        +example_isolates %>%
        +  select(mo:AMC) %>% 
        +  as_tibble()

    -
    +

    -Changed

    +Changed
    • Many algorithm improvements for as.mo() (of which some led to additions to the microorganisms data set). Many thanks to all contributors that helped improving the algorithms.
        @@ -562,14 +585,14 @@
        • Function rsi_df() to transform a data.frame to a data set containing only the microbial interpretation (S, I, R), the antibiotic, the percentage of S/I/R and the number of available isolates. This is a convenient combination of the existing functions count_df() and portion_df() to immediately show resistance percentages and number of available isolates:

          -
          septic_patients %>%
          -  select(AMX, CIP) %>%
          -  rsi_df()
          -#      antibiotic  interpretation      value  isolates
          -# 1   Amoxicillin              SI  0.4442636       546
          -# 2   Amoxicillin               R  0.5557364       683
          -# 3 Ciprofloxacin              SI  0.8381831      1181
          -# 4 Ciprofloxacin               R  0.1618169       228
          +
          septic_patients %>%
          +  select(AMX, CIP) %>%
          +  rsi_df()
          +#      antibiotic  interpretation      value  isolates
          +# 1   Amoxicillin              SI  0.4442636       546
          +# 2   Amoxicillin               R  0.5557364       683
          +# 3 Ciprofloxacin              SI  0.8381831      1181
          +# 4 Ciprofloxacin               R  0.1618169       228
        • Support for all scientifically published pathotypes of E. coli to date (that we could find). Supported are:

          @@ -587,20 +610,20 @@
        • UPEC (Uropathogenic E. coli)

        All these lead to the microbial ID of E. coli:

        -
        as.mo("UPEC")
        -# B_ESCHR_COL
        -mo_name("UPEC")
        -# "Escherichia coli"
        -mo_gramstain("EHEC")
        -# "Gram-negative"
        +
        as.mo("UPEC")
        +# B_ESCHR_COL
        +mo_name("UPEC")
        +# "Escherichia coli"
        +mo_gramstain("EHEC")
        +# "Gram-negative"
      • Function mo_info() as an analogy to ab_info(). The mo_info() prints a list with the full taxonomy, authors, and the URL to the online database of a microorganism

      • Function mo_synonyms() to get all previously accepted taxonomic names of a microorganism

    -
    +

    -Changed

    +Changed
    • Column names of output count_df() and portion_df() are now lowercase
    • Fixed bug in translation of microorganism names
    • @@ -647,9 +670,9 @@
    • Added guidelines of the WHO to determine multi-drug resistance (MDR) for TB (mdr_tb()) and added a new vignette about MDR. Read this tutorial here on our website.
    -
    +

    -Changed

    +Changed
    • Fixed a critical bug in first_isolate() 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.

    • Fixed a bug in eucast_rules() where antibiotics from WHONET software would not be recognised

    • @@ -694,14 +717,14 @@
    • when all values are unique it now shows a message instead of a warning

    • support for boxplots:

      -
      septic_patients %>% 
      -  freq(age) %>% 
      -  boxplot()
      -# grouped boxplots:
      -septic_patients %>% 
      -  group_by(hospital_id) %>% 
      -  freq(age) %>%
      -  boxplot()
      +
      septic_patients %>% 
      +  freq(age) %>% 
      +  boxplot()
      +# grouped boxplots:
      +septic_patients %>% 
      +  group_by(hospital_id) %>% 
      +  freq(age) %>%
      +  boxplot()
    @@ -734,9 +757,9 @@

    AMR 0.6.1 2019-03-29

    -
    +

    -Changed

    +Changed
    -
    +

    -Changed

    +Changed
    • Function eucast_rules():
        @@ -864,33 +887,33 @@
        • Now handles incorrect spelling, like i instead of y and f instead of ph:

          -
          # mo_fullname() uses as.mo() internally
          -
          -mo_fullname("Sthafilokockus aaureuz")
          -#> [1] "Staphylococcus aureus"
          -
          -mo_fullname("S. klossi")
          -#> [1] "Staphylococcus kloosii"
          +
          # mo_fullname() uses as.mo() internally
          +
          +mo_fullname("Sthafilokockus aaureuz")
          +#> [1] "Staphylococcus aureus"
          +
          +mo_fullname("S. klossi")
          +#> [1] "Staphylococcus kloosii"
        • Uncertainty of the algorithm is now divided into four levels, 0 to 3, where the default allow_uncertain = TRUE is equal to uncertainty level 2. Run ?as.mo for more info about these levels.

          -
          # equal:
          -as.mo(..., allow_uncertain = TRUE)
          -as.mo(..., allow_uncertain = 2)
          -
          -# also equal:
          -as.mo(..., allow_uncertain = FALSE)
          -as.mo(..., allow_uncertain = 0)
          +
          # equal:
          +as.mo(..., allow_uncertain = TRUE)
          +as.mo(..., allow_uncertain = 2)
          +
          +# also equal:
          +as.mo(..., allow_uncertain = FALSE)
          +as.mo(..., allow_uncertain = 0)

          Using as.mo(..., allow_uncertain = 3) could lead to very unreliable results.

        • Implemented the latest publication of Becker et al. (2019), for categorising coagulase-negative Staphylococci

        • All microbial IDs that found are now saved to a local file ~/.Rhistory_mo. Use the new function clean_mo_history() to delete this file, which resets the algorithms.

        • Incoercible results will now be considered ‘unknown’, MO code UNKNOWN. On foreign systems, properties of these will be translated to all languages already previously supported: German, Dutch, French, Italian, Spanish and Portuguese:

          -
          mo_genus("qwerty", language = "es")
          -# Warning: 
          -# one unique value (^= 100.0%) could not be coerced and is considered 'unknown': "qwerty". Use mo_failures() to review it.
          -#> [1] "(género desconocido)"
          +
          mo_genus("qwerty", language = "es")
          +# Warning: 
          +# one unique value (^= 100.0%) could not be coerced and is considered 'unknown': "qwerty". Use mo_failures() to review it.
          +#> [1] "(género desconocido)"
        • Fix for vector containing only empty values

        • Finds better results when input is in other languages

        • @@ -935,19 +958,19 @@
          • Support for tidyverse quasiquotation! Now you can create frequency tables of function outcomes:

            -
            # Determine genus of microorganisms (mo) in `septic_patients` data set:
            -# OLD WAY
            -septic_patients %>%
            -  mutate(genus = mo_genus(mo)) %>%
            -  freq(genus)
            -# NEW WAY
            -septic_patients %>% 
            -  freq(mo_genus(mo))
            -
            -# Even supports grouping variables:
            -septic_patients %>%
            -  group_by(gender) %>% 
            -  freq(mo_genus(mo))
            +
            # Determine genus of microorganisms (mo) in `septic_patients` data set:
            +# OLD WAY
            +septic_patients %>%
            +  mutate(genus = mo_genus(mo)) %>%
            +  freq(genus)
            +# NEW WAY
            +septic_patients %>% 
            +  freq(mo_genus(mo))
            +
            +# Even supports grouping variables:
            +septic_patients %>%
            +  group_by(gender) %>% 
            +  freq(mo_genus(mo))
          • Header info is now available as a list, with the header function

          • The parameter header is now set to TRUE at default, even for markdown

          • @@ -994,9 +1017,9 @@
          • Functions mo_authors and mo_year to get specific values about the scientific reference of a taxonomic entry
    -
    +

    -Changed

    +Changed
    • Functions MDRO, BRMO, MRGN and EUCAST_exceptional_phenotypes were renamed to mdro, brmo, mrgn and eucast_exceptional_phenotypes

    • EUCAST_rules was renamed to eucast_rules, the old function still exists as a deprecated function

    • @@ -1018,10 +1041,10 @@
    • Fewer than 3 characters as input for as.mo will return NA

    • Function as.mo (and all mo_* wrappers) now supports genus abbreviations with “species” attached

      -
      as.mo("E. species")        # B_ESCHR
      -mo_fullname("E. spp.")     # "Escherichia species"
      -as.mo("S. spp")            # B_STPHY
      -mo_fullname("S. species")  # "Staphylococcus species"
      +
      as.mo("E. species")        # B_ESCHR
      +mo_fullname("E. spp.")     # "Escherichia species"
      +as.mo("S. spp")            # B_STPHY
      +mo_fullname("S. species")  # "Staphylococcus species"
    • Added parameter combine_IR (TRUE/FALSE) to functions portion_df and count_df, 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)

    • Fix for portion_*(..., as_percent = TRUE) when minimal number of isolates would not be met

    • @@ -1033,15 +1056,15 @@
      • Support for grouping variables, test with:

        -
        septic_patients %>% 
        -  group_by(hospital_id) %>% 
        -  freq(gender)
        +
        septic_patients %>% 
        +  group_by(hospital_id) %>% 
        +  freq(gender)
      • Support for (un)selecting columns:

        -
        septic_patients %>% 
        -  freq(hospital_id) %>% 
        -  select(-count, -cum_count) # only get item, percent, cum_percent
        +
        septic_patients %>% 
        +  freq(hospital_id) %>% 
        +  select(-count, -cum_count) # only get item, percent, cum_percent
      • Check for hms::is.hms

      • Now prints in markdown at default in non-interactive sessions

      • @@ -1117,18 +1140,18 @@

      They also come with support for German, Dutch, French, Italian, Spanish and Portuguese:

      -
      mo_gramstain("E. coli")
      -# [1] "Gram negative"
      -mo_gramstain("E. coli", language = "de") # German
      -# [1] "Gramnegativ"
      -mo_gramstain("E. coli", language = "es") # Spanish
      -# [1] "Gram negativo"
      -mo_fullname("S. group A", language = "pt") # Portuguese
      -# [1] "Streptococcus grupo A"
      +
      mo_gramstain("E. coli")
      +# [1] "Gram negative"
      +mo_gramstain("E. coli", language = "de") # German
      +# [1] "Gramnegativ"
      +mo_gramstain("E. coli", language = "es") # Spanish
      +# [1] "Gram negativo"
      +mo_fullname("S. group A", language = "pt") # Portuguese
      +# [1] "Streptococcus grupo A"

      Furthermore, former taxonomic names will give a note about the current taxonomic name:

      -
      mo_gramstain("Esc blattae")
      -# Note: 'Escherichia blattae' (Burgess et al., 1973) was renamed 'Shimwellia blattae' (Priest and Barker, 2010)
      -# [1] "Gram negative"
      +
      mo_gramstain("Esc blattae")
      +# Note: 'Escherichia blattae' (Burgess et al., 1973) was renamed 'Shimwellia blattae' (Priest and Barker, 2010)
      +# [1] "Gram negative"
    • Functions count_R, count_IR, count_I, count_SI and count_S to selectively count resistant or susceptible isolates

      @@ -1139,18 +1162,18 @@
    • Function is.rsi.eligible to check for columns that have valid antimicrobial results, but do not have the rsi class yet. Transform the columns of your raw data with: data %>% mutate_if(is.rsi.eligible, as.rsi)

    • Functions as.mo and is.mo as replacements for as.bactid and is.bactid (since the microoganisms data set not only contains bacteria). These last two functions are deprecated and will be removed in a future release. The as.mo function determines microbial IDs using intelligent rules:

      -
      as.mo("E. coli")
      -# [1] B_ESCHR_COL
      -as.mo("MRSA")
      -# [1] B_STPHY_AUR
      -as.mo("S group A")
      -# [1] B_STRPTC_GRA
      +
      as.mo("E. coli")
      +# [1] B_ESCHR_COL
      +as.mo("MRSA")
      +# [1] B_STPHY_AUR
      +as.mo("S group A")
      +# [1] B_STRPTC_GRA

      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:

      -
      thousands_of_E_colis <- rep("E. coli", 25000)
      -microbenchmark::microbenchmark(as.mo(thousands_of_E_colis), unit = "s")
      -# Unit: seconds
      -#         min       median         max  neval
      -#  0.01817717  0.01843957  0.03878077    100
      +
      thousands_of_E_colis <- rep("E. coli", 25000)
      +microbenchmark::microbenchmark(as.mo(thousands_of_E_colis), unit = "s")
      +# Unit: seconds
      +#         min       median         max  neval
      +#  0.01817717  0.01843957  0.03878077    100
    • Added parameter reference_df for as.mo, so users can supply their own microbial IDs, name or codes as a reference table

    • @@ -1171,19 +1194,19 @@
    • Renamed septic_patients$sex to septic_patients$gender

    -
    +

    -Changed

    +Changed
    • Added three antimicrobial agents to the antibiotics data set: Terbinafine (D01BA02), Rifaximin (A07AA11) and Isoconazole (D01AC05)

    • Added 163 trade names to the antibiotics data set, it now contains 298 different trade names in total, e.g.:

      -
      ab_official("Bactroban")
      -# [1] "Mupirocin"
      -ab_name(c("Bactroban", "Amoxil", "Zithromax", "Floxapen"))
      -# [1] "Mupirocin" "Amoxicillin" "Azithromycin" "Flucloxacillin"
      -ab_atc(c("Bactroban", "Amoxil", "Zithromax", "Floxapen"))
      -# [1] "R01AX06" "J01CA04" "J01FA10" "J01CF05"
      +
      ab_official("Bactroban")
      +# [1] "Mupirocin"
      +ab_name(c("Bactroban", "Amoxil", "Zithromax", "Floxapen"))
      +# [1] "Mupirocin" "Amoxicillin" "Azithromycin" "Flucloxacillin"
      +ab_atc(c("Bactroban", "Amoxil", "Zithromax", "Floxapen"))
      +# [1] "R01AX06" "J01CA04" "J01FA10" "J01CF05"
    • For first_isolate, rows will be ignored when there’s no species available

    • Function ratio is now deprecated and will be removed in a future release, as it is not really the scope of this package

    • @@ -1193,13 +1216,13 @@
    • Added parameters minimum and as_percent to portion_df

    • Support for quasiquotation in the functions series count_* and portions_*, and n_rsi. This allows to check for more than 2 vectors or columns.

      -
      septic_patients %>% select(amox, cipr) %>% count_IR()
      -# which is the same as:
      -septic_patients %>% count_IR(amox, cipr)
      -
      -septic_patients %>% portion_S(amcl)
      -septic_patients %>% portion_S(amcl, gent)
      -septic_patients %>% portion_S(amcl, gent, pita)
      +
      septic_patients %>% select(amox, cipr) %>% count_IR()
      +# which is the same as:
      +septic_patients %>% count_IR(amox, cipr)
      +
      +septic_patients %>% portion_S(amcl)
      +septic_patients %>% portion_S(amcl, gent)
      +septic_patients %>% portion_S(amcl, gent, pita)
    • Edited ggplot_rsi and geom_rsi so they can cope with count_df. The new fun parameter has value portion_df at default, but can be set to count_df.

    • Fix for ggplot_rsi when the ggplot2 package was not loaded

    • @@ -1211,12 +1234,12 @@
    • Added longest en shortest character length in the frequency table (freq) header of class character

    • Support for types (classes) list and matrix for freq

      -
      my_matrix = with(septic_patients, matrix(c(age, gender), ncol = 2))
      -freq(my_matrix)
      +
      my_matrix = with(septic_patients, matrix(c(age, gender), ncol = 2))
      +freq(my_matrix)

      For lists, subsetting is possible:

      -
      my_list = list(age = septic_patients$age, gender = septic_patients$gender)
      -my_list %>% freq(age)
      -my_list %>% freq(gender)
      +
      my_list = list(age = septic_patients$age, gender = septic_patients$gender)
      +my_list %>% freq(age)
      +my_list %>% freq(gender)
    @@ -1305,9 +1328,9 @@
    -
    +

    -Changed

    +Changed
    • Improvements for forecasting with resistance_predict and added more examples
    • More antibiotics added as parameters for EUCAST rules
    • @@ -1391,9 +1414,9 @@
    • New print format for tibbles and data.tables
    -
    +

    -Changed

    +Changed
    • Fixed rsi class for vectors that contain only invalid antimicrobial interpretations
    • Renamed dataset ablist to antibiotics @@ -1450,7 +1473,8 @@

      Contents

      diff --git a/docs/reference/AMR.html b/docs/reference/AMR.html index 87e56098..fc395f33 100644 --- a/docs/reference/AMR.html +++ b/docs/reference/AMR.html @@ -79,7 +79,7 @@ AMR (for R) - 0.9.0.9026 + 0.9.0.9029
    diff --git a/docs/reference/WHOCC.html b/docs/reference/WHOCC.html index e1a09e7e..4317b538 100644 --- a/docs/reference/WHOCC.html +++ b/docs/reference/WHOCC.html @@ -79,7 +79,7 @@ AMR (for R) - 0.9.0.9025 + 0.9.0.9029
    diff --git a/docs/reference/WHONET.html b/docs/reference/WHONET.html index 97fe38a7..7eaf4eb3 100644 --- a/docs/reference/WHONET.html +++ b/docs/reference/WHONET.html @@ -79,7 +79,7 @@ AMR (for R) - 0.9.0.9025 + 0.9.0.9029
    diff --git a/docs/reference/ab_property.html b/docs/reference/ab_property.html index f4c0fbba..bc8fef21 100644 --- a/docs/reference/ab_property.html +++ b/docs/reference/ab_property.html @@ -79,7 +79,7 @@ AMR (for R) - 0.9.0.9025 + 0.9.0.9029
    diff --git a/docs/reference/age.html b/docs/reference/age.html index 205a32cf..9dae96cc 100644 --- a/docs/reference/age.html +++ b/docs/reference/age.html @@ -79,7 +79,7 @@ AMR (for R) - 0.9.0.9025 + 0.9.0.9029
    diff --git a/docs/reference/age_groups.html b/docs/reference/age_groups.html index 5167ddf5..5aba898b 100644 --- a/docs/reference/age_groups.html +++ b/docs/reference/age_groups.html @@ -79,7 +79,7 @@ AMR (for R) - 0.9.0.9025 + 0.9.0.9029
    diff --git a/docs/reference/antibiotics.html b/docs/reference/antibiotics.html index 2d509b79..40746ff2 100644 --- a/docs/reference/antibiotics.html +++ b/docs/reference/antibiotics.html @@ -79,7 +79,7 @@ AMR (for R) - 0.9.0.9025 + 0.9.0.9029
    diff --git a/docs/reference/as.ab.html b/docs/reference/as.ab.html index 8fb33e07..746689ca 100644 --- a/docs/reference/as.ab.html +++ b/docs/reference/as.ab.html @@ -79,7 +79,7 @@ AMR (for R) - 0.9.0.9025 + 0.9.0.9029
    diff --git a/docs/reference/as.disk.html b/docs/reference/as.disk.html index c03b4383..bee97140 100644 --- a/docs/reference/as.disk.html +++ b/docs/reference/as.disk.html @@ -79,7 +79,7 @@ AMR (for R) - 0.9.0.9027 + 0.9.0.9029
    diff --git a/docs/reference/as.mic.html b/docs/reference/as.mic.html index 2a533196..f1eb1039 100644 --- a/docs/reference/as.mic.html +++ b/docs/reference/as.mic.html @@ -79,7 +79,7 @@ AMR (for R) - 0.9.0.9025 + 0.9.0.9029
    diff --git a/docs/reference/as.mo.html b/docs/reference/as.mo.html index 38689c9a..eca26b70 100644 --- a/docs/reference/as.mo.html +++ b/docs/reference/as.mo.html @@ -79,7 +79,7 @@ AMR (for R) - 0.9.0.9025 + 0.9.0.9029
    diff --git a/docs/reference/as.rsi.html b/docs/reference/as.rsi.html index dd1d54b8..51f41c67 100644 --- a/docs/reference/as.rsi.html +++ b/docs/reference/as.rsi.html @@ -79,7 +79,7 @@ AMR (for R) - 0.9.0.9025 + 0.9.0.9029 @@ -228,13 +228,27 @@
    as.rsi(x, ...)
     
     # S3 method for mic
    -as.rsi(x, mo, ab, guideline = "EUCAST", ...)
    +as.rsi(
    +  x,
    +  mo,
    +  ab = deparse(substitute(x)),
    +  guideline = "EUCAST",
    +  uti = FALSE,
    +  ...
    +)
     
     # S3 method for disk
    -as.rsi(x, mo, ab, guideline = "EUCAST", ...)
    +as.rsi(
    +  x,
    +  mo,
    +  ab = deparse(substitute(x)),
    +  guideline = "EUCAST",
    +  uti = FALSE,
    +  ...
    +)
     
     # S3 method for data.frame
    -as.rsi(x, col_mo = NULL, guideline = "EUCAST", ...)
    +as.rsi(x, col_mo = NULL, guideline = "EUCAST", uti = NULL, ...)
     
     is.rsi(x)
     
    @@ -263,6 +277,10 @@
           guideline
           

    defaults to the latest included EUCAST guideline, run unique(rsi_translation$guideline) for all options

    + + uti +

    (Urinary Tract Infection) A vector with logicals (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 logicals 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.

    + col_mo

    column name of the IDs of the microorganisms (see as.mo()), defaults to the first column of class mo. Values will be coerced using as.mo().

    @@ -315,7 +333,40 @@ The lifecycle of this function is stableExamples
    # For INTERPRETING disk diffusion and MIC values -----------------------
     
    -# single 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)
    +
    +# 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),
            mo = as.mo("S. pneumoniae"),
            ab = "AMP",
    @@ -326,14 +377,6 @@ The lifecycle of this function is stableab = "ampicillin",  # and `ab` with as.ab()
            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 ------------------------------------
     
    diff --git a/docs/reference/atc_online.html b/docs/reference/atc_online.html
    index 41ee1c83..6abbe08d 100644
    --- a/docs/reference/atc_online.html
    +++ b/docs/reference/atc_online.html
    @@ -80,7 +80,7 @@ This function requires an internet connection." />
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/availability.html b/docs/reference/availability.html
    index cd74db39..613462be 100644
    --- a/docs/reference/availability.html
    +++ b/docs/reference/availability.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/bug_drug_combinations.html b/docs/reference/bug_drug_combinations.html
    index e320559f..dfcf8a33 100644
    --- a/docs/reference/bug_drug_combinations.html
    +++ b/docs/reference/bug_drug_combinations.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/catalogue_of_life.html b/docs/reference/catalogue_of_life.html
    index 02c1ba7a..469c5be7 100644
    --- a/docs/reference/catalogue_of_life.html
    +++ b/docs/reference/catalogue_of_life.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/catalogue_of_life_version.html b/docs/reference/catalogue_of_life_version.html
    index f4e86c27..28bd210c 100644
    --- a/docs/reference/catalogue_of_life_version.html
    +++ b/docs/reference/catalogue_of_life_version.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/count.html b/docs/reference/count.html
    index 5870a3fb..2b9872ba 100644
    --- a/docs/reference/count.html
    +++ b/docs/reference/count.html
    @@ -80,7 +80,7 @@ count_resistant() should be used to count resistant isolates, count_susceptible(
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/eucast_rules.html b/docs/reference/eucast_rules.html
    index 983426bc..bc69c608 100644
    --- a/docs/reference/eucast_rules.html
    +++ b/docs/reference/eucast_rules.html
    @@ -80,7 +80,7 @@ To improve the interpretation of the antibiogram before EUCAST rules are applied
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/example_isolates.html b/docs/reference/example_isolates.html
    index fbb28224..40ad5da9 100644
    --- a/docs/reference/example_isolates.html
    +++ b/docs/reference/example_isolates.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/extended-functions.html b/docs/reference/extended-functions.html
    index 9ed3228b..71ea9bde 100644
    --- a/docs/reference/extended-functions.html
    +++ b/docs/reference/extended-functions.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/first_isolate.html b/docs/reference/first_isolate.html
    index 6dbe9469..60d8f6ea 100644
    --- a/docs/reference/first_isolate.html
    +++ b/docs/reference/first_isolate.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/g.test.html b/docs/reference/g.test.html
    index df17ccd0..68c48e5c 100644
    --- a/docs/reference/g.test.html
    +++ b/docs/reference/g.test.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/ggplot_rsi.html b/docs/reference/ggplot_rsi.html
    index 39f180f4..df8420eb 100644
    --- a/docs/reference/ggplot_rsi.html
    +++ b/docs/reference/ggplot_rsi.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/guess_ab_col.html b/docs/reference/guess_ab_col.html
    index 3b412744..e5e99522 100644
    --- a/docs/reference/guess_ab_col.html
    +++ b/docs/reference/guess_ab_col.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/index.html b/docs/reference/index.html
    index ae5adcca..8887c1e6 100644
    --- a/docs/reference/index.html
    +++ b/docs/reference/index.html
    @@ -78,7 +78,7 @@
           
           
             AMR (for R)
    -        0.9.0.9027
    +        1.0.0.9000
           
         
     
    diff --git a/docs/reference/join.html b/docs/reference/join.html
    index d4149e8d..b6285a87 100644
    --- a/docs/reference/join.html
    +++ b/docs/reference/join.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/key_antibiotics.html b/docs/reference/key_antibiotics.html
    index ba7c11b7..8d9edc84 100644
    --- a/docs/reference/key_antibiotics.html
    +++ b/docs/reference/key_antibiotics.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/kurtosis.html b/docs/reference/kurtosis.html
    index 5702237f..97ec52c4 100644
    --- a/docs/reference/kurtosis.html
    +++ b/docs/reference/kurtosis.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/like.html b/docs/reference/like.html
    index 9ee0b694..eb60bf27 100644
    --- a/docs/reference/like.html
    +++ b/docs/reference/like.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/mdro.html b/docs/reference/mdro.html
    index 58b4c0b6..084d51a3 100644
    --- a/docs/reference/mdro.html
    +++ b/docs/reference/mdro.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/microorganisms.codes.html b/docs/reference/microorganisms.codes.html
    index 2535a9a6..57453e52 100644
    --- a/docs/reference/microorganisms.codes.html
    +++ b/docs/reference/microorganisms.codes.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/microorganisms.html b/docs/reference/microorganisms.html
    index cce0c5b7..3b0cec6f 100644
    --- a/docs/reference/microorganisms.html
    +++ b/docs/reference/microorganisms.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/microorganisms.old.html b/docs/reference/microorganisms.old.html
    index 2b159dfc..51268201 100644
    --- a/docs/reference/microorganisms.old.html
    +++ b/docs/reference/microorganisms.old.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/mo_property.html b/docs/reference/mo_property.html
    index 1cad32cf..938715a5 100644
    --- a/docs/reference/mo_property.html
    +++ b/docs/reference/mo_property.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/mo_source.html b/docs/reference/mo_source.html
    index ecdb5534..1f51227c 100644
    --- a/docs/reference/mo_source.html
    +++ b/docs/reference/mo_source.html
    @@ -80,7 +80,7 @@ This is the fastest way to have your organisation (or analysis) specific codes p
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/p_symbol.html b/docs/reference/p_symbol.html
    index 5291a486..84587906 100644
    --- a/docs/reference/p_symbol.html
    +++ b/docs/reference/p_symbol.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/proportion.html b/docs/reference/proportion.html
    index 71ae129c..fd78dc35 100644
    --- a/docs/reference/proportion.html
    +++ b/docs/reference/proportion.html
    @@ -80,7 +80,7 @@ resistance() should be used to calculate resistance, susceptibility() should be
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/read.4D.html b/docs/reference/read.4D.html
    index f9232789..19694f99 100644
    --- a/docs/reference/read.4D.html
    +++ b/docs/reference/read.4D.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/resistance_predict.html b/docs/reference/resistance_predict.html
    index f25718b3..6a25eb11 100644
    --- a/docs/reference/resistance_predict.html
    +++ b/docs/reference/resistance_predict.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/rsi_translation.html b/docs/reference/rsi_translation.html
    index 20306c5d..92c556c6 100644
    --- a/docs/reference/rsi_translation.html
    +++ b/docs/reference/rsi_translation.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/skewness.html b/docs/reference/skewness.html
    index 80b654ce..38a44b12 100644
    --- a/docs/reference/skewness.html
    +++ b/docs/reference/skewness.html
    @@ -80,7 +80,7 @@ When negative: the left tail is longer; the mass of the distribution is concentr
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/docs/reference/translate.html b/docs/reference/translate.html
    index ad7bf966..cb121b3b 100644
    --- a/docs/reference/translate.html
    +++ b/docs/reference/translate.html
    @@ -79,7 +79,7 @@
           
           
             AMR (for R)
    -        0.9.0.9025
    +        0.9.0.9029
           
         
     
    diff --git a/man/as.rsi.Rd b/man/as.rsi.Rd
    index a06052ad..9518772c 100755
    --- a/man/as.rsi.Rd
    +++ b/man/as.rsi.Rd
    @@ -12,11 +12,25 @@
     \usage{
     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)
     
    @@ -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{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{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{
     # 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),
            mo = as.mo("S. pneumoniae"),
            ab = "AMP",
    @@ -93,14 +142,6 @@ as.rsi(x = as.disk(18),
            mo = "Strep pneu",  # `mo` will be coerced with as.mo()
            ab = "ampicillin",  # and `ab` with as.ab()
            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 ------------------------------------
    diff --git a/tests/testthat/test-rsi.R b/tests/testthat/test-rsi.R
    index 04b27adb..b80858ab 100644
    --- a/tests/testthat/test-rsi.R
    +++ b/tests/testthat/test-rsi.R
    @@ -81,6 +81,19 @@ test_that("mic2rsi works", {
                     as.rsi() %>%
                     pull(amox_mic) %>%
                     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", {