diff --git a/DESCRIPTION b/DESCRIPTION index 8cc41304..9e8cfbb5 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 0.7.1.9004 -Date: 2019-06-27 +Version: 0.7.1.9005 +Date: 2019-07-01 Title: Antimicrobial Resistance Analysis Authors@R: c( person( diff --git a/NAMESPACE b/NAMESPACE index 6963dd4b..e233f55e 100755 --- a/NAMESPACE +++ b/NAMESPACE @@ -224,7 +224,6 @@ importFrom(crayon,black) importFrom(crayon,blue) importFrom(crayon,bold) importFrom(crayon,green) -importFrom(crayon,has_color) importFrom(crayon,italic) importFrom(crayon,magenta) importFrom(crayon,red) diff --git a/NEWS.md b/NEWS.md index 48bdda46..ce8e8189 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,11 +1,42 @@ -# AMR 0.7.1.9004 +# AMR 0.7.1.9005 + +### New +* Additional way to calculate co-resistance, i.e. when using multiple antibiotics as input for `portion_*` functions or `count_*` functions. This can be used to determine the empiric susceptibily of a combination therapy. A new parameter `only_all_tested` replaces the old `also_single_tested` and can be used to select one of the two methods to count isolates and calculate portions. The difference can be seen in this example table (which is also on the `portion` and `count` help pages), where the %SI is being determined: + + ```r + # ------------------------------------------------------------------------- + # only_all_tested = FALSE only_all_tested = TRUE + # Antibiotic Antibiotic ----------------------- ----------------------- + # A B include as include as include as include as + # numerator denominator numerator denominator + # ---------- ---------- ---------- ----------- ---------- ----------- + # S S X X X X + # I S X X X X + # R S X X X X + # not tested S X X - - + # S I X X X X + # I I X X X X + # R I X X X X + # not tested I X X - - + # S R X X X X + # I R X X X X + # R R - X - X + # not tested R - - - - + # S not tested X X - - + # I not tested X X - - + # R not tested - - - - + # not tested not tested - - - - + # ------------------------------------------------------------------------- + ``` + + Since this is a major change, usage of the old `also_single_tested` will throw an informative error that it has been replaced by `only_all_tested`. ### Changed * Removed class `atc` - using `as.atc()` is now deprecated in favour of `ab_atc()` and this will return a character, not the `atc` class anymore * Removed deprecated functions `abname()`, `ab_official()`, `atc_name()`, `atc_official()`, `atc_property()`, `atc_tradenames()`, `atc_trivial_nl()` * Fix and speed improvement for `mo_shortname()` * Fix for `as.mo()` where misspelled input would not be understood -* Fix for `also_single_tested` parameter in `count_*` functions +* Fix for using `mo_*` functions where the coercion uncertainties and failures would not be available through `mo_uncertainties()` and `mo_failures()` anymore # AMR 0.7.1 diff --git a/R/count.R b/R/count.R index 641e31c2..0a03d22e 100755 --- a/R/count.R +++ b/R/count.R @@ -34,6 +34,7 @@ #' The function \code{count_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and counts the amounts of S, I and R. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}. #' #' The function \code{rsi_df} works exactly like \code{count_df}, but adds the percentage of S, I and R. +#' @inheritSection portion Combination therapy #' @source Wickham H. \strong{Tidy Data.} The Journal of Statistical Software, vol. 59, 2014. \url{http://vita.had.co.nz/papers/tidy-data.html} #' @seealso \code{\link{portion}_*} to calculate microbial resistance and susceptibility. #' @keywords resistance susceptibility rsi antibiotics isolate isolates @@ -61,8 +62,8 @@ #' # Since n_rsi counts available isolates, you can #' # calculate back to count e.g. non-susceptible isolates. #' # This results in the same: -#' count_IR(septic_patients$AMX) -#' portion_IR(septic_patients$AMX) * n_rsi(septic_patients$AMX) +#' count_SI(septic_patients$AMX) +#' portion_SI(septic_patients$AMX) * n_rsi(septic_patients$AMX) #' #' library(dplyr) #' septic_patients %>% @@ -76,17 +77,17 @@ #' #' # Count co-resistance between amoxicillin/clav acid and gentamicin, #' # so we can see that combination therapy does a lot more than mono therapy. -#' # Please mind that `portion_S` calculates percentages right away instead. -#' count_S(septic_patients$AMC) # S = 1342 (71.4%) -#' count_all(septic_patients$AMC) # n = 1879 +#' # Please mind that `portion_SI` calculates percentages right away instead. +#' count_SI(septic_patients$AMC) # 1433 +#' count_all(septic_patients$AMC) # 1879 #' -#' count_S(septic_patients$GEN) # S = 1372 (74.0%) -#' count_all(septic_patients$GEN) # n = 1855 +#' count_SI(septic_patients$GEN) # 1399 +#' count_all(septic_patients$GEN) # 1855 #' #' with(septic_patients, -#' count_S(AMC, GEN)) # S = 1660 (92.3%) -#' with(septic_patients, # n = 1798 -#' n_rsi(AMC, GEN)) +#' count_SI(AMC, GEN)) # 1764 +#' with(septic_patients, +#' n_rsi(AMC, GEN)) # 1936 #' #' # Get portions S/I/R immediately of all rsi columns #' septic_patients %>% @@ -99,71 +100,56 @@ #' group_by(hospital_id) %>% #' count_df(translate = FALSE) #' -count_R <- function(..., also_single_tested = FALSE) { +count_R <- function(..., only_all_tested = FALSE) { rsi_calc(..., - type = "R", - include_I = FALSE, - minimum = 0, - as_percent = FALSE, - also_single_tested = also_single_tested, + ab_result = "R", + only_all_tested = only_all_tested, only_count = TRUE) } #' @rdname count #' @export -count_IR <- function(..., also_single_tested = FALSE) { +count_IR <- function(..., only_all_tested = FALSE) { rsi_calc(..., - type = "R", - include_I = TRUE, - minimum = 0, - as_percent = FALSE, - also_single_tested = also_single_tested, + ab_result = c("I", "R"), + only_all_tested = only_all_tested, only_count = TRUE) } #' @rdname count #' @export -count_I <- function(..., also_single_tested = FALSE) { +count_I <- function(..., only_all_tested = FALSE) { rsi_calc(..., - type = "I", - include_I = FALSE, - minimum = 0, - as_percent = FALSE, - also_single_tested = also_single_tested, + ab_result = "I", + only_all_tested = only_all_tested, only_count = TRUE) } #' @rdname count #' @export -count_SI <- function(..., also_single_tested = FALSE) { +count_SI <- function(..., only_all_tested = FALSE) { rsi_calc(..., - type = "S", - include_I = TRUE, - minimum = 0, - as_percent = FALSE, - also_single_tested = also_single_tested, + ab_result = c("S", "I"), + only_all_tested = only_all_tested, only_count = TRUE) } #' @rdname count #' @export -count_S <- function(..., also_single_tested = FALSE) { +count_S <- function(..., only_all_tested = FALSE) { rsi_calc(..., - type = "S", - include_I = FALSE, - minimum = 0, - as_percent = FALSE, - also_single_tested = also_single_tested, + ab_result = "S", + only_all_tested = only_all_tested, only_count = TRUE) } #' @rdname count #' @export -count_all <- function(..., also_single_tested = FALSE) { - res_SI <- count_SI(..., also_single_tested = also_single_tested) - # only print warnings once, if needed - res_R <- suppressWarnings(count_R(..., also_single_tested = also_single_tested)) - res_SI + res_R +count_all <- function(..., only_all_tested = FALSE) { + rsi_calc(..., + ab_result = c("S", "I", "R"), + only_all_tested = only_all_tested, + only_count = TRUE) } #' @rdname count diff --git a/R/mo.R b/R/mo.R index b1f5fbf3..605a6cc0 100755 --- a/R/mo.R +++ b/R/mo.R @@ -87,12 +87,9 @@ #' \strong{Uncertain results} \cr #' The algorithm can additionally use three different levels of uncertainty to guess valid results. The default is \code{allow_uncertain = TRUE}, which is equal to uncertainty level 2. Using \code{allow_uncertain = FALSE} will skip all of these additional rules: #' \itemize{ -#' \item{(uncertainty level 1): It tries to look for only matching genera} -#' \item{(uncertainty level 1): It tries to look for previously accepted (but now invalid) taxonomic names} -#' \item{(uncertainty level 2): It strips off values between brackets and the brackets itself, and re-evaluates the input with all previous rules} -#' \item{(uncertainty level 2): It strips off words from the end one by one and re-evaluates the input with all previous rules} -#' \item{(uncertainty level 3): It strips off words from the start one by one and re-evaluates the input with all previous rules} -#' \item{(uncertainty level 3): It tries any part of the name} +#' \item{(uncertainty level 1): It tries to look for only matching genera, previously accepted (but now invalid) taxonomic names and misspelled input} +#' \item{(uncertainty level 2): It removed parts between brackets, strips off words from the end one by one and re-evaluates the input with all previous rules} +#' \item{(uncertainty level 3): It strips off words from the start one by one and tries any part of the name} #' } #' #' You can also use e.g. \code{as.mo(..., allow_uncertain = 1)} to only allow up to level 1 uncertainty. @@ -281,7 +278,7 @@ is.mo <- function(x) { #' @importFrom dplyr %>% pull left_join n_distinct progress_estimated filter distinct #' @importFrom data.table data.table as.data.table setkey -#' @importFrom crayon magenta red blue silver italic has_color +#' @importFrom crayon magenta red blue silver italic # param property a column name of AMR::microorganisms # param initial_search logical - is FALSE when coming from uncertain tries, which uses exec_as.mo internally too # param force_mo_history logical - whether found result must be saved with set_mo_history (default FALSE on non-interactive sessions) @@ -486,7 +483,7 @@ exec_as.mo <- function(x, # remove genus as first word x <- gsub("^Genus ", "", x) # allow characters that resemble others - if (uncertainty_level >= 2) { + if (initial_search == FALSE) { x <- tolower(x) x <- gsub("[iy]+", "[iy]+", x) x <- gsub("(c|k|q|qu|s|z|x|ks)+", "(c|k|q|qu|s|z|x|ks)+", x) @@ -768,31 +765,24 @@ exec_as.mo <- function(x, } next } - if (grepl("[sS]almonella [A-Z][a-z]+ ?.*", x_backup_without_spp[i], ignore.case = FALSE)) { + if (x_backup_without_spp[i] %like% "salmonella [a-z]+ ?.*") { if (x_backup_without_spp[i] %like% "Salmonella group") { # Salmonella Group A to Z, just return S. species for now x[i] <- microorganismsDT[mo == 'B_SLMNL', ..property][[1]][1L] if (initial_search == TRUE) { set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history) } - options(mo_renamed = c(getOption("mo_renamed"), - magenta(paste0("NOTE: ", - italic("Salmonella"), " ", trimws(gsub("Salmonella", "", x_backup_without_spp[i])), - " was considered ", - italic("Salmonella species"), - " (B_SLMNL)")))) - } else { + } else if (grepl("[sS]almonella [A-Z][a-z]+ ?.*", x_backup_without_spp[i], ignore.case = FALSE)) { # Salmonella with capital letter species like "Salmonella Goettingen" - they're all S. enterica x[i] <- microorganismsDT[mo == 'B_SLMNL_ENT', ..property][[1]][1L] if (initial_search == TRUE) { set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history) } - options(mo_renamed = c(getOption("mo_renamed"), - magenta(paste0("NOTE: ", - italic("Salmonella"), " ", trimws(gsub("Salmonella", "", x_backup_without_spp[i])), - " was considered a subspecies of ", - italic("Salmonella enterica"), - " (B_SLMNL_ENT)")))) + uncertainties <- rbind(uncertainties, + data.frame(uncertainty = 1, + input = x_backup_without_spp[i], + fullname = microorganismsDT[mo == "B_SLMNL_ENT", fullname][[1]], + mo = "B_SLMNL_ENT")) } next } @@ -1041,9 +1031,27 @@ exec_as.mo <- function(x, } return(x) } + + # (2) Try with misspelled input ---- + # just rerun with initial_search = FALSE will used the extensive regex part above + found <- suppressMessages(suppressWarnings(exec_as.mo(a.x_backup, initial_search = FALSE, allow_uncertain = FALSE))) + if (!empty_result(found)) { + found_result <- found + found <- microorganismsDT[mo == found, ..property][[1]] + uncertainties <<- rbind(uncertainties, + data.frame(uncertainty = 1, + input = a.x_backup, + fullname = microorganismsDT[mo == found_result[1L], fullname][[1]], + mo = found_result[1L])) + if (initial_search == TRUE) { + set_mo_history(a.x_backup, get_mo_code(found[1L], property), 1, force = force_mo_history) + } + return(found[1L]) + } } if (uncertainty_level >= 2) { + # (3) look for genus only, part of name ---- if (nchar(g.x_backup_without_spp) > 4 & !b.x_trimmed %like% " ") { if (!grepl("^[A-Z][a-z]+", b.x_trimmed, ignore.case = FALSE)) { @@ -1286,10 +1294,11 @@ exec_as.mo <- function(x, post_Becker <- c("argensis", "caeli", "cornubiensis", "edaphicus") if (any(x %in% MOs_staph[species %in% post_Becker, ..property][[1]])) { - warning("Becker ", italic("et al."), " (2014, 2019) does not contain species named after their publication: ", + warning("Becker ", italic("et al."), " (2014, 2019) does not contain these species named after their publication: ", italic(paste("S.", sort(mo_species(unique(x[x %in% MOs_staph[species %in% post_Becker, ..property][[1]]]))), collapse = ", ")), + ".", call. = FALSE, immediate. = TRUE) } @@ -1352,15 +1361,7 @@ exec_as.mo <- function(x, } if (length(mo_renamed()) > 0) { - if (has_color()) { - notes <- getOption("mo_renamed") - } else { - notes <- mo_renamed() - } - notes <- sort(notes) - for (i in 1:length(notes)) { - base::message(blue(paste("NOTE:", notes[i]))) - } + print(mo_renamed()) } x @@ -1387,9 +1388,14 @@ was_renamed <- function(name_old, name_new, ref_old = "", ref_new = "", mo = "") } else { mo <- "" } - msg <- paste0(italic(name_old), ref_old, " was renamed ", italic(name_new), ref_new, mo) - msg <- gsub("et al.", italic("et al."), msg) - options(mo_renamed = c(getOption("mo_renamed"), sort(msg))) + old_values <- paste0(italic(name_old), ref_old) + old_values <- gsub("et al.", italic("et al."), old_values) + new_values <- paste0(italic(name_new), ref_new, mo) + new_values <- gsub("et al.", italic("et al."), new_values) + + names(new_values) <- old_values + total <- c(getOption("mo_renamed"), new_values) + options(mo_renamed = total[order(names(total))]) } #' @exportMethod print.mo @@ -1451,6 +1457,9 @@ mo_failures <- function() { #' @importFrom crayon italic #' @export mo_uncertainties <- function() { + if (is.null(getOption("mo_uncertainties"))) { + return(NULL) + } structure(.Data = as.data.frame(getOption("mo_uncertainties"), stringsAsFactors = FALSE), class = c("mo_uncertainties", "data.frame")) } @@ -1463,8 +1472,8 @@ print.mo_uncertainties <- function(x, ...) { if (NROW(x) == 0) { return(NULL) } - cat(paste0(bold(nrow(x), "unique result(s) guessed with uncertainty:"), - "\n(1 = ", green("renamed"), + cat(paste0(bold(nr2char(nrow(x)), paste0("unique result", ifelse(nrow(x) > 1, "s", ""), " guessed with uncertainty:")), + "\n(1 = ", green("renamed/misspelled"), ", 2 = ", yellow("uncertain"), ", 3 = ", red("very uncertain"), ")\n")) @@ -1489,10 +1498,18 @@ print.mo_uncertainties <- function(x, ...) { } #' @rdname as.mo +#' @importFrom crayon strip_style #' @export mo_renamed <- function() { - structure(.Data = strip_style(gsub("was renamed", "->", getOption("mo_renamed"), fixed = TRUE)), - class = c("mo_renamed", "character")) + items <- getOption("mo_renamed") + if (is.null(items)) { + return(NULL) + } + + items <- strip_style(items) + names(items) <- strip_style(names(items)) + structure(.Data = items, + class = c("mo_renamed", "character")) } #' @exportMethod print.mo_renamed @@ -1500,7 +1517,8 @@ mo_renamed <- function() { #' @export #' @noRd print.mo_renamed <- function(x, ...) { - cat(blue(paste(getOption("mo_renamed"), collapse = "\n"))) + items <- getOption("mo_renamed") + base::message(blue(paste("NOTE:", names(items), "was renamed", items, collapse = "\n"), collapse = "\n")) } nr2char <- function(x) { @@ -1540,3 +1558,15 @@ translate_allow_uncertain <- function(allow_uncertain) { } allow_uncertain } + +get_mo_failures_uncertainties_renamed <- function() { + list(failures = getOption("mo_failures"), + uncertainties = getOption("mo_uncertainties"), + renamed = getOption("mo_renamed")) +} + +load_mo_failures_uncertainties_renamed <- function(metadata) { + options("mo_failures" = metadata$failures) + options("mo_uncertainties" = metadata$uncertainties) + options("mo_renamed" = metadata$renamed) +} diff --git a/R/mo_property.R b/R/mo_property.R index 4dfac1fd..8e72cabe 100755 --- a/R/mo_property.R +++ b/R/mo_property.R @@ -148,7 +148,9 @@ mo_fullname <- mo_name #' @importFrom dplyr %>% mutate pull #' @export mo_shortname <- function(x, language = get_locale(), ...) { - x.mo <- as.mo(x, ...) + x.mo <- AMR::as.mo(x, ...) + metadata <- get_mo_failures_uncertainties_renamed() + # get first char of genus and complete species in English shortnames <- paste0(substr(mo_genus(x.mo, language = NULL), 1, 1), ". ", mo_species(x.mo, language = NULL)) @@ -158,6 +160,7 @@ mo_shortname <- function(x, language = get_locale(), ...) { # exceptions for Streptococci shortnames[shortnames %like% "S. group [ABCDFGHK]"] <- paste0("G", gsub("S. group ([ABCDFGHK])", "\\1", shortnames[shortnames %like% "S. group [ABCDFGHK]"]), "S") + load_mo_failures_uncertainties_renamed(metadata) translate_AMR(shortnames, language = language, only_unknown = FALSE) } @@ -218,8 +221,10 @@ mo_type <- function(x, language = get_locale(), ...) { #' @rdname mo_property #' @export mo_gramstain <- function(x, language = get_locale(), ...) { - x.mo <- as.mo(x, ...) - x.phylum <- mo_phylum(x.mo, language = NULL) + x.mo <- AMR::as.mo(x, ...) + metadata <- get_mo_failures_uncertainties_renamed() + + x.phylum <- mo_phylum(x.mo) # DETERMINE GRAM STAIN FOR BACTERIA # Source: https://itis.gov/servlet/SingleRpt/SingleRpt?search_topic=TSN&search_value=956097 # It says this: @@ -232,13 +237,15 @@ mo_gramstain <- function(x, language = get_locale(), ...) { # Phylum Tenericutes (Murray, 1984) x <- NA_character_ # make all bacteria Gram negative - x[mo_kingdom(x.mo, language = NULL) == "Bacteria"] <- "Gram-negative" + x[mo_kingdom(x.mo) == "Bacteria"] <- "Gram-negative" # overwrite these phyla with Gram positive x[x.phylum %in% c("Actinobacteria", "Chloroflexi", "Firmicutes", "Tenericutes") | x.mo == "B_GRAMP"] <- "Gram-positive" + + load_mo_failures_uncertainties_renamed(metadata) translate_AMR(x, language = language, only_unknown = FALSE) } @@ -276,7 +283,9 @@ mo_rank <- function(x, ...) { #' @export mo_taxonomy <- function(x, language = get_locale(), ...) { x <- AMR::as.mo(x, ...) - base::list(kingdom = AMR::mo_kingdom(x, language = language), + metadata <- get_mo_failures_uncertainties_renamed() + + result <- base::list(kingdom = AMR::mo_kingdom(x, language = language), phylum = AMR::mo_phylum(x, language = language), class = AMR::mo_class(x, language = language), order = AMR::mo_order(x, language = language), @@ -284,12 +293,17 @@ mo_taxonomy <- function(x, language = get_locale(), ...) { genus = AMR::mo_genus(x, language = language), species = AMR::mo_species(x, language = language), subspecies = AMR::mo_subspecies(x, language = language)) + + load_mo_failures_uncertainties_renamed(metadata) + result } #' @rdname mo_property #' @export mo_synonyms <- function(x, ...) { - x <- as.mo(x, ...) + x <- AMR::as.mo(x, ...) + metadata <- get_mo_failures_uncertainties_renamed() + IDs <- AMR::mo_property(x = x, property = "col_id", language = NULL) syns <- lapply(IDs, function(col_id) { res <- sort(AMR::microorganisms.old[which(AMR::microorganisms.old$col_id_new == col_id), "fullname"]) @@ -301,16 +315,21 @@ mo_synonyms <- function(x, ...) { }) if (length(syns) > 1) { names(syns) <- mo_fullname(x) - syns + result <- syns } else { - unlist(syns) + result <- unlist(syns) } + + load_mo_failures_uncertainties_renamed(metadata) + result } #' @rdname mo_property #' @export mo_info <- function(x, language = get_locale(), ...) { x <- AMR::as.mo(x, ...) + metadata <- get_mo_failures_uncertainties_renamed() + info <- lapply(x, function(y) c(mo_taxonomy(y, language = language), list(synonyms = mo_synonyms(y), @@ -318,10 +337,13 @@ mo_info <- function(x, language = get_locale(), ...) { ref = mo_ref(y)))) if (length(info) > 1) { names(info) <- mo_fullname(x) - info + result <- info } else { - info[[1L]] + result <- info[[1L]] } + + load_mo_failures_uncertainties_renamed(metadata) + result } #' @rdname mo_property @@ -330,6 +352,8 @@ mo_info <- function(x, language = get_locale(), ...) { #' @export mo_url <- function(x, open = FALSE, ...) { mo <- AMR::as.mo(x = x, ... = ...) + metadata <- get_mo_failures_uncertainties_renamed() + df <- data.frame(mo, stringsAsFactors = FALSE) %>% left_join(select(AMR::microorganisms, mo, source, species_id), by = "mo") %>% mutate(url = case_when(source == "CoL" ~ @@ -347,6 +371,8 @@ mo_url <- function(x, open = FALSE, ...) { } browseURL(u[1L]) } + + load_mo_failures_uncertainties_renamed(metadata) u } diff --git a/R/portion.R b/R/portion.R index 18e2d00c..6599fec0 100755 --- a/R/portion.R +++ b/R/portion.R @@ -27,36 +27,61 @@ #' @param ... one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with \code{\link{as.rsi}} if needed. Use multiple columns to calculate (the lack of) co-resistance: the probability where one of two drugs have a resistant or susceptible result. See Examples. #' @param minimum the minimum allowed number of available (tested) isolates. Any isolate count lower than \code{minimum} will return \code{NA} with a warning. The default number of \code{30} isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source. #' @param as_percent a logical to indicate whether the output must be returned as a hundred fold with \% sign (a character). A value of \code{0.123456} will then be returned as \code{"12.3\%"}. -#' @param also_single_tested a logical to indicate whether for combination therapies also observations should be included where not all antibiotics were tested, but at least one of the tested antibiotics contains a target interpretation (e.g. S in case of \code{portion_S} and R in case of \code{portion_R}). \strong{This could lead to selection bias.} +#' @param only_all_tested (for combination therapies, i.e. using more than one variable for \code{...}) a logical to indicate that isolates must be tested for all antibiotics, see section \emph{Combination therapy} below #' @param data a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}}) #' @param translate_ab a column name of the \code{\link{antibiotics}} data set to translate the antibiotic abbreviations to, using \code{\link{ab_property}} #' @inheritParams ab_property #' @param combine_SI a logical to indicate whether all values of S and I must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter \code{combine_IR}, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see section 'Interpretation of S, I and R' below. Default is \code{TRUE}. #' @param combine_IR a logical to indicate whether all values of I and R must be merged into one, so the output only consists of S vs. I+R (susceptible vs. non-susceptible). This is outdated, see parameter \code{combine_SI}. #' @inheritSection as.rsi Interpretation of S, I and R -#' @details \strong{Remember that you should filter your table to let it contain only first isolates!} Use \code{\link{first_isolate}} to determine them in your data set. +#' @details \strong{Remember that you should filter your table to let it contain only first isolates!} This is needed to exclude duplicates and to reduce selection bias. Use \code{\link{first_isolate}} to determine them in your data set. #' #' These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. \emph{Low counts can infuence the outcome - these \code{portion} functions may camouflage this, since they only return the portion albeit being dependent on the \code{minimum} parameter.} #' #' The function \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each group and each variable with class \code{"rsi"}. #' #' The function \code{rsi_df} works exactly like \code{portion_df}, but adds the number of isolates. -#' \if{html}{ -# (created with https://www.latex4technics.com/) -#' \cr\cr -#' To calculate the probability (\emph{p}) of susceptibility of one antibiotic, we use this formula: -#' \out{
}\figure{combi_therapy_2.png}\out{
} -#' To calculate the probability (\emph{p}) of susceptibility of more antibiotics (i.e. combination therapy), we need to check whether one of them has a susceptible result (as numerator) and count all cases where all antibiotics were tested (as denominator). \cr -#' \cr -#' For two antibiotics: -#' \out{
}\figure{combi_therapy_2.png}\out{
} -#' \cr -#' For three antibiotics: -#' \out{
}\figure{combi_therapy_2.png}\out{
} -#' \cr -#' And so on. +#' @section Combination therapy: +#' When using more than one variable for \code{...} (= combination therapy)), use \code{only_all_tested} to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antibiotics, Antibiotic A and Antibiotic B, about how \code{portion_SI} works to calculate the \%SI: +#' +#' \preformatted{ +#' ------------------------------------------------------------------------- +#' only_all_tested = FALSE only_all_tested = TRUE +#' Antibiotic Antibiotic ----------------------- ----------------------- +#' A B include as include as include as include as +#' numerator denominator numerator denominator +#' ---------- ---------- ---------- ----------- ---------- ----------- +#' S S X X X X +#' I S X X X X +#' R S X X X X +#' not tested S X X - - +#' S I X X X X +#' I I X X X X +#' R I X X X X +#' not tested I X X - - +#' S R X X X X +#' I R X X X X +#' R R - X - X +#' not tested R - - - - +#' S not tested X X - - +#' I not tested X X - - +#' R not tested - - - - +#' not tested not tested - - - - +#' ------------------------------------------------------------------------- #' } #' +#' Please note that for \code{only_all_tested = TRUE} applies that: +#' \preformatted{ +#' count_S() + count_I() + count_R() == count_all() +#' portion_S() + portion_I() + portion_R() == 1 +#' } +#' and that for \code{only_all_tested = FALSE} applies that: +#' \preformatted{ +#' count_S() + count_I() + count_R() >= count_all() +#' portion_S() + portion_I() + portion_R() >= 1 +#' } +#' +#' Using \code{only_all_tested} has no impact when only using one antibiotic as input. #' @source \strong{M39 Analysis and Presentation of Cumulative Antimicrobial Susceptibility Test Data, 4th Edition}, 2014, \emph{Clinical and Laboratory Standards Institute (CLSI)}. \url{https://clsi.org/standards/products/microbiology/documents/m39/}. #' #' Wickham H. \strong{Tidy Data.} The Journal of Statistical Software, vol. 59, 2014. \url{http://vita.had.co.nz/papers/tidy-data.html} @@ -89,7 +114,7 @@ #' #' septic_patients %>% #' group_by(hospital_id) %>% -#' summarise(p = portion_S(CIP), +#' summarise(p = portion_SI(CIP), #' n = n_rsi(CIP)) # n_rsi works like n_distinct in dplyr #' #' septic_patients %>% @@ -103,32 +128,38 @@ #' #' # Calculate co-resistance between amoxicillin/clav acid and gentamicin, #' # so we can see that combination therapy does a lot more than mono therapy: -#' septic_patients %>% portion_S(AMC) # S = 71.4% -#' septic_patients %>% count_all(AMC) # n = 1879 +#' septic_patients %>% portion_SI(AMC) # %SI = 76.3% +#' septic_patients %>% count_all(AMC) # n = 1879 #' -#' septic_patients %>% portion_S(GEN) # S = 74.0% -#' septic_patients %>% count_all(GEN) # n = 1855 +#' septic_patients %>% portion_SI(GEN) # %SI = 75.4% +#' septic_patients %>% count_all(GEN) # n = 1855 #' -#' septic_patients %>% portion_S(AMC, GEN) # S = 92.3% -#' septic_patients %>% count_all(AMC, GEN) # n = 1798 +#' septic_patients %>% portion_SI(AMC, GEN) # %SI = 94.1% +#' septic_patients %>% count_all(AMC, GEN) # n = 1939 #' -#' # Using `also_single_tested` can be useful ... +#' +#' # See Details on how `only_all_tested` works. Example: #' septic_patients %>% -#' portion_S(AMC, GEN, -#' also_single_tested = TRUE) # S = 92.6% -#' # ... but can also lead to selection bias - the data only has 2,000 rows: +#' summarise(numerator = count_SI(AMC, GEN), +#' denominator = count_all(AMC, GEN), +#' portion = portion_SI(AMC, GEN)) +#' # numerator denominator portion +#' # 1764 1936 0.9408 #' septic_patients %>% -#' count_all(AMC, GEN, -#' also_single_tested = TRUE) # n = 2555 +#' summarise(numerator = count_SI(AMC, GEN, only_all_tested = TRUE), +#' denominator = count_all(AMC, GEN, only_all_tested = TRUE), +#' portion = portion_SI(AMC, GEN, only_all_tested = TRUE)) +#' # numerator denominator portion +#' # 1687 1798 0.9383 #' #' #' septic_patients %>% #' group_by(hospital_id) %>% -#' summarise(cipro_p = portion_S(CIP, as_percent = TRUE), +#' summarise(cipro_p = portion_SI(CIP, as_percent = TRUE), #' cipro_n = count_all(CIP), -#' genta_p = portion_S(GEN, as_percent = TRUE), +#' genta_p = portion_SI(GEN, as_percent = TRUE), #' genta_n = count_all(GEN), -#' combination_p = portion_S(CIP, GEN, as_percent = TRUE), +#' combination_p = portion_SI(CIP, GEN, as_percent = TRUE), #' combination_n = count_all(CIP, GEN)) #' #' # Get portions S/I/R immediately of all rsi columns @@ -155,13 +186,12 @@ portion_R <- function(..., minimum = 30, as_percent = FALSE, - also_single_tested = FALSE) { + only_all_tested = FALSE) { rsi_calc(..., - type = "R", - include_I = FALSE, + ab_result = "R", minimum = minimum, as_percent = as_percent, - also_single_tested = also_single_tested, + only_all_tested = only_all_tested, only_count = FALSE) } @@ -170,13 +200,12 @@ portion_R <- function(..., portion_IR <- function(..., minimum = 30, as_percent = FALSE, - also_single_tested = FALSE) { + only_all_tested = FALSE) { rsi_calc(..., - type = "R", - include_I = TRUE, + ab_result = c("I", "R"), minimum = minimum, as_percent = as_percent, - also_single_tested = also_single_tested, + only_all_tested = only_all_tested, only_count = FALSE) } @@ -185,13 +214,12 @@ portion_IR <- function(..., portion_I <- function(..., minimum = 30, as_percent = FALSE, - also_single_tested = FALSE) { + only_all_tested = FALSE) { rsi_calc(..., - type = "I", - include_I = FALSE, + ab_result = "I", minimum = minimum, as_percent = as_percent, - also_single_tested = also_single_tested, + only_all_tested = only_all_tested, only_count = FALSE) } @@ -200,13 +228,12 @@ portion_I <- function(..., portion_SI <- function(..., minimum = 30, as_percent = FALSE, - also_single_tested = FALSE) { + only_all_tested = FALSE) { rsi_calc(..., - type = "S", - include_I = TRUE, + ab_result = c("S", "I"), minimum = minimum, as_percent = as_percent, - also_single_tested = also_single_tested, + only_all_tested = only_all_tested, only_count = FALSE) } @@ -215,13 +242,12 @@ portion_SI <- function(..., portion_S <- function(..., minimum = 30, as_percent = FALSE, - also_single_tested = FALSE) { + only_all_tested = FALSE) { rsi_calc(..., - type = "S", - include_I = FALSE, + ab_result = "S", minimum = minimum, as_percent = as_percent, - also_single_tested = also_single_tested, + only_all_tested = only_all_tested, only_count = FALSE) } diff --git a/R/rsi.R b/R/rsi.R index 694db988..3abec415 100755 --- a/R/rsi.R +++ b/R/rsi.R @@ -36,7 +36,7 @@ #' #' The function \code{is.rsi.eligible} returns \code{TRUE} when a columns contains at most 5\% invalid antimicrobial interpretations (not S and/or I and/or R), and \code{FALSE} otherwise. The threshold of 5\% can be set with the \code{threshold} parameter. #' @section Interpretation of S, I and R: -#' In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations". +#' In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (\url{http://www.eucast.org/newsiandr/}). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations". #' #' \itemize{ #' \item{\strong{S} - }{Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.} @@ -46,9 +46,7 @@ #' #' Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection. #' -#' Source: \url{http://www.eucast.org/newsiandr/}. -#' -#' \strong{This AMR package honours this new insight.} +#' This AMR package honours this new insight. Use \code{\link{portion_SI}} to determine antimicrobial susceptibility and \code{\link{count_SI}} to count susceptible isolates. #' @return Ordered factor with new class \code{rsi} #' @keywords rsi #' @export diff --git a/R/rsi_calc.R b/R/rsi_calc.R index 19960479..74e2151f 100755 --- a/R/rsi_calc.R +++ b/R/rsi_calc.R @@ -38,30 +38,29 @@ dots2vars <- function(...) { #' @importFrom dplyr %>% pull all_vars any_vars filter_all funs mutate_all rsi_calc <- function(..., - type, - include_I, - minimum, - as_percent, - also_single_tested, - only_count) { + ab_result, + minimum = 0, + as_percent = FALSE, + only_all_tested = FALSE, + only_count = FALSE) { data_vars <- dots2vars(...) - if (!is.logical(include_I)) { - stop('`include_I` must be logical', call. = FALSE) - } if (!is.numeric(minimum)) { stop('`minimum` must be numeric', call. = FALSE) } if (!is.logical(as_percent)) { stop('`as_percent` must be logical', call. = FALSE) } - if (!is.logical(also_single_tested)) { - stop('`also_single_tested` must be logical', call. = FALSE) + if (!is.logical(only_all_tested)) { + stop('`only_all_tested` must be logical', call. = FALSE) } dots_df <- ...elt(1) # it needs this evaluation dots <- base::eval(base::substitute(base::alist(...))) + if ("also_single_tested" %in% names(dots)) { + stop("`also_single_tested` was replaced by `only_all_tested`. Please read Details in the help page (`?portion`) as this may have a considerable impact on your analysis.", call. = FALSE) + } ndots <- length(dots) if ("data.frame" %in% class(dots_df)) { @@ -99,8 +98,7 @@ rsi_calc <- function(..., print_warning <- FALSE - type_trans <- as.integer(as.rsi(type)) - type_others <- base::setdiff(1:3, type_trans) + ab_result <- as.rsi(ab_result) if (is.data.frame(x)) { rsi_integrity_check <- character(0) @@ -108,43 +106,38 @@ rsi_calc <- function(..., # check integrity of columns: force rsi class if (!is.rsi(x %>% pull(i))) { rsi_integrity_check <- c(rsi_integrity_check, x %>% pull(i) %>% as.character()) - x[, i] <- suppressWarnings(as.rsi(x[, i])) # warning will be given later + x[, i] <- suppressWarnings(x %>% pull(i) %>% as.rsi()) # warning will be given later print_warning <- TRUE } - x[, i] <- x %>% pull(i) %>% as.integer() + #x[, i] <- x %>% pull(i) } if (length(rsi_integrity_check) > 0) { # this will give a warning for invalid results, of all input columns (so only 1 warning) rsi_integrity_check <- as.rsi(rsi_integrity_check) } - if (include_I == TRUE) { - x <- x %>% mutate_all(funs(ifelse(. == 2, type_trans, .))) - } - - if (also_single_tested == TRUE) { - # THE CHANCE THAT AT LEAST ONE RESULT IS type - found <- x %>% filter_all(any_vars(. == type_trans)) %>% nrow() - # THE CHANCE THAT AT LEAST ONE RESULT IS type OR ALL ARE TESTED - total <- found + x %>% filter_all(all_vars(. %in% type_others)) %>% nrow() + # THE CHANCE THAT AT LEAST ONE RESULT IS ab_result + #numerator <- x %>% filter_all(any_vars(. %in% ab_result)) %>% nrow() + if (only_all_tested == TRUE) { + # THE NUMBER OF ISOLATES WHERE *ALL* ABx ARE S/I/R + x_filtered <- x %>% filter_all(all_vars(!is.na(.))) + numerator <- x_filtered %>% filter_all(any_vars(. %in% ab_result)) %>% nrow() + denominator <- x_filtered %>% nrow() } else { - x <- apply(X = x, - MARGIN = 1, - FUN = min) - found <- sum(as.integer(x) == type_trans, na.rm = TRUE) - total <- length(x) - sum(is.na(x)) + # THE NUMBER OF ISOLATES WHERE *ANY* ABx IS S/I/R + other_values <- base::setdiff(c(NA, levels(ab_result)), ab_result) + other_values_filter <- base::apply(x, 1, function(y) { base::all(y %in% other_values) & base::any(is.na(y)) }) + numerator <- x %>% filter_all(any_vars(. %in% ab_result)) %>% nrow() + denominator <- x %>% filter(!other_values_filter) %>% nrow() } } else { + # x is not a data.frame if (!is.rsi(x)) { x <- as.rsi(x) print_warning <- TRUE } - x <- as.integer(x) - if (include_I == TRUE) { - x[x == 2] <- type_trans - } - found <- sum(x == type_trans, na.rm = TRUE) - total <- length(x) - sum(is.na(x)) + numerator <- sum(x %in% ab_result, na.rm = TRUE) + denominator <- sum(x %in% levels(ab_result), na.rm = TRUE) } if (print_warning == TRUE) { @@ -153,20 +146,23 @@ rsi_calc <- function(..., } if (only_count == TRUE) { - return(found) + return(numerator) } - if (total < minimum) { - warning("Introducing NA: only ", total, " results available for ", data_vars, " (minimum set to ", minimum, ").", call. = FALSE) - result <- NA + if (denominator < minimum) { + if (data_vars != "") { + data_vars <- paste(" for", data_vars) + } + warning("Introducing NA: only ", denominator, " results available", data_vars, " (minimum set to ", minimum, ").", call. = FALSE) + fraction <- NA } else { - result <- found / total + fraction <- numerator / denominator } if (as_percent == TRUE) { - percent(result, force_zero = TRUE) + percent(fraction, force_zero = TRUE) } else { - result + fraction } } diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index 370609a0..8a234d0d 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.1.9004 + 0.7.1.9005 diff --git a/docs/articles/AMR.html b/docs/articles/AMR.html index 6496de6a..a4c0afd1 100644 --- a/docs/articles/AMR.html +++ b/docs/articles/AMR.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 @@ -192,7 +192,7 @@

How to conduct AMR analysis

Matthijs S. Berends

-

23 June 2019

+

01 July 2019

@@ -201,7 +201,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 23 June 2019.

+

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 01 July 2019.

Introduction

@@ -217,21 +217,21 @@ -2019-06-23 +2019-07-01 abcd Escherichia coli S S -2019-06-23 +2019-07-01 abcd Escherichia coli S R -2019-06-23 +2019-07-01 efgh Escherichia coli R @@ -327,69 +327,69 @@ -2017-10-01 -O3 +2011-09-06 +Z5 Hospital B Escherichia coli R -R +S S S F -2011-03-09 -U5 -Hospital B -Staphylococcus aureus +2015-03-21 +E7 +Hospital C +Escherichia coli +R +I S S +M + + +2010-08-11 +X6 +Hospital C +Escherichia coli S S +R +S F - -2011-03-26 -N5 -Hospital A -Escherichia coli + +2012-06-16 +E10 +Hospital D +Staphylococcus aureus +R S S S +M + + +2016-12-29 +J3 +Hospital C +Escherichia coli +R +S +S S M -2013-03-11 -O1 -Hospital A -Escherichia coli +2010-04-09 +Q3 +Hospital B +Streptococcus pneumoniae R S -R -R -F - - -2016-05-24 -V5 -Hospital D -Staphylococcus aureus S S -S -S -F - - -2016-09-21 -Z8 -Hospital A -Klebsiella pneumoniae -S -S -R -S F @@ -411,8 +411,8 @@ # # Item Count Percent Cum. Count Cum. Percent # --- ----- ------- -------- ----------- ------------- -# 1 M 10,366 51.8% 10,366 51.8% -# 2 F 9,634 48.2% 20,000 100.0% +# 1 M 10,408 52.0% 10,408 52.0% +# 2 F 9,592 48.0% 20,000 100.0%

So, we can draw at least two conclusions immediately. From a data scientists perspective, the data looks clean: only values M and F. From a researchers perspective: there are slightly more men. Nothing we didn’t already know.

The data is already quite clean, but we still need to transform some variables. The bacteria column now consists of text, and we want to add more variables based on microbial IDs later on. So, we will transform this column to valid IDs. The mutate() function of the dplyr package makes this really easy:

data <- data %>%
@@ -442,14 +442,14 @@
 # Pasteurella multocida (no new changes)
 # Staphylococcus (no new changes)
 # Streptococcus groups A, B, C, G (no new changes)
-# Streptococcus pneumoniae (1,453 new changes)
+# Streptococcus pneumoniae (1,443 new changes)
 # Viridans group streptococci (no new changes)
 # 
 # EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)
-# Table 01: Intrinsic resistance in Enterobacteriaceae (1,298 new changes)
+# Table 01: Intrinsic resistance in Enterobacteriaceae (1,332 new changes)
 # Table 02: Intrinsic resistance in non-fermentative Gram-negative bacteria (no new changes)
 # Table 03: Intrinsic resistance in other Gram-negative bacteria (no new changes)
-# Table 04: Intrinsic resistance in Gram-positive bacteria (2,747 new changes)
+# Table 04: Intrinsic resistance in Gram-positive bacteria (2,723 new changes)
 # Table 08: Interpretive rules for B-lactam agents and Gram-positive cocci (no new changes)
 # Table 09: Interpretive rules for B-lactam agents and Gram-negative rods (no new changes)
 # Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins (no new changes)
@@ -457,24 +457,24 @@
 # Table 13: Interpretive rules for quinolones (no new changes)
 # 
 # Other rules
-# Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (2,176 new changes)
-# Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (121 new changes)
+# Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (2,213 new changes)
+# Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (127 new changes)
 # Non-EUCAST: piperacillin = R where piperacillin/tazobactam = R (no new changes)
 # Non-EUCAST: piperacillin/tazobactam = S where piperacillin = S (no new changes)
 # Non-EUCAST: trimethoprim = R where trimethoprim/sulfa = R (no new changes)
 # Non-EUCAST: trimethoprim/sulfa = S where trimethoprim = S (no new changes)
 # 
 # --------------------------------------------------------------------------
-# EUCAST rules affected 6,468 out of 20,000 rows, making a total of 7,795 edits
+# EUCAST rules affected 6,513 out of 20,000 rows, making a total of 7,838 edits
 # => added 0 test results
 # 
-# => changed 7,795 test results
-#    - 107 test results changed from S to I
-#    - 4,725 test results changed from S to R
-#    - 1,040 test results changed from I to S
-#    - 329 test results changed from I to R
-#    - 1,579 test results changed from R to S
-#    - 15 test results changed from R to I
+# => changed 7,838 test results
+#    - 115 test results changed from S to I
+#    - 4,719 test results changed from S to R
+#    - 1,077 test results changed from I to S
+#    - 335 test results changed from I to R
+#    - 1,573 test results changed from R to S
+#    - 19 test results changed from R to I
 # --------------------------------------------------------------------------
 # 
 # Use verbose = TRUE to get a data.frame with all specified edits instead.
@@ -502,8 +502,8 @@ # 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,644 first isolates (28.2% of total)
-

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

+# => Found 5,719 first isolates (28.6% of total) +

So only 28.6% 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:

@@ -513,7 +513,7 @@

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 M3, 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 S7, sorted on date:

@@ -529,74 +529,74 @@ - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + - - + + @@ -606,10 +606,10 @@ - - + + - + @@ -617,19 +617,19 @@ - - + + - + - - + + @@ -639,7 +639,7 @@
isolate
12010-01-24M3B_ESCHR_COLSSRSTRUE
22010-03-17M3B_ESCHR_COLSSSSFALSE
32010-04-12M3B_ESCHR_COLSSRSFALSE
42010-05-20M3B_ESCHR_COLSSRSFALSE
52010-06-08M3B_ESCHR_COLSSRSFALSE
62010-06-20M32010-01-28S7 B_ESCHR_COL R I S STRUE
22010-02-07S7B_ESCHR_COLSSSR FALSE
32010-03-16S7B_ESCHR_COLRSSSFALSE
42010-10-09S7B_ESCHR_COLSSSSFALSE
52011-01-25S7B_ESCHR_COLRSSSFALSE
62011-02-16S7B_ESCHR_COLSSSSTRUE
72010-09-18M32011-02-24S7 B_ESCHR_COL S S
82010-10-08M32011-03-30S7 B_ESCHR_COLSR S R S
92010-11-05M32011-04-25S7 B_ESCHR_COL S S SSR FALSE
102010-12-23M32011-05-06S7 B_ESCHR_COL S S
-

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(.)) %>% 
@@ -650,7 +650,7 @@
 # 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 15,080 first weighted isolates (75.4% of total)
+# => Found 15,097 first weighted isolates (75.5% of total)
@@ -667,94 +667,94 @@ - - + + - - + + - - + + - + - - + + - - + + - - + + - + - + - - + + - - + + - + - - + + - - - + + + - - + + - + - - + + - + @@ -763,8 +763,20 @@ - - + + + + + + + + + + + + + + @@ -773,25 +785,13 @@ - - - - - - - - - - - -
isolate
12010-01-24M32010-01-28S7 B_ESCHR_COLSS RIS S TRUE TRUE
22010-03-17M32010-02-07S7 B_ESCHR_COL S S SSR FALSE TRUE
32010-04-12M32010-03-16S7 B_ESCHR_COLSS R SSS FALSE TRUE
42010-05-20M32010-10-09S7 B_ESCHR_COL S SRS S FALSEFALSETRUE
52010-06-08M32011-01-25S7 B_ESCHR_COLSS R SSS FALSEFALSETRUE
62010-06-20M32011-02-16S7 B_ESCHR_COLRI S SFALSESSTRUE TRUE
72010-09-18M32011-02-24S7 B_ESCHR_COL S S S S FALSETRUEFALSE
82010-10-08M32011-03-30S7 B_ESCHR_COLSR S R S
92010-11-05M32011-04-25S7B_ESCHR_COLSSSRFALSETRUE
102011-05-06S7 B_ESCHR_COL S SFALSE TRUE
102010-12-23M3B_ESCHR_COLSSSSFALSEFALSE
-

Instead of 1, now 7 isolates are flagged. In total, 75.4% of all isolates are marked ‘first weighted’ - 47.2% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.

+

Instead of 2, now 9 isolates are flagged. In total, 75.5% of all isolates are marked ‘first weighted’ - 46.9% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.

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 15,080 isolates for analysis.

+

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

We can remove unneeded columns:

data_1st <- data_1st %>% 
   select(-c(first, keyab))
@@ -799,7 +799,6 @@
head(data_1st)
- @@ -816,13 +815,12 @@ - - - + + - + @@ -832,62 +830,58 @@ - - - - + + + + - - - + + - - - - - - + + + + + + + + + + + + + + + + + + + + - - - - - - - - - - - - - - - - - - - + + - + @@ -896,19 +890,18 @@ - - - - - + + + + + + - - - - - - - + + + + + @@ -928,9 +921,9 @@
freq(paste(data_1st$genus, data_1st$species))

Or can be used like the dplyr way, which is easier readable:

data_1st %>% freq(genus, species)
-

Frequency table of genus and species from data_1st (15,080 x 13)

+

Frequency table of genus and species from data_1st (15,097 x 13)

Columns: 2
-Length: 15,080 (of which NA: 0 = 0.00%)
+Length: 15,097 (of which NA: 0 = 0.00%)
Unique: 4

Shortest: 16
Longest: 24

@@ -947,33 +940,33 @@ Longest: 24

- - - - + + + + - - - - + + + + - - - - + + + + - - - + + + @@ -984,7 +977,7 @@ Longest: 24

Resistance percentages

The functions portion_S(), portion_SI(), portion_I(), portion_IR() and portion_R() can be used to determine the portion of a specific antimicrobial outcome. As per the EUCAST guideline of 2019, we calculate resistance as the portion of R (portion_R()) and susceptibility as the portion of S and I (portion_SI()). These functions can be used on their own:

data_1st %>% portion_R(AMX)
-# [1] 0.4661804
+# [1] 0.4738027

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

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

- + - + - + - +
date patient_id hospital
12017-10-01O32011-09-06Z5 Hospital B B_ESCHR_COL RRS S S FTRUE
42013-03-11O1Hospital A2015-03-21E7Hospital C B_ESCHR_COL RI SRRFSM Gram-negative Escherichia coli TRUE
52016-05-24V5Hospital DB_STPHY_AURS2010-08-11X6Hospital CB_ESCHR_COL S SR S FGram-negativeEscherichiacoliTRUE
2012-06-16E10Hospital DB_STPHY_AURRSSSM Gram-positive Staphylococcus aureus TRUE
62016-09-21Z8Hospital AB_KLBSL_PNERSRSFGram-negativeKlebsiellapneumoniaeTRUE
72010-09-19H32016-12-29J3 Hospital C B_ESCHR_COL R SRS S M Gram-negativeTRUE
82015-04-27C9Hospital CB_ESCHR_COL2010-04-09Q3Hospital BB_STRPT_PNERR SSSSMGram-negativeEscherichiacoliRFGram-positiveStreptococcuspneumoniae TRUE
1 Escherichia coli7,41449.2%7,41449.2%7,48349.6%7,48349.6%
2 Staphylococcus aureus3,78725.1%11,20174.3%3,67324.3%11,15673.9%
3 Streptococcus pneumoniae2,31915.4%13,52089.7%2,30615.3%13,46289.2%
4 Klebsiella pneumoniae1,56010.3%15,0801,63510.8%15,097 100.0%
Hospital A0.46580160.4810406
Hospital B0.46146530.4714259
Hospital C0.47445260.4625113
Hospital D0.46863340.4753247
@@ -1027,23 +1020,23 @@ Longest: 24

Hospital A -0.4658016 -4547 +0.4810406 +4536 Hospital B -0.4614653 -5255 +0.4714259 +5267 Hospital C -0.4744526 -2329 +0.4625113 +2214 Hospital D -0.4686334 -2949 +0.4753247 +3080 @@ -1063,27 +1056,27 @@ Longest: 24

Escherichia -0.9219045 -0.8950634 -0.9950094 +0.9256982 +0.8929574 +0.9951891 Klebsiella -0.8153846 -0.8935897 -0.9865385 +0.8214067 +0.9033639 +0.9865443 Staphylococcus -0.9176129 -0.9144442 -0.9949828 +0.9229513 +0.9224068 +0.9937381 Streptococcus -0.6196636 +0.6153513 0.0000000 -0.6196636 +0.6153513 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 33eec1ad..97295b95 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 205cf20b..bf1b2b19 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 053f0125..3f4fbeb6 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 1030ab8e..dc9c4aa3 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 3300a7ef..256d165e 100644 --- a/docs/articles/EUCAST.html +++ b/docs/articles/EUCAST.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 @@ -192,7 +192,7 @@

How to apply EUCAST rules

Matthijs S. Berends

-

23 June 2019

+

01 July 2019

diff --git a/docs/articles/MDR.html b/docs/articles/MDR.html index 2db12903..f59d29b5 100644 --- a/docs/articles/MDR.html +++ b/docs/articles/MDR.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 @@ -192,7 +192,7 @@

How to determine multi-drug resistance (MDR)

Matthijs S. Berends

-

23 June 2019

+

01 July 2019

@@ -235,18 +235,18 @@

The data set looks like this now:

head(my_TB_data)
 #   rifampicin isoniazid gatifloxacin ethambutol pyrazinamide moxifloxacin
-# 1          R         S            R          S            S            S
-# 2          I         R            S          S            I            S
-# 3          S         R            R          R            S            R
-# 4          R         S            R          R            I            S
-# 5          I         R            R          S            R            S
-# 6          S         S            S          S            R            R
+# 1          R         R            S          S            R            I
+# 2          R         R            S          R            S            R
+# 3          R         S            S          R            R            R
+# 4          R         R            S          S            S            I
+# 5          R         R            S          S            R            I
+# 6          R         S            R          R            S            S
 #   kanamycin
 # 1         S
-# 2         I
+# 2         S
 # 3         S
-# 4         S
-# 5         S
+# 4         R
+# 5         R
 # 6         S

We can now add the interpretation of MDR-TB to our data set:

my_TB_data$mdr <- mdr_tb(my_TB_data)
@@ -277,40 +277,40 @@ Unique: 5

1 Mono-resistance -3,206 -64.1% -3,206 -64.1% +3,222 +64.4% +3,222 +64.4% 2 Negative -689 -13.8% -3,895 -77.9% +659 +13.2% +3,881 +77.6% 3 Multidrug resistance -578 -11.6% -4,473 -89.5% +589 +11.8% +4,470 +89.4% 4 Poly-resistance -299 -6.0% -4,772 -95.4% +313 +6.3% +4,783 +95.7% 5 Extensive drug resistance -228 -4.6% +217 +4.3% 5,000 100.0% diff --git a/docs/articles/SPSS.html b/docs/articles/SPSS.html index bbbf6767..35c47c15 100644 --- a/docs/articles/SPSS.html +++ b/docs/articles/SPSS.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005
@@ -192,7 +192,7 @@

How to import data from SPSS / SAS / Stata

Matthijs S. Berends

-

23 June 2019

+

01 July 2019

@@ -274,8 +274,7 @@ # [7] "Flucloxacillin" "Flucloxacilline" "Flucloxacillinum" # [10] "Fluorochloroxacillin" ab_atc("floxapen") -# Class 'atc' -# [1] J01CF05
+# [1] "J01CF05"

diff --git a/docs/articles/WHONET.html b/docs/articles/WHONET.html index 94c2e162..e4e054b8 100644 --- a/docs/articles/WHONET.html +++ b/docs/articles/WHONET.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005

@@ -192,7 +192,7 @@

How to work with WHONET data

Matthijs S. Berends

-

23 June 2019

+

01 July 2019

diff --git a/docs/articles/benchmarks.html b/docs/articles/benchmarks.html index 37b86f5a..d950825d 100644 --- a/docs/articles/benchmarks.html +++ b/docs/articles/benchmarks.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 @@ -192,7 +192,7 @@

Benchmarks

Matthijs S. Berends

-

23 June 2019

+

01 July 2019

@@ -217,14 +217,14 @@ times = 10) print(S.aureus, unit = "ms", signif = 2) # Unit: milliseconds -# expr min lq mean median uq max neval -# as.mo("sau") 17.0 18.0 22.0 18.0 18.0 61.0 10 -# as.mo("stau") 66.0 66.0 75.0 66.0 68.0 110.0 10 -# as.mo("staaur") 17.0 18.0 18.0 18.0 18.0 18.0 10 -# as.mo("STAAUR") 18.0 18.0 32.0 18.0 54.0 80.0 10 -# as.mo("S. aureus") 52.0 53.0 57.0 53.0 53.0 96.0 10 -# as.mo("S. aureus") 52.0 53.0 78.0 53.0 110.0 150.0 10 -# as.mo("Staphylococcus aureus") 8.1 8.1 8.2 8.2 8.2 8.3 10 +# expr min lq mean median uq max neval +# as.mo("sau") 18.0 18.0 22 18.0 18.0 61 10 +# as.mo("stau") 65.0 65.0 70 66.0 66.0 110 10 +# as.mo("staaur") 18.0 18.0 33 18.0 62.0 81 10 +# as.mo("STAAUR") 18.0 18.0 18 18.0 18.0 19 10 +# as.mo("S. aureus") 52.0 52.0 61 52.0 53.0 97 10 +# as.mo("S. aureus") 52.0 52.0 71 53.0 97.0 150 10 +# as.mo("Staphylococcus aureus") 8.1 8.1 14 8.1 8.2 63 10

In the table above, all measurements are shown in milliseconds (thousands of seconds). A value of 5 milliseconds means it can determine 200 input values per second. It case of 100 milliseconds, this is only 10 input values per second. The second input is the only one that has to be looked up thoroughly. All the others are known codes (the first one is a WHONET code) or common laboratory codes, or common full organism names like the last one. Full organism names are always preferred.

To achieve this speed, the as.mo function also takes into account the prevalence of human pathogenic microorganisms. The downside is of course that less prevalent microorganisms will be determined less fast. See this example for the ID of Thermus islandicus (B_THERMS_ISL), a bug probably never found before in humans:

T.islandicus <- microbenchmark(as.mo("theisl"),
@@ -237,10 +237,10 @@
 # Unit: milliseconds
 #                         expr min  lq mean median  uq max neval
 #              as.mo("theisl") 390 390  420    440 440 440    10
-#              as.mo("THEISL") 390 390  420    440 440 450    10
-#       as.mo("T. islandicus") 210 250  250    250 260 270    10
-#      as.mo("T.  islandicus") 210 210  240    220 250 410    10
-#  as.mo("Thermus islandicus")  72  72   82     72  73 120    10
+# as.mo("THEISL") 390 390 410 400 440 440 10 +# as.mo("T. islandicus") 210 210 230 220 250 270 10 +# as.mo("T. islandicus") 210 210 240 260 260 280 10 +# as.mo("Thermus islandicus") 72 72 92 73 120 130 10

That takes 6.8 times as much time on average. A value of 100 milliseconds means it can only determine ~10 different input values per second. We can conclude that looking up arbitrary codes of less prevalent microorganisms is the worst way to go, in terms of calculation performance. Full names (like Thermus islandicus) are almost fast - these are the most probable input from most data sets.

In the figure below, we compare Escherichia coli (which is very common) with Prevotella brevis (which is moderately common) and with Thermus islandicus (which is very uncommon):

par(mar = c(5, 16, 4, 2)) # set more space for left margin text (16)
@@ -287,8 +287,8 @@
 print(run_it, unit = "ms", signif = 3)
 # Unit: milliseconds
 #            expr  min   lq mean median   uq  max neval
-#  mo_fullname(x) 1120 1140 1190   1180 1210 1260    10
-

So transforming 500,000 values (!!) of 50 unique values only takes 1.18 seconds (1182 ms). You only lose time on your unique input values.

+# mo_fullname(x) 1050 1050 1100 1090 1120 1230 10 +

So transforming 500,000 values (!!) of 50 unique values only takes 1.09 seconds (1092 ms). You only lose time on your unique input values.

@@ -300,11 +300,11 @@ times = 10) print(run_it, unit = "ms", signif = 3) # Unit: milliseconds -# expr min lq mean median uq max neval -# A 12.90 13.1 18.50 13.60 13.90 63.60 10 -# B 49.90 50.1 52.20 51.10 52.20 62.60 10 -# C 1.49 1.7 1.76 1.73 1.96 1.98 10

-

So going from mo_fullname("Staphylococcus aureus") to "Staphylococcus aureus" takes 0.0017 seconds - it doesn’t even start calculating if the result would be the same as the expected resulting value. That goes for all helper functions:

+# expr min lq mean median uq max neval +# A 13.00 13.20 13.60 13.60 14.00 14.40 10 +# B 49.40 50.00 57.50 51.90 52.40 103.00 10 +# C 1.52 1.72 1.81 1.78 1.98 1.99 10 +

So going from mo_fullname("Staphylococcus aureus") to "Staphylococcus aureus" takes 0.0018 seconds - it doesn’t even start calculating if the result would be the same as the expected resulting value. That goes for all helper functions:

run_it <- microbenchmark(A = mo_species("aureus"),
                          B = mo_genus("Staphylococcus"),
                          C = mo_fullname("Staphylococcus aureus"),
@@ -317,14 +317,14 @@
 print(run_it, unit = "ms", signif = 3)
 # Unit: milliseconds
 #  expr   min    lq  mean median    uq   max neval
-#     A 0.518 0.544 0.630  0.620 0.683 0.752    10
-#     B 0.548 0.650 0.695  0.703 0.728 0.855    10
-#     C 1.530 1.600 1.750  1.780 1.880 1.950    10
-#     D 0.541 0.640 0.690  0.665 0.728 0.857    10
-#     E 0.496 0.545 0.610  0.612 0.680 0.754    10
-#     F 0.523 0.547 0.613  0.580 0.701 0.756    10
-#     G 0.528 0.547 0.586  0.568 0.600 0.743    10
-#     H 0.547 0.553 0.634  0.609 0.670 0.864    10
+# A 0.612 0.623 0.685 0.653 0.789 0.814 10 +# B 0.556 0.575 0.680 0.671 0.689 0.958 10 +# C 1.520 1.710 1.800 1.820 1.950 1.970 10 +# D 0.547 0.665 0.723 0.688 0.811 0.997 10 +# E 0.490 0.541 0.633 0.629 0.748 0.756 10 +# F 0.482 0.569 0.612 0.590 0.663 0.756 10 +# G 0.551 0.558 0.601 0.586 0.632 0.735 10 +# H 0.494 0.564 0.595 0.575 0.608 0.757 10

Of course, when running mo_phylum("Firmicutes") the function has zero knowledge about the actual microorganism, namely S. aureus. But since the result would be "Firmicutes" too, there is no point in calculating the result. And because this package ‘knows’ all phyla of all known bacteria (according to the Catalogue of Life), it can just return the initial value immediately.

@@ -351,13 +351,13 @@ print(run_it, unit = "ms", signif = 4) # Unit: milliseconds # expr min lq mean median uq max neval -# en 43.34 43.72 43.76 43.82 43.93 43.98 10 -# de 45.77 45.82 46.40 45.90 46.21 50.16 10 -# nl 59.12 59.39 60.61 59.81 60.97 65.36 10 -# es 45.35 45.70 55.58 46.30 50.91 90.30 10 -# it 45.54 45.72 47.36 46.02 46.23 57.97 10 -# fr 45.44 45.68 55.49 45.91 46.30 97.86 10 -# pt 45.60 45.68 52.57 45.79 46.17 110.10 10
+# en 43.00 43.12 45.51 44.82 44.89 56.61 10 +# de 46.47 46.99 52.11 47.57 48.11 93.77 10 +# nl 60.86 62.72 67.57 63.69 63.99 108.20 10 +# es 45.74 46.05 52.37 46.42 47.98 103.00 10 +# it 45.84 45.89 51.90 47.66 47.73 94.83 10 +# fr 45.97 46.92 47.44 47.76 47.86 48.49 10 +# pt 45.93 46.77 47.36 47.77 47.93 48.12 10

Currently supported are German, Dutch, Spanish, Italian, French and Portuguese.

diff --git a/docs/articles/benchmarks_files/figure-html/unnamed-chunk-5-1.png b/docs/articles/benchmarks_files/figure-html/unnamed-chunk-5-1.png index b92bce59..e79a5f73 100644 Binary files a/docs/articles/benchmarks_files/figure-html/unnamed-chunk-5-1.png and b/docs/articles/benchmarks_files/figure-html/unnamed-chunk-5-1.png differ diff --git a/docs/articles/freq.html b/docs/articles/freq.html index 76f11103..3da235d3 100644 --- a/docs/articles/freq.html +++ b/docs/articles/freq.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 @@ -192,7 +192,7 @@

How to create frequency tables

Matthijs S. Berends

-

23 June 2019

+

01 July 2019

diff --git a/docs/articles/index.html b/docs/articles/index.html index ff3cfa46..5e1c1d91 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.1.9004 + 0.7.1.9005 diff --git a/docs/articles/resistance_predict.html b/docs/articles/resistance_predict.html index 9046de87..43c05208 100644 --- a/docs/articles/resistance_predict.html +++ b/docs/articles/resistance_predict.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 @@ -192,7 +192,7 @@

How to predict antimicrobial resistance

Matthijs S. Berends

-

23 June 2019

+

01 July 2019

diff --git a/docs/authors.html b/docs/authors.html index c79f7acc..bbdaf4b9 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.1.9004 + 0.7.1.9005 diff --git a/docs/index.html b/docs/index.html index d1b07f56..88449734 100644 --- a/docs/index.html +++ b/docs/index.html @@ -42,7 +42,7 @@ AMR (for R) - 0.7.1.9004 + 0.7.1.9005 diff --git a/docs/news/index.html b/docs/news/index.html index 139669cb..132adec3 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.1.9004 + 0.7.1.9005 @@ -232,10 +232,43 @@ -
+

-AMR 0.7.1.9004 Unreleased +AMR 0.7.1.9005 Unreleased

+
+

+New

+ +

Changed

@@ -246,7 +279,7 @@
  • Fix and speed improvement for mo_shortname()
  • Fix for as.mo() where misspelled input would not be understood
  • -
  • Fix for also_single_tested parameter in count_* functions
  • +
  • Fix for using mo_* functions where the coercion uncertainties and failures would not be available through mo_uncertainties() and mo_failures() anymore
  • @@ -254,20 +287,20 @@

    AMR 0.7.1 2019-06-23

    -
    +

    -New

    +New

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

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

  • @@ -335,9 +368,9 @@

    AMR 0.7.0 2019-06-03

    -
    +

    -New

    +New
    + @@ -452,9 +485,9 @@ Please +

    -New

    +New
    diff --git a/docs/reference/as.ab.html b/docs/reference/as.ab.html index 0f35c0e8..b2fb70b5 100644 --- a/docs/reference/as.ab.html +++ b/docs/reference/as.ab.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005
    diff --git a/docs/reference/as.disk.html b/docs/reference/as.disk.html index d9698d72..b2aa1c90 100644 --- a/docs/reference/as.disk.html +++ b/docs/reference/as.disk.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005
    diff --git a/docs/reference/as.mic.html b/docs/reference/as.mic.html index 0d1524b3..0e02ee0b 100644 --- a/docs/reference/as.mic.html +++ b/docs/reference/as.mic.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005
    diff --git a/docs/reference/as.mo.html b/docs/reference/as.mo.html index 9a42e6ac..e3bfe49a 100644 --- a/docs/reference/as.mo.html +++ b/docs/reference/as.mo.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005
    @@ -322,12 +322,9 @@ This function uses intelligent rules to help getting fast and logical results. I

    This means that looking up human pathogenic microorganisms takes less time than looking up human non-pathogenic microorganisms.

    Uncertain results
    The algorithm can additionally use three different levels of uncertainty to guess valid results. The default is allow_uncertain = TRUE, which is equal to uncertainty level 2. Using allow_uncertain = FALSE will skip all of these additional rules:

      -
    • (uncertainty level 1): It tries to look for only matching genera

    • -
    • (uncertainty level 1): It tries to look for previously accepted (but now invalid) taxonomic names

    • -
    • (uncertainty level 2): It strips off values between brackets and the brackets itself, and re-evaluates the input with all previous rules

    • -
    • (uncertainty level 2): It strips off words from the end one by one and re-evaluates the input with all previous rules

    • -
    • (uncertainty level 3): It strips off words from the start one by one and re-evaluates the input with all previous rules

    • -
    • (uncertainty level 3): It tries any part of the name

    • +
    • (uncertainty level 1): It tries to look for only matching genera, previously accepted (but now invalid) taxonomic names and misspelled input

    • +
    • (uncertainty level 2): It removed parts between brackets, strips off words from the end one by one and re-evaluates the input with all previous rules

    • +
    • (uncertainty level 3): It strips off words from the start one by one and tries any part of the name

    You can also use e.g. as.mo(..., allow_uncertain = 1) to only allow up to level 1 uncertainty.

    Examples:

      diff --git a/docs/reference/as.rsi.html b/docs/reference/as.rsi.html index 2fc17921..5a4dec68 100644 --- a/docs/reference/as.rsi.html +++ b/docs/reference/as.rsi.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 @@ -303,15 +303,14 @@

      Interpretation of S, I and R

      -

      In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".

      +

      In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (http://www.eucast.org/newsiandr/). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".

      • S - Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.

      • I - Susceptible, increased exposure: A microorganism is categorised as "Susceptible, Increased exposure" when there is a high likelihood of therapeutic success because exposure to the agent is increased by adjusting the dosing regimen or by its concentration at the site of infection.

      • R - Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.

      Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.

      -

      Source: http://www.eucast.org/newsiandr/.

      -

      This AMR package honours this new insight.

      +

      This AMR package honours this new insight. Use portion_SI to determine antimicrobial susceptibility and count_SI to count susceptible isolates.

      Read more on our website!

      diff --git a/docs/reference/atc_online.html b/docs/reference/atc_online.html index 52dea325..761c1564 100644 --- a/docs/reference/atc_online.html +++ b/docs/reference/atc_online.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/availability.html b/docs/reference/availability.html index a6a22783..2d22deff 100644 --- a/docs/reference/availability.html +++ b/docs/reference/availability.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/catalogue_of_life.html b/docs/reference/catalogue_of_life.html index a507f2b6..ebbd8feb 100644 --- a/docs/reference/catalogue_of_life.html +++ b/docs/reference/catalogue_of_life.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/catalogue_of_life_version.html b/docs/reference/catalogue_of_life_version.html index b74e7d98..c02e7631 100644 --- a/docs/reference/catalogue_of_life_version.html +++ b/docs/reference/catalogue_of_life_version.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/count.html b/docs/reference/count.html index 2b1f50a1..732c6e31 100644 --- a/docs/reference/count.html +++ b/docs/reference/count.html @@ -81,7 +81,7 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_ AMR (for R) - 0.7.1.9004 + 0.7.1.9005 @@ -243,19 +243,19 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_ -
      count_R(..., also_single_tested = FALSE)
      +    
      count_R(..., only_all_tested = FALSE)
       
      -count_IR(..., also_single_tested = FALSE)
      +count_IR(..., only_all_tested = FALSE)
       
      -count_I(..., also_single_tested = FALSE)
      +count_I(..., only_all_tested = FALSE)
       
      -count_SI(..., also_single_tested = FALSE)
      +count_SI(..., only_all_tested = FALSE)
       
      -count_S(..., also_single_tested = FALSE)
      +count_S(..., only_all_tested = FALSE)
       
      -count_all(..., also_single_tested = FALSE)
      +count_all(..., only_all_tested = FALSE)
       
      -n_rsi(..., also_single_tested = FALSE)
      +n_rsi(..., only_all_tested = FALSE)
       
       count_df(data, translate_ab = "name", language = get_locale(),
         combine_SI = TRUE, combine_IR = FALSE)
      @@ -268,8 +268,8 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_

      one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with as.rsi if needed.

      - also_single_tested -

      a logical to indicate whether for combination therapies also observations should be included where not all antibiotics were tested, but at least one of the tested antibiotics contains a target interpretation (e.g. S in case of portion_S and R in case of portion_R). This could lead to selection bias.

      + only_all_tested +

      (for combination therapies, i.e. using more than one variable for ...) a logical to indicate that isolates must be tested for all antibiotics, see section Combination therapy below

      data @@ -311,15 +311,52 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_

      Interpretation of S, I and R

      -

      In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".

      +

      In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (http://www.eucast.org/newsiandr/). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".

      • S - Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.

      • I - Susceptible, increased exposure: A microorganism is categorised as "Susceptible, Increased exposure" when there is a high likelihood of therapeutic success because exposure to the agent is increased by adjusting the dosing regimen or by its concentration at the site of infection.

      • R - Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.

      Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.

      -

      Source: http://www.eucast.org/newsiandr/.

      -

      This AMR package honours this new insight.

      +

      This AMR package honours this new insight. Use portion_SI to determine antimicrobial susceptibility and count_SI to count susceptible isolates.

      + +

      Combination therapy

      + + +

      When using more than one variable for ... (= combination therapy)), use only_all_tested to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antibiotics, Antibiotic A and Antibiotic B, about how portion_SI works to calculate the %SI:

      +
      +-------------------------------------------------------------------------
      +                        only_all_tested = FALSE   only_all_tested = TRUE
      +Antibiotic  Antibiotic  -----------------------   -----------------------
      +    A           B       include as  include as    include as  include as
      +                        numerator   denominator   numerator   denominator
      +----------  ----------  ----------  -----------   ----------  -----------
      +    S           S           X            X             X            X
      +    I           S           X            X             X            X
      +    R           S           X            X             X            X
      +not tested      S           X            X             -            -
      +    S           I           X            X             X            X
      +    I           I           X            X             X            X
      +    R           I           X            X             X            X
      +not tested      I           X            X             -            -
      +    S           R           X            X             X            X
      +    I           R           X            X             X            X
      +    R           R           -            X             -            X
      +not tested      R           -            -             -            -
      +    S       not tested      X            X             -            -
      +    I       not tested      X            X             -            -
      +    R       not tested      -            -             -            -
      +not tested  not tested      -            -             -            -
      +-------------------------------------------------------------------------
      +
      +

      Please note that for only_all_tested = TRUE applies that:

      +   count_S()  +  count_I()  +  count_R()  == count_all()
      +  portion_S() + portion_I() + portion_R() == 1
      +

      and that for only_all_tested = FALSE applies that:

      +   count_S()  +  count_I()  +  count_R()  >= count_all()
      +  portion_S() + portion_I() + portion_R() >= 1
      +
      +

      Using only_all_tested has no impact when only using one antibiotic as input.

      Read more on our website!

      @@ -351,8 +388,8 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_ # Since n_rsi counts available isolates, you can # calculate back to count e.g. non-susceptible isolates. # This results in the same: -count_IR(septic_patients$AMX) -portion_IR(septic_patients$AMX) * n_rsi(septic_patients$AMX) +count_SI(septic_patients$AMX) +portion_SI(septic_patients$AMX) * n_rsi(septic_patients$AMX) library(dplyr) septic_patients %>% @@ -366,17 +403,17 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_ # Count co-resistance between amoxicillin/clav acid and gentamicin, # so we can see that combination therapy does a lot more than mono therapy. -# Please mind that `portion_S` calculates percentages right away instead. -count_S(septic_patients$AMC) # S = 1342 (71.4%) -count_all(septic_patients$AMC) # n = 1879 +# Please mind that `portion_SI` calculates percentages right away instead. +count_SI(septic_patients$AMC) # 1433 +count_all(septic_patients$AMC) # 1879 -count_S(septic_patients$GEN) # S = 1372 (74.0%) -count_all(septic_patients$GEN) # n = 1855 +count_SI(septic_patients$GEN) # 1399 +count_all(septic_patients$GEN) # 1855 with(septic_patients, - count_S(AMC, GEN)) # S = 1660 (92.3%) -with(septic_patients, # n = 1798 - n_rsi(AMC, GEN)) + count_SI(AMC, GEN)) # 1764 +with(septic_patients, + n_rsi(AMC, GEN)) # 1936 # Get portions S/I/R immediately of all rsi columns septic_patients %>% @@ -404,6 +441,8 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
    • Interpretation of S, I and R
    • +
    • Combination therapy
    • +
    • Read more on our website!
    • See also
    • diff --git a/docs/reference/eucast_rules.html b/docs/reference/eucast_rules.html index 594f83c2..705f6c9c 100644 --- a/docs/reference/eucast_rules.html +++ b/docs/reference/eucast_rules.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/extended-functions.html b/docs/reference/extended-functions.html index 3d8dc804..ce2e53b5 100644 --- a/docs/reference/extended-functions.html +++ b/docs/reference/extended-functions.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/filter_ab_class.html b/docs/reference/filter_ab_class.html index 9064b021..72788170 100644 --- a/docs/reference/filter_ab_class.html +++ b/docs/reference/filter_ab_class.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/first_isolate.html b/docs/reference/first_isolate.html index b056313e..5a72e039 100644 --- a/docs/reference/first_isolate.html +++ b/docs/reference/first_isolate.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/freq.html b/docs/reference/freq.html index f1c60e1d..e4c707f8 100644 --- a/docs/reference/freq.html +++ b/docs/reference/freq.html @@ -81,7 +81,7 @@ top_freq can be used to get the top/bottom n items of a frequency table, with co AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/g.test.html b/docs/reference/g.test.html index 0e0525d6..d4d57e49 100644 --- a/docs/reference/g.test.html +++ b/docs/reference/g.test.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/ggplot_rsi.html b/docs/reference/ggplot_rsi.html index eeb3c741..4c17660c 100644 --- a/docs/reference/ggplot_rsi.html +++ b/docs/reference/ggplot_rsi.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9004 + 0.7.1.9005 diff --git a/docs/reference/guess_ab_col.html b/docs/reference/guess_ab_col.html index 6922e3f4..ce86c053 100644 --- a/docs/reference/guess_ab_col.html +++ b/docs/reference/guess_ab_col.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/index.html b/docs/reference/index.html index 2ed5fc35..c46837c3 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.1.9004 + 0.7.1.9005 diff --git a/docs/reference/join.html b/docs/reference/join.html index caaa5c1b..81e39caf 100644 --- a/docs/reference/join.html +++ b/docs/reference/join.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/key_antibiotics.html b/docs/reference/key_antibiotics.html index 5002897c..114bde04 100644 --- a/docs/reference/key_antibiotics.html +++ b/docs/reference/key_antibiotics.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/kurtosis.html b/docs/reference/kurtosis.html index 5e1791ce..0d731157 100644 --- a/docs/reference/kurtosis.html +++ b/docs/reference/kurtosis.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/like.html b/docs/reference/like.html index 17a7ac50..d7b74259 100644 --- a/docs/reference/like.html +++ b/docs/reference/like.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/mdro.html b/docs/reference/mdro.html index 3e92d9f9..8dfa5a25 100644 --- a/docs/reference/mdro.html +++ b/docs/reference/mdro.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/microorganisms.codes.html b/docs/reference/microorganisms.codes.html index 0139b878..0bc2192b 100644 --- a/docs/reference/microorganisms.codes.html +++ b/docs/reference/microorganisms.codes.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/microorganisms.html b/docs/reference/microorganisms.html index 1b22753b..e86e90b7 100644 --- a/docs/reference/microorganisms.html +++ b/docs/reference/microorganisms.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/microorganisms.old.html b/docs/reference/microorganisms.old.html index a2ce3acd..5024ae93 100644 --- a/docs/reference/microorganisms.old.html +++ b/docs/reference/microorganisms.old.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/mo_property.html b/docs/reference/mo_property.html index 3b82969a..57de2e60 100644 --- a/docs/reference/mo_property.html +++ b/docs/reference/mo_property.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9004 + 0.7.1.9005 diff --git a/docs/reference/mo_source.html b/docs/reference/mo_source.html index eb3961b4..0606ee24 100644 --- a/docs/reference/mo_source.html +++ b/docs/reference/mo_source.html @@ -81,7 +81,7 @@ This is the fastest way to have your organisation (or analysis) specific codes p AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/p.symbol.html b/docs/reference/p.symbol.html index 079db613..6bcaa8c4 100644 --- a/docs/reference/p.symbol.html +++ b/docs/reference/p.symbol.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/portion.html b/docs/reference/portion.html index 58144382..3b723cbb 100644 --- a/docs/reference/portion.html +++ b/docs/reference/portion.html @@ -81,7 +81,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port AMR (for R) - 0.7.1.9004 + 0.7.1.9005 @@ -244,19 +244,19 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
      portion_R(..., minimum = 30, as_percent = FALSE,
      -  also_single_tested = FALSE)
      +  only_all_tested = FALSE)
       
       portion_IR(..., minimum = 30, as_percent = FALSE,
      -  also_single_tested = FALSE)
      +  only_all_tested = FALSE)
       
       portion_I(..., minimum = 30, as_percent = FALSE,
      -  also_single_tested = FALSE)
      +  only_all_tested = FALSE)
       
       portion_SI(..., minimum = 30, as_percent = FALSE,
      -  also_single_tested = FALSE)
      +  only_all_tested = FALSE)
       
       portion_S(..., minimum = 30, as_percent = FALSE,
      -  also_single_tested = FALSE)
      +  only_all_tested = FALSE)
       
       portion_df(data, translate_ab = "name", language = get_locale(),
         minimum = 30, as_percent = FALSE, combine_SI = TRUE,
      @@ -282,8 +282,8 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
             

      a logical to indicate whether the output must be returned as a hundred fold with % sign (a character). A value of 0.123456 will then be returned as "12.3%".

      - also_single_tested -

      a logical to indicate whether for combination therapies also observations should be included where not all antibiotics were tested, but at least one of the tested antibiotics contains a target interpretation (e.g. S in case of portion_S and R in case of portion_R). This could lead to selection bias.

      + only_all_tested +

      (for combination therapies, i.e. using more than one variable for ...) a logical to indicate that isolates must be tested for all antibiotics, see section Combination therapy below

      data @@ -318,35 +318,60 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port

      Details

      -

      Remember that you should filter your table to let it contain only first isolates! Use first_isolate to determine them in your data set.

      +

      Remember that you should filter your table to let it contain only first isolates! This is needed to exclude duplicates and to reduce selection bias. Use first_isolate to determine them in your data set.

      These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the count functions to count isolates. Low counts can infuence the outcome - these portion functions may camouflage this, since they only return the portion albeit being dependent on the minimum parameter.

      The function portion_df takes any variable from data that has an "rsi" class (created with as.rsi) and calculates the portions R, I and S. The resulting tidy data (see Source) data.frame will have three rows (S/I/R) and a column for each group and each variable with class "rsi".

      -

      The function rsi_df works exactly like portion_df, but adds the number of isolates. -

      - To calculate the probability (p) of susceptibility of one antibiotic, we use this formula: -

      - To calculate the probability (p) of susceptibility of more antibiotics (i.e. combination therapy), we need to check whether one of them has a susceptible result (as numerator) and count all cases where all antibiotics were tested (as denominator).
      -
      - For two antibiotics: -
      -
      - For three antibiotics: -
      -
      - And so on.

      +

      The function rsi_df works exactly like portion_df, but adds the number of isolates.

      + +

      Combination therapy

      + + +

      When using more than one variable for ... (= combination therapy)), use only_all_tested to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antibiotics, Antibiotic A and Antibiotic B, about how portion_SI works to calculate the %SI:

      +
      +-------------------------------------------------------------------------
      +                        only_all_tested = FALSE   only_all_tested = TRUE
      +Antibiotic  Antibiotic  -----------------------   -----------------------
      +    A           B       include as  include as    include as  include as
      +                        numerator   denominator   numerator   denominator
      +----------  ----------  ----------  -----------   ----------  -----------
      +    S           S           X            X             X            X
      +    I           S           X            X             X            X
      +    R           S           X            X             X            X
      +not tested      S           X            X             -            -
      +    S           I           X            X             X            X
      +    I           I           X            X             X            X
      +    R           I           X            X             X            X
      +not tested      I           X            X             -            -
      +    S           R           X            X             X            X
      +    I           R           X            X             X            X
      +    R           R           -            X             -            X
      +not tested      R           -            -             -            -
      +    S       not tested      X            X             -            -
      +    I       not tested      X            X             -            -
      +    R       not tested      -            -             -            -
      +not tested  not tested      -            -             -            -
      +-------------------------------------------------------------------------
      +
      +

      Please note that for only_all_tested = TRUE applies that:

      +   count_S()  +  count_I()  +  count_R()  == count_all()
      +  portion_S() + portion_I() + portion_R() == 1
      +

      and that for only_all_tested = FALSE applies that:

      +   count_S()  +  count_I()  +  count_R()  >= count_all()
      +  portion_S() + portion_I() + portion_R() >= 1
      +
      +

      Using only_all_tested has no impact when only using one antibiotic as input.

      Interpretation of S, I and R

      -

      In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".

      +

      In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (http://www.eucast.org/newsiandr/). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".

      • S - Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.

      • I - Susceptible, increased exposure: A microorganism is categorised as "Susceptible, Increased exposure" when there is a high likelihood of therapeutic success because exposure to the agent is increased by adjusting the dosing regimen or by its concentration at the site of infection.

      • R - Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.

      Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.

      -

      Source: http://www.eucast.org/newsiandr/.

      -

      This AMR package honours this new insight.

      +

      This AMR package honours this new insight. Use portion_SI to determine antimicrobial susceptibility and count_SI to count susceptible isolates.

      Read more on our website!

      @@ -380,7 +405,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port septic_patients %>% group_by(hospital_id) %>% - summarise(p = portion_S(CIP), + summarise(p = portion_SI(CIP), n = n_rsi(CIP)) # n_rsi works like n_distinct in dplyr septic_patients %>% @@ -394,32 +419,38 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port # Calculate co-resistance between amoxicillin/clav acid and gentamicin, # so we can see that combination therapy does a lot more than mono therapy: -septic_patients %>% portion_S(AMC) # S = 71.4% -septic_patients %>% count_all(AMC) # n = 1879 +septic_patients %>% portion_SI(AMC) # %SI = 76.3% +septic_patients %>% count_all(AMC) # n = 1879 -septic_patients %>% portion_S(GEN) # S = 74.0% -septic_patients %>% count_all(GEN) # n = 1855 +septic_patients %>% portion_SI(GEN) # %SI = 75.4% +septic_patients %>% count_all(GEN) # n = 1855 -septic_patients %>% portion_S(AMC, GEN) # S = 92.3% -septic_patients %>% count_all(AMC, GEN) # n = 1798 +septic_patients %>% portion_SI(AMC, GEN) # %SI = 94.1% +septic_patients %>% count_all(AMC, GEN) # n = 1939 -# Using `also_single_tested` can be useful ... + +# See Details on how `only_all_tested` works. Example: septic_patients %>% - portion_S(AMC, GEN, - also_single_tested = TRUE) # S = 92.6% -# ... but can also lead to selection bias - the data only has 2,000 rows: + summarise(numerator = count_SI(AMC, GEN), + denominator = count_all(AMC, GEN), + portion = portion_SI(AMC, GEN)) +# numerator denominator portion +# 1764 1936 0.9408 septic_patients %>% - count_all(AMC, GEN, - also_single_tested = TRUE) # n = 2555 + summarise(numerator = count_SI(AMC, GEN, only_all_tested = TRUE), + denominator = count_all(AMC, GEN, only_all_tested = TRUE), + portion = portion_SI(AMC, GEN, only_all_tested = TRUE)) +# numerator denominator portion +# 1687 1798 0.9383 septic_patients %>% group_by(hospital_id) %>% - summarise(cipro_p = portion_S(CIP, as_percent = TRUE), + summarise(cipro_p = portion_SI(CIP, as_percent = TRUE), cipro_n = count_all(CIP), - genta_p = portion_S(GEN, as_percent = TRUE), + genta_p = portion_SI(GEN, as_percent = TRUE), genta_n = count_all(GEN), - combination_p = portion_S(CIP, GEN, as_percent = TRUE), + combination_p = portion_SI(CIP, GEN, as_percent = TRUE), combination_n = count_all(CIP, GEN)) # Get portions S/I/R immediately of all rsi columns @@ -454,6 +485,8 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
    • Details
    • +
    • Combination therapy
    • +
    • Interpretation of S, I and R
    • Read more on our website!
    • diff --git a/docs/reference/read.4D.html b/docs/reference/read.4D.html index f93a3edf..c255e9d8 100644 --- a/docs/reference/read.4D.html +++ b/docs/reference/read.4D.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/resistance_predict.html b/docs/reference/resistance_predict.html index 6b9f0e5e..6fea0ba0 100644 --- a/docs/reference/resistance_predict.html +++ b/docs/reference/resistance_predict.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/rsi_translation.html b/docs/reference/rsi_translation.html index 862b3ad0..e96af83b 100644 --- a/docs/reference/rsi_translation.html +++ b/docs/reference/rsi_translation.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/septic_patients.html b/docs/reference/septic_patients.html index 410350bb..aa05fe8a 100644 --- a/docs/reference/septic_patients.html +++ b/docs/reference/septic_patients.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9004 + 0.7.1.9005 diff --git a/docs/reference/skewness.html b/docs/reference/skewness.html index 54aaf7bd..2e7d66c1 100644 --- a/docs/reference/skewness.html +++ b/docs/reference/skewness.html @@ -81,7 +81,7 @@ When negative: the left tail is longer; the mass of the distribution is concentr AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/docs/reference/translate.html b/docs/reference/translate.html index 676219de..7c38140c 100644 --- a/docs/reference/translate.html +++ b/docs/reference/translate.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.1.9003 + 0.7.1.9005 diff --git a/man/as.mo.Rd b/man/as.mo.Rd index 2bbf53f9..e515628b 100644 --- a/man/as.mo.Rd +++ b/man/as.mo.Rd @@ -88,12 +88,9 @@ This means that looking up human pathogenic microorganisms takes less time than \strong{Uncertain results} \cr The algorithm can additionally use three different levels of uncertainty to guess valid results. The default is \code{allow_uncertain = TRUE}, which is equal to uncertainty level 2. Using \code{allow_uncertain = FALSE} will skip all of these additional rules: \itemize{ - \item{(uncertainty level 1): It tries to look for only matching genera} - \item{(uncertainty level 1): It tries to look for previously accepted (but now invalid) taxonomic names} - \item{(uncertainty level 2): It strips off values between brackets and the brackets itself, and re-evaluates the input with all previous rules} - \item{(uncertainty level 2): It strips off words from the end one by one and re-evaluates the input with all previous rules} - \item{(uncertainty level 3): It strips off words from the start one by one and re-evaluates the input with all previous rules} - \item{(uncertainty level 3): It tries any part of the name} + \item{(uncertainty level 1): It tries to look for only matching genera, previously accepted (but now invalid) taxonomic names and misspelled input} + \item{(uncertainty level 2): It removed parts between brackets, strips off words from the end one by one and re-evaluates the input with all previous rules} + \item{(uncertainty level 3): It strips off words from the start one by one and tries any part of the name} } You can also use e.g. \code{as.mo(..., allow_uncertain = 1)} to only allow up to level 1 uncertainty. diff --git a/man/as.rsi.Rd b/man/as.rsi.Rd index a74f0207..2f19890e 100755 --- a/man/as.rsi.Rd +++ b/man/as.rsi.Rd @@ -52,7 +52,7 @@ The function \code{is.rsi.eligible} returns \code{TRUE} when a columns contains } \section{Interpretation of S, I and R}{ -In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations". +In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (\url{http://www.eucast.org/newsiandr/}). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations". \itemize{ \item{\strong{S} - }{Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.} @@ -62,9 +62,7 @@ In 2019, EUCAST has decided to change the definitions of susceptibility testing Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection. -Source: \url{http://www.eucast.org/newsiandr/}. - -\strong{This AMR package honours this new insight.} +This AMR package honours this new insight. Use \code{\link{portion_SI}} to determine antimicrobial susceptibility and \code{\link{count_SI}} to count susceptible isolates. } \section{Read more on our website!}{ diff --git a/man/count.Rd b/man/count.Rd index 906e365d..f70562e1 100644 --- a/man/count.Rd +++ b/man/count.Rd @@ -15,19 +15,19 @@ Wickham H. \strong{Tidy Data.} The Journal of Statistical Software, vol. 59, 2014. \url{http://vita.had.co.nz/papers/tidy-data.html} } \usage{ -count_R(..., also_single_tested = FALSE) +count_R(..., only_all_tested = FALSE) -count_IR(..., also_single_tested = FALSE) +count_IR(..., only_all_tested = FALSE) -count_I(..., also_single_tested = FALSE) +count_I(..., only_all_tested = FALSE) -count_SI(..., also_single_tested = FALSE) +count_SI(..., only_all_tested = FALSE) -count_S(..., also_single_tested = FALSE) +count_S(..., only_all_tested = FALSE) -count_all(..., also_single_tested = FALSE) +count_all(..., only_all_tested = FALSE) -n_rsi(..., also_single_tested = FALSE) +n_rsi(..., only_all_tested = FALSE) count_df(data, translate_ab = "name", language = get_locale(), combine_SI = TRUE, combine_IR = FALSE) @@ -35,7 +35,7 @@ count_df(data, translate_ab = "name", language = get_locale(), \arguments{ \item{...}{one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with \code{\link{as.rsi}} if needed.} -\item{also_single_tested}{a logical to indicate whether for combination therapies also observations should be included where not all antibiotics were tested, but at least one of the tested antibiotics contains a target interpretation (e.g. S in case of \code{portion_S} and R in case of \code{portion_R}). \strong{This could lead to selection bias.}} +\item{only_all_tested}{(for combination therapies, i.e. using more than one variable for \code{...}) a logical to indicate that isolates must be tested for all antibiotics, see section \emph{Combination therapy} below} \item{data}{a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}})} @@ -66,7 +66,7 @@ The function \code{rsi_df} works exactly like \code{count_df}, but adds the perc } \section{Interpretation of S, I and R}{ -In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations". +In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (\url{http://www.eucast.org/newsiandr/}). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations". \itemize{ \item{\strong{S} - }{Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.} @@ -76,9 +76,51 @@ In 2019, EUCAST has decided to change the definitions of susceptibility testing Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection. -Source: \url{http://www.eucast.org/newsiandr/}. +This AMR package honours this new insight. Use \code{\link{portion_SI}} to determine antimicrobial susceptibility and \code{\link{count_SI}} to count susceptible isolates. +} -\strong{This AMR package honours this new insight.} +\section{Combination therapy}{ + +When using more than one variable for \code{...} (= combination therapy)), use \code{only_all_tested} to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antibiotics, Antibiotic A and Antibiotic B, about how \code{portion_SI} works to calculate the \%SI: + +\preformatted{ +------------------------------------------------------------------------- + only_all_tested = FALSE only_all_tested = TRUE +Antibiotic Antibiotic ----------------------- ----------------------- + A B include as include as include as include as + numerator denominator numerator denominator +---------- ---------- ---------- ----------- ---------- ----------- + S S X X X X + I S X X X X + R S X X X X +not tested S X X - - + S I X X X X + I I X X X X + R I X X X X +not tested I X X - - + S R X X X X + I R X X X X + R R - X - X +not tested R - - - - + S not tested X X - - + I not tested X X - - + R not tested - - - - +not tested not tested - - - - +------------------------------------------------------------------------- +} + +Please note that for \code{only_all_tested = TRUE} applies that: +\preformatted{ + count_S() + count_I() + count_R() == count_all() + portion_S() + portion_I() + portion_R() == 1 +} +and that for \code{only_all_tested = FALSE} applies that: +\preformatted{ + count_S() + count_I() + count_R() >= count_all() + portion_S() + portion_I() + portion_R() >= 1 +} + +Using \code{only_all_tested} has no impact when only using one antibiotic as input. } \section{Read more on our website!}{ @@ -105,8 +147,8 @@ n_rsi(septic_patients$AMX) # Since n_rsi counts available isolates, you can # calculate back to count e.g. non-susceptible isolates. # This results in the same: -count_IR(septic_patients$AMX) -portion_IR(septic_patients$AMX) * n_rsi(septic_patients$AMX) +count_SI(septic_patients$AMX) +portion_SI(septic_patients$AMX) * n_rsi(septic_patients$AMX) library(dplyr) septic_patients \%>\% @@ -120,17 +162,17 @@ septic_patients \%>\% # Count co-resistance between amoxicillin/clav acid and gentamicin, # so we can see that combination therapy does a lot more than mono therapy. -# Please mind that `portion_S` calculates percentages right away instead. -count_S(septic_patients$AMC) # S = 1342 (71.4\%) -count_all(septic_patients$AMC) # n = 1879 +# Please mind that `portion_SI` calculates percentages right away instead. +count_SI(septic_patients$AMC) # 1433 +count_all(septic_patients$AMC) # 1879 -count_S(septic_patients$GEN) # S = 1372 (74.0\%) -count_all(septic_patients$GEN) # n = 1855 +count_SI(septic_patients$GEN) # 1399 +count_all(septic_patients$GEN) # 1855 with(septic_patients, - count_S(AMC, GEN)) # S = 1660 (92.3\%) -with(septic_patients, # n = 1798 - n_rsi(AMC, GEN)) + count_SI(AMC, GEN)) # 1764 +with(septic_patients, + n_rsi(AMC, GEN)) # 1936 # Get portions S/I/R immediately of all rsi columns septic_patients \%>\% diff --git a/man/portion.Rd b/man/portion.Rd index 8c4cf253..2a6f8304 100644 --- a/man/portion.Rd +++ b/man/portion.Rd @@ -17,19 +17,19 @@ Wickham H. \strong{Tidy Data.} The Journal of Statistical Software, vol. 59, 201 } \usage{ portion_R(..., minimum = 30, as_percent = FALSE, - also_single_tested = FALSE) + only_all_tested = FALSE) portion_IR(..., minimum = 30, as_percent = FALSE, - also_single_tested = FALSE) + only_all_tested = FALSE) portion_I(..., minimum = 30, as_percent = FALSE, - also_single_tested = FALSE) + only_all_tested = FALSE) portion_SI(..., minimum = 30, as_percent = FALSE, - also_single_tested = FALSE) + only_all_tested = FALSE) portion_S(..., minimum = 30, as_percent = FALSE, - also_single_tested = FALSE) + only_all_tested = FALSE) portion_df(data, translate_ab = "name", language = get_locale(), minimum = 30, as_percent = FALSE, combine_SI = TRUE, @@ -46,7 +46,7 @@ rsi_df(data, translate_ab = "name", language = get_locale(), \item{as_percent}{a logical to indicate whether the output must be returned as a hundred fold with \% sign (a character). A value of \code{0.123456} will then be returned as \code{"12.3\%"}.} -\item{also_single_tested}{a logical to indicate whether for combination therapies also observations should be included where not all antibiotics were tested, but at least one of the tested antibiotics contains a target interpretation (e.g. S in case of \code{portion_S} and R in case of \code{portion_R}). \strong{This could lead to selection bias.}} +\item{only_all_tested}{(for combination therapies, i.e. using more than one variable for \code{...}) a logical to indicate that isolates must be tested for all antibiotics, see section \emph{Combination therapy} below} \item{data}{a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}})} @@ -67,31 +67,61 @@ These functions can be used to calculate the (co-)resistance of microbial isolat \code{portion_R} and \code{portion_IR} can be used to calculate resistance, \code{portion_S} and \code{portion_SI} can be used to calculate susceptibility.\cr } \details{ -\strong{Remember that you should filter your table to let it contain only first isolates!} Use \code{\link{first_isolate}} to determine them in your data set. +\strong{Remember that you should filter your table to let it contain only first isolates!} This is needed to exclude duplicates and to reduce selection bias. Use \code{\link{first_isolate}} to determine them in your data set. These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. \emph{Low counts can infuence the outcome - these \code{portion} functions may camouflage this, since they only return the portion albeit being dependent on the \code{minimum} parameter.} The function \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each group and each variable with class \code{"rsi"}. The function \code{rsi_df} works exactly like \code{portion_df}, but adds the number of isolates. -\if{html}{ - \cr\cr - To calculate the probability (\emph{p}) of susceptibility of one antibiotic, we use this formula: - \out{
      }\figure{combi_therapy_2.png}\out{
      } - To calculate the probability (\emph{p}) of susceptibility of more antibiotics (i.e. combination therapy), we need to check whether one of them has a susceptible result (as numerator) and count all cases where all antibiotics were tested (as denominator). \cr - \cr - For two antibiotics: - \out{
      }\figure{combi_therapy_2.png}\out{
      } - \cr - For three antibiotics: - \out{
      }\figure{combi_therapy_2.png}\out{
      } - \cr - And so on. } +\section{Combination therapy}{ + +When using more than one variable for \code{...} (= combination therapy)), use \code{only_all_tested} to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antibiotics, Antibiotic A and Antibiotic B, about how \code{portion_SI} works to calculate the \%SI: + +\preformatted{ +------------------------------------------------------------------------- + only_all_tested = FALSE only_all_tested = TRUE +Antibiotic Antibiotic ----------------------- ----------------------- + A B include as include as include as include as + numerator denominator numerator denominator +---------- ---------- ---------- ----------- ---------- ----------- + S S X X X X + I S X X X X + R S X X X X +not tested S X X - - + S I X X X X + I I X X X X + R I X X X X +not tested I X X - - + S R X X X X + I R X X X X + R R - X - X +not tested R - - - - + S not tested X X - - + I not tested X X - - + R not tested - - - - +not tested not tested - - - - +------------------------------------------------------------------------- } + +Please note that for \code{only_all_tested = TRUE} applies that: +\preformatted{ + count_S() + count_I() + count_R() == count_all() + portion_S() + portion_I() + portion_R() == 1 +} +and that for \code{only_all_tested = FALSE} applies that: +\preformatted{ + count_S() + count_I() + count_R() >= count_all() + portion_S() + portion_I() + portion_R() >= 1 +} + +Using \code{only_all_tested} has no impact when only using one antibiotic as input. +} + \section{Interpretation of S, I and R}{ -In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below. Results of several consultations on the new definitions are available on the EUCAST website under "Consultations". +In 2019, EUCAST has decided to change the definitions of susceptibility testing categories S, I and R as shown below (\url{http://www.eucast.org/newsiandr/}). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations". \itemize{ \item{\strong{S} - }{Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.} @@ -101,9 +131,7 @@ In 2019, EUCAST has decided to change the definitions of susceptibility testing Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection. -Source: \url{http://www.eucast.org/newsiandr/}. - -\strong{This AMR package honours this new insight.} +This AMR package honours this new insight. Use \code{\link{portion_SI}} to determine antimicrobial susceptibility and \code{\link{count_SI}} to count susceptible isolates. } \section{Read more on our website!}{ @@ -132,7 +160,7 @@ septic_patients \%>\% portion_SI(AMX) septic_patients \%>\% group_by(hospital_id) \%>\% - summarise(p = portion_S(CIP), + summarise(p = portion_SI(CIP), n = n_rsi(CIP)) # n_rsi works like n_distinct in dplyr septic_patients \%>\% @@ -146,32 +174,38 @@ septic_patients \%>\% # Calculate co-resistance between amoxicillin/clav acid and gentamicin, # so we can see that combination therapy does a lot more than mono therapy: -septic_patients \%>\% portion_S(AMC) # S = 71.4\% -septic_patients \%>\% count_all(AMC) # n = 1879 +septic_patients \%>\% portion_SI(AMC) # \%SI = 76.3\% +septic_patients \%>\% count_all(AMC) # n = 1879 -septic_patients \%>\% portion_S(GEN) # S = 74.0\% -septic_patients \%>\% count_all(GEN) # n = 1855 +septic_patients \%>\% portion_SI(GEN) # \%SI = 75.4\% +septic_patients \%>\% count_all(GEN) # n = 1855 -septic_patients \%>\% portion_S(AMC, GEN) # S = 92.3\% -septic_patients \%>\% count_all(AMC, GEN) # n = 1798 +septic_patients \%>\% portion_SI(AMC, GEN) # \%SI = 94.1\% +septic_patients \%>\% count_all(AMC, GEN) # n = 1939 -# Using `also_single_tested` can be useful ... + +# See Details on how `only_all_tested` works. Example: septic_patients \%>\% - portion_S(AMC, GEN, - also_single_tested = TRUE) # S = 92.6\% -# ... but can also lead to selection bias - the data only has 2,000 rows: + summarise(numerator = count_SI(AMC, GEN), + denominator = count_all(AMC, GEN), + portion = portion_SI(AMC, GEN)) +# numerator denominator portion +# 1764 1936 0.9408 septic_patients \%>\% - count_all(AMC, GEN, - also_single_tested = TRUE) # n = 2555 + summarise(numerator = count_SI(AMC, GEN, only_all_tested = TRUE), + denominator = count_all(AMC, GEN, only_all_tested = TRUE), + portion = portion_SI(AMC, GEN, only_all_tested = TRUE)) +# numerator denominator portion +# 1687 1798 0.9383 septic_patients \%>\% group_by(hospital_id) \%>\% - summarise(cipro_p = portion_S(CIP, as_percent = TRUE), + summarise(cipro_p = portion_SI(CIP, as_percent = TRUE), cipro_n = count_all(CIP), - genta_p = portion_S(GEN, as_percent = TRUE), + genta_p = portion_SI(GEN, as_percent = TRUE), genta_n = count_all(GEN), - combination_p = portion_S(CIP, GEN, as_percent = TRUE), + combination_p = portion_SI(CIP, GEN, as_percent = TRUE), combination_n = count_all(CIP, GEN)) # Get portions S/I/R immediately of all rsi columns diff --git a/tests/testthat/test-count.R b/tests/testthat/test-count.R index 4f4f4c3e..5688b13c 100644 --- a/tests/testthat/test-count.R +++ b/tests/testthat/test-count.R @@ -33,20 +33,22 @@ test_that("counts work", { library(dplyr) expect_equal(septic_patients %>% count_S(AMC), 1342) - expect_equal(septic_patients %>% count_S(AMC, GEN), 1660) - expect_equal(septic_patients %>% count_all(AMC, GEN), 1798) - expect_identical(septic_patients %>% count_all(AMC, GEN), - septic_patients %>% count_S(AMC, GEN) + - septic_patients %>% count_IR(AMC, GEN)) + expect_equal(septic_patients %>% count_S(AMC, GEN, only_all_tested = TRUE), 1660) + expect_equal(septic_patients %>% count_S(AMC, GEN, only_all_tested = FALSE), 1728) + expect_equal(septic_patients %>% count_all(AMC, GEN, only_all_tested = TRUE), 1798) + expect_equal(septic_patients %>% count_all(AMC, GEN, only_all_tested = FALSE), 1936) + expect_identical(septic_patients %>% count_all(AMC, GEN, only_all_tested = TRUE), + septic_patients %>% count_S(AMC, GEN, only_all_tested = TRUE) + + septic_patients %>% count_IR(AMC, GEN, only_all_tested = TRUE)) # count of cases expect_equal(septic_patients %>% group_by(hospital_id) %>% - summarise(cipro = count_S(CIP), - genta = count_S(GEN), - combination = count_S(CIP, GEN)) %>% + summarise(cipro = count_SI(CIP), + genta = count_SI(GEN), + combination = count_SI(CIP, GEN)) %>% pull(combination), - c(192, 446, 184, 474)) + c(253, 465, 192, 558)) # count_df expect_equal( diff --git a/tests/testthat/test-portion.R b/tests/testthat/test-portion.R index 84599859..47c473e9 100755 --- a/tests/testthat/test-portion.R +++ b/tests/testthat/test-portion.R @@ -32,14 +32,14 @@ test_that("portions works", { expect_equal(portion_S(septic_patients$AMX) + portion_I(septic_patients$AMX), portion_SI(septic_patients$AMX)) - expect_equal(septic_patients %>% portion_S(AMC), - 0.7142097, + expect_equal(septic_patients %>% portion_SI(AMC), + 0.7626397, tolerance = 0.0001) - expect_equal(septic_patients %>% portion_S(AMC, GEN), - 0.9232481, + expect_equal(septic_patients %>% portion_SI(AMC, GEN), + 0.9408, tolerance = 0.0001) - expect_equal(septic_patients %>% portion_S(AMC, GEN, also_single_tested = TRUE), - 0.926045, + expect_equal(septic_patients %>% portion_SI(AMC, GEN, only_all_tested = TRUE), + 0.9382647, tolerance = 0.0001) # percentages @@ -57,14 +57,14 @@ test_that("portions works", { # count of cases expect_equal(septic_patients %>% group_by(hospital_id) %>% - summarise(CIPo_p = portion_S(CIP, as_percent = TRUE), - CIPo_n = n_rsi(CIP), - GENa_p = portion_S(GEN, as_percent = TRUE), - GENa_n = n_rsi(GEN), - combination_p = portion_S(CIP, GEN, as_percent = TRUE), + summarise(cipro_p = portion_SI(CIP, as_percent = TRUE), + cipro_n = n_rsi(CIP), + genta_p = portion_SI(GEN, as_percent = TRUE), + genta_n = n_rsi(GEN), + combination_p = portion_SI(CIP, GEN, as_percent = TRUE), combination_n = n_rsi(CIP, GEN)) %>% pull(combination_n), - c(202, 488, 201, 499)) + c(305, 617, 241, 711)) expect_warning(portion_R(as.character(septic_patients$AMC))) expect_warning(portion_S(as.character(septic_patients$AMC))) @@ -83,7 +83,7 @@ test_that("portions works", { expect_error(portion_I("test", as_percent = "test")) expect_error(portion_S("test", minimum = "test")) expect_error(portion_S("test", as_percent = "test")) - expect_error(portion_S("test", also_single_tested = "test")) + expect_error(portion_S("test", also_single_tested = TRUE)) # check too low amount of isolates expect_identical(suppressWarnings(portion_R(septic_patients$AMX, minimum = nrow(septic_patients) + 1)),