diff --git a/DESCRIPTION b/DESCRIPTION index e535bbf5..4897140e 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 0.7.0.9000 -Date: 2019-06-03 +Version: 0.7.0.9001 +Date: 2019-06-07 Title: Antimicrobial Resistance Analysis Authors@R: c( person( diff --git a/NAMESPACE b/NAMESPACE index 9493fb50..4983e269 100755 --- a/NAMESPACE +++ b/NAMESPACE @@ -173,6 +173,8 @@ export(resistance_predict) export(right_join_microorganisms) export(rsi_predict) export(scale_rsi_colours) +export(scale_type.ab) +export(scale_type.mo) export(scale_y_percent) export(semi_join_microorganisms) export(set_mo_source) @@ -217,6 +219,8 @@ exportMethods(print.rsi) exportMethods(pull.ab) exportMethods(pull.atc) exportMethods(pull.mo) +exportMethods(scale_type.ab) +exportMethods(scale_type.mo) exportMethods(select.freq) exportMethods(skewness) exportMethods(skewness.data.frame) @@ -241,6 +245,7 @@ importFrom(crayon,strip_style) importFrom(crayon,underline) importFrom(crayon,white) importFrom(crayon,yellow) +importFrom(data.table,address) importFrom(data.table,as.data.table) importFrom(data.table,data.table) importFrom(data.table,setkey) @@ -302,6 +307,7 @@ importFrom(microbenchmark,microbenchmark) importFrom(rlang,as_label) importFrom(rlang,enquos) importFrom(rlang,eval_tidy) +importFrom(scales,percent) importFrom(stats,complete.cases) importFrom(stats,fivenum) importFrom(stats,glm) diff --git a/NEWS.md b/NEWS.md index 0962111c..640e8e0a 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,10 +1,26 @@ -# AMR 0.7.0.9000 +# AMR 0.7.0.9001 #### New +* Support for all scientifically published pathotypes of *E. coli* to date. Supported are: AIEC (Adherent-Invasive *E. coli*), ATEC (Atypical Entero-pathogenic *E. coli*), DAEC (Diffusely Adhering *E. coli*), EAEC (Entero-Aggresive *E. coli*), EHEC (Entero-Haemorrhagic *E. coli*), EIEC (Entero-Invasive *E. coli*), EPEC (Entero-Pathogenic *E. coli*), ETEC (Entero-Toxigenic *E. coli*), NMEC (Neonatal Meningitis‐causing *E. coli*), STEC (Shiga-toxin producing *E. coli*) and UPEC (Uropathogenic *E. coli*). All these lead to the microbial ID of *E. coli*: + ```r + as.mo("UPEC") + # B_ESCHR_COL + mo_fullname("UPEC") + # "Escherichia coli" + ``` #### Changed +* Fixed bug in translation of microorganism names +* Fixed bug in determining taxonomic kingdoms +* Algorithm improvements for `as.ab()` and `as.mo()` to understand even more severe misspelled input +* Added `ggplot2` methods for automatically determining the scale type of classes `mo` and `ab` +* Added names of object in the header in frequency tables, even when using pipes +* Prevented `"bacteria"` from getting coerced by `as.ab()` because Bacterial is a brand name of trimethoprim (TMP) +* Fixed a bug where setting an antibiotic would not work for `eucast_rules()` and `mdro()` +* Fixed a EUCAST rule for Staphylococci, where amikacin resistance would not be inferred from tobramycin #### Other +* Fixed a note thrown by CRAN tests # AMR 0.7.0 diff --git a/R/ab.R b/R/ab.R index c90c206b..b39d0e4a 100755 --- a/R/ab.R +++ b/R/ab.R @@ -91,6 +91,11 @@ as.ab <- function(x) { x_unknown <- c(x_unknown, x_bak[x[i] == x_bak_clean][1]) next } + # prevent "bacteria" from coercing to TMP, since Bacterial is a brand name of it + if (identical(tolower(x[i]), "bacteria")) { + x_unknown <- c(x_unknown, x_bak[x[i] == x_bak_clean][1]) + next + } # exact AB code found <- AMR::antibiotics[which(AMR::antibiotics$ab == toupper(x[i])),]$ab @@ -162,23 +167,20 @@ as.ab <- function(x) { } x_spelling <- tolower(x[i]) x_spelling <- gsub("[iy]+", "[iy]+", x_spelling) - x_spelling <- gsub("[sz]+", "[sz]+", x_spelling) - x_spelling <- gsub("(c|k|q|qu)+", "(c|k|q|qu)+", x_spelling) + x_spelling <- gsub("(c|k|q|qu|s|z|x|ks)+", "(c|k|q|qu|s|z|x|ks)+", x_spelling) x_spelling <- gsub("(ph|f|v)+", "(ph|f|v)+", x_spelling) x_spelling <- gsub("(th|t)+", "(th|t)+", x_spelling) - x_spelling <- gsub("(x|ks)+", "(x|ks)+", x_spelling) x_spelling <- gsub("a+", "a+", x_spelling) x_spelling <- gsub("e+", "e+", x_spelling) x_spelling <- gsub("o+", "o+", x_spelling) - # allow start with C/S/Z - x_spelling <- gsub("^(\\(c\\|k\\|q\\|qu\\)|\\[sz\\])", "(c|k|q|qu|s|z)", x_spelling) - x_spelling <- gsub("(c|k|q|qu)+[sz]", "(c|k|q|qu|s|x|z)", x_spelling, fixed = TRUE) # allow any ending of -in/-ine and -im/-ime x_spelling <- gsub("(\\[iy\\]\\+(n|m)|\\[iy\\]\\+(n|m)e\\+)$", "[iy]+(n|m)e*", x_spelling) # allow any ending of -ol/-ole x_spelling <- gsub("(o\\+l|o\\+le\\+)$", "o+le*", x_spelling) # allow any ending of -on/-one x_spelling <- gsub("(o\\+n|o\\+ne\\+)$", "o+ne*", x_spelling) + # replace multiple same characters to single one with '+', like "ll" -> "l+" + x_spelling <- gsub("(.)\\1+", "\\1+", x_spelling) # try if name starts with it found <- AMR::antibiotics[which(AMR::antibiotics$name %like% paste0("^", x_spelling)),]$ab if (length(found) > 0) { @@ -256,3 +258,13 @@ as.data.frame.ab <- function (x, ...) { pull.ab <- function(.data, ...) { pull(as.data.frame(.data), ...) } + +#' @exportMethod scale_type.ab +#' @export +#' @noRd +scale_type.ab <- function(x) { + # fix for: + # "Don't know how to automatically pick scale for object of type ab. Defaulting to continuous." + # "Error: Discrete value supplied to continuous scale" + "discrete" +} diff --git a/R/amr.R b/R/amr.R index 5351cf9d..cbff6fb2 100644 --- a/R/amr.R +++ b/R/amr.R @@ -67,4 +67,5 @@ #' @rdname AMR # # prevent NOTE on R >= 3.6 #' @importFrom microbenchmark microbenchmark +#' @importFrom scales percent NULL diff --git a/R/eucast_rules.R b/R/eucast_rules.R index 9b7b82c6..e6bb0a49 100755 --- a/R/eucast_rules.R +++ b/R/eucast_rules.R @@ -209,6 +209,12 @@ eucast_rules <- function(x, stop("`col_mo` must be set") } + decimal.mark <- getOption("OutDec") + big.mark <- ifelse(decimal.mark != ",", ",", ".") + formatnr <- function(x) { + trimws(format(x, big.mark = big.mark, decimal.mark = decimal.mark)) + } + warned <- FALSE txt_error <- function() { cat("", bgRed(white(" ERROR ")), "\n") } @@ -219,7 +225,7 @@ eucast_rules <- function(x, if (no_of_changes == 1) { cat(blue(" (1 new change)\n")) } else { - cat(blue(paste0(" (", no_of_changes, " new changes)\n"))) + cat(blue(paste0(" (", formatnr(no_of_changes), " new changes)\n"))) } } else { cat(green(" (no new changes)\n")) @@ -664,12 +670,6 @@ eucast_rules <- function(x, verbose_info <- verbose_info %>% arrange(row, rule_group, rule_name, col) - decimal.mark <- getOption("OutDec") - big.mark <- ifelse(decimal.mark != ",", ",", ".") - formatnr <- function(x) { - trimws(format(x, big.mark = big.mark, decimal.mark = decimal.mark)) - } - cat(paste0("\n", silver(strrep("-", options()$width - 1)), "\n")) cat(bold(paste('EUCAST rules', paste0(wouldve, 'affected'), formatnr(n_distinct(verbose_info$row)), diff --git a/R/first_isolate.R b/R/first_isolate.R index 49a29a82..ba95f4a1 100755 --- a/R/first_isolate.R +++ b/R/first_isolate.R @@ -414,15 +414,15 @@ first_isolate <- function(x, if (length(x) == 1) { return(TRUE) } - indices = integer(0) - start = x[1] - ind = 1 - indices[ind] = ind + indices <- integer(0) + start <- x[1] + ind <- 1 + indices[ind] <- ind for (i in 2:length(x)) { - if (as.numeric(x[i] - start >= episode_days)) { - ind = ind + 1 - indices[ind] = i - start = x[i] + if (isTRUE(as.numeric(x[i] - start) >= episode_days)) { + ind <- ind + 1 + indices[ind] <- i + start <- x[i] } } result <- rep(FALSE, length(x)) diff --git a/R/freq.R b/R/freq.R index 07faa5bd..a234593a 100755 --- a/R/freq.R +++ b/R/freq.R @@ -238,7 +238,13 @@ freq <- function(x, x.name <- x.name %>% strsplit("%>%", fixed = TRUE) %>% unlist() %>% .[1] %>% trimws() } if (x.name == ".") { - x.name <- "a data.frame" + # passed on with pipe + x.name <- get_data_source_name(x) + if (!is.null(x.name)) { + x.name <- paste0("`", x.name, "`") + } else { + x.name <- "a data.frame" + } } else { x.name <- paste0("`", x.name, "`") } @@ -1230,3 +1236,21 @@ format.freq <- function(x, digits = 1, ...) { x$cum_percent <- percent(x$cum_percent, round = digits, force_zero = TRUE) base::format.data.frame(x, ...) } + +#' @importFrom data.table address +get_data_source_name <- function(x, else_txt = NULL) { + obj_addr <- address(x) + # try global environment + addrs <- unlist(lapply(ls(".GlobalEnv"), function(x) address(get(x)))) + res <- ls(".GlobalEnv")[addrs == obj_addr] + if (length(res) == 0) { + # check AMR package - some users might use our data sets for testing + addrs <- unlist(lapply(ls("package:AMR"), function(x) address(get(x)))) + res <- ls("package:AMR")[addrs == obj_addr] + } + if (length(res) == 0) { + else_txt + } else { + res + } +} diff --git a/R/misc.R b/R/misc.R index 799b0631..e0cf3840 100755 --- a/R/misc.R +++ b/R/misc.R @@ -172,16 +172,19 @@ get_column_abx <- function(x, # get_column_abx(septic_patients %>% rename(thisone = AMX), amox = "thisone") dots <- list(...) if (length(dots) > 0) { - dots <- unlist(dots) newnames <- suppressWarnings(as.ab(names(dots))) if (any(is.na(newnames))) { warning("Invalid antibiotic reference(s): ", toString(names(dots)[is.na(newnames)]), call. = FALSE, immediate. = TRUE) } + # turn all NULLs to NAs + dots <- unlist(lapply(dots, function(x) if (is.null(x)) NA else x)) names(dots) <- newnames dots <- dots[!is.na(names(dots))] # merge, but overwrite automatically determined ones by 'dots' x <- c(x[!x %in% dots & !names(x) %in% names(dots)], dots) + # delete NAs, this will make eucast_rules(... TMP = NULL) work to prevent TMP from being used + x <- x[!is.na(x)] } # sort on name diff --git a/R/mo.R b/R/mo.R index 9ba0252b..1e375073 100755 --- a/R/mo.R +++ b/R/mo.R @@ -485,18 +485,21 @@ exec_as.mo <- function(x, # remove genus as first word x <- gsub("^Genus ", "", x) # allow characters that resemble others - x <- gsub("[iy]+", "[iy]+", x, ignore.case = TRUE) - x <- gsub("[sz]+", "[sz]+", x, ignore.case = TRUE) - x <- gsub("(c|k|q|qu)+", "(c|k|q|qu)+", x, ignore.case = TRUE) - x <- gsub("(ph|f|v)+", "(ph|f|v)+", x, ignore.case = TRUE) - x <- gsub("(th|t)+", "(th|t)+", x, ignore.case = TRUE) - x <- gsub("a+", "a+", x, ignore.case = TRUE) - # allow any ending of -um, -us, -ium, -ius and -a (needs perl for the negative backward lookup): - x <- gsub("(um|u\\[sz\\]\\+|\\[iy\\]\\+um|\\[iy\\]\\+u\\[sz\\]\\+|a\\+)(?![a-z[])", - "(um|us|ium|ius|a)", x, ignore.case = TRUE, perl = TRUE) - x <- gsub("e+", "e+", x, ignore.case = TRUE) - x <- gsub("o+", "o+", x, ignore.case = TRUE) - + 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) + x <- gsub("(ph|f|v)+", "(ph|f|v)+", x) + x <- gsub("(th|t)+", "(th|t)+", x) + x <- gsub("a+", "a+", x) + x <- gsub("u+", "u+", x) + # allow any ending of -um, -us, -ium, -ius and -a (needs perl for the negative backward lookup): + x <- gsub("(um|u\\[sz\\]\\+|\\[iy\\]\\+um|\\[iy\\]\\+u\\[sz\\]\\+|a\\+)(?![a-z[])", + "(um|us|ium|ius|a)", x, ignore.case = TRUE, perl = TRUE) + x <- gsub("e+", "e+", x, ignore.case = TRUE) + x <- gsub("o+", "o+", x, ignore.case = TRUE) + x <- gsub("(.)\\1+", "\\1+", x) + } x <- strip_whitespace(x) x_trimmed <- x @@ -639,7 +642,7 @@ exec_as.mo <- function(x, } next } - if (toupper(x_backup_without_spp[i]) %in% c("EHEC", "EPEC", "EIEC", "STEC", "ATEC") + if (toupper(x_backup_without_spp[i]) %in% c("AIEC", "ATEC", "DAEC", "EAEC", "EHEC", "EIEC", "EPEC", "ETEC", "NMEC", "STEC", "UPEC") | x_backup_without_spp[i] %like% "O?(26|103|104|104|111|121|145|157)") { x[i] <- microorganismsDT[mo == 'B_ESCHR_COL', ..property][[1]][1L] if (initial_search == TRUE) { @@ -1481,3 +1484,13 @@ translate_allow_uncertain <- function(allow_uncertain) { } allow_uncertain } + +#' @exportMethod scale_type.mo +#' @export +#' @noRd +scale_type.mo <- function(x) { + # fix for: + # "Don't know how to automatically pick scale for object of type mo. Defaulting to continuous." + # "Error: Discrete value supplied to continuous scale" + "discrete" +} diff --git a/R/mo_property.R b/R/mo_property.R index 3d0c6024..cb7aeb41 100755 --- a/R/mo_property.R +++ b/R/mo_property.R @@ -238,7 +238,8 @@ mo_kingdom <- function(x, language = get_locale(), ...) { x <- as.mo(x, ...) kngdm <- mo_validate(x = x, property = "kingdom", ...) if (language != "en") { - kngdm[x == "UNKNOWN"] <- t(kngdm[x == "UNKNOWN"], language = language) + # translate only unknown, so "Bacteria" (the official taxonomic name) would not change + kngdm[identical(x, "UNKNOWN")] <- t(kngdm[identical(x, "UNKNOWN")], language = language) } kngdm } diff --git a/R/sysdata.rda b/R/sysdata.rda index ee6d78c5..7c43f0a4 100644 Binary files a/R/sysdata.rda and b/R/sysdata.rda differ diff --git a/R/zzz.R b/R/zzz.R index 9cc92b47..f21644bf 100755 --- a/R/zzz.R +++ b/R/zzz.R @@ -51,6 +51,31 @@ } + +.onAttach <- function(...) { + if (interactive()) { + console_width <- options()$width - 1 + url <- "https://www.surveymonkey.com/r/AMR_for_R" + txt <- paste("Thanks for using the AMR package!", + "As researchers, we are interested in how and why you use this package and if there are things you're missing from it.", + "Please fill in our 2-minute survey at:", url) + + # make it honour new lines bases on console width: + txt <- unlist(strsplit(txt, " ")) + txt_new <- "" + total_chars <- 0 + for (i in 1:length(txt)) { + total_chars <- total_chars + nchar(txt[i]) + 1 + if (total_chars > console_width) { + txt_new <- paste0(txt_new, "\n") + total_chars <- 0 + } + txt_new <- paste0(txt_new, txt[i], " ") + } + packageStartupMessage(txt_new) + } +} + #' @importFrom data.table as.data.table setkey make_DT <- function() { microorganismsDT <- as.data.table(AMR::microorganisms) diff --git a/data-raw/eucast_rules.tsv b/data-raw/eucast_rules.tsv index 2537e598..5df26eb4 100644 --- a/data-raw/eucast_rules.tsv +++ b/data-raw/eucast_rules.tsv @@ -165,7 +165,7 @@ family is Enterobacteriaceae TIC, PIP R, S PIP R Table 09: Interpretive rules fo genus is .* ERY S AZM, CLR S Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins Expert Rules genus is .* ERY I AZM, CLR I Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins Expert Rules genus is .* ERY R AZM, CLR R Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins Expert Rules -genus is Staphylococcus TOB R KAN, amik R Table 12: Interpretive rules for aminoglycosides Expert Rules +genus is Staphylococcus TOB R KAN, AMK R Table 12: Interpretive rules for aminoglycosides Expert Rules genus is Staphylococcus GEN R aminoglycosides R Table 12: Interpretive rules for aminoglycosides Expert Rules family is Enterobacteriaceae GEN, TOB I, S GEN R Table 12: Interpretive rules for aminoglycosides Expert Rules family is Enterobacteriaceae GEN, TOB R, I TOB R Table 12: Interpretive rules for aminoglycosides Expert Rules diff --git a/data-raw/internals.R b/data-raw/internals.R index 0c55d4aa..29396bbe 100644 --- a/data-raw/internals.R +++ b/data-raw/internals.R @@ -18,7 +18,7 @@ eucast_rules_file <- dplyr::arrange( reference.rule) # Translations ----- -translations_file <- utils::read.table(file = "data-raw/translations.tsv", +translations_file <- utils::read.delim(file = "data-raw/translations.tsv", sep = "\t", stringsAsFactors = FALSE, header = TRUE, @@ -27,7 +27,9 @@ translations_file <- utils::read.table(file = "data-raw/translations.tsv", strip.white = TRUE, encoding = "UTF-8", fileEncoding = "UTF-8", - na.strings = c(NA, "", NULL)) + na.strings = c(NA, "", NULL), + allowEscapes = TRUE, # else "\\1" will be imported as "\\\\1" + quote = "") # Export to package as internal data ---- usethis::use_data(eucast_rules_file, translations_file, diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index de5cd3cd..9b3d7e15 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.0.9000 + 0.7.0.9001 diff --git a/docs/articles/AMR.html b/docs/articles/AMR.html index deb20be5..32705737 100644 --- a/docs/articles/AMR.html +++ b/docs/articles/AMR.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0 + 0.7.0.9000 @@ -199,7 +199,7 @@

How to conduct AMR analysis

Matthijs S. Berends

-

03 June 2019

+

07 June 2019

@@ -208,7 +208,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 03 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 07 June 2019.

Introduction

@@ -224,21 +224,21 @@ -2019-06-03 +2019-06-07 abcd Escherichia coli S S -2019-06-03 +2019-06-07 abcd Escherichia coli S R -2019-06-03 +2019-06-07 efgh Escherichia coli R @@ -334,19 +334,52 @@ -2010-12-01 -Y6 -Hospital C +2010-01-26 +S3 +Hospital B +Escherichia coli +R +I +R +S +F + + +2010-08-26 +G7 +Hospital D Escherichia coli R S S S -F +M + + +2016-05-04 +B8 +Hospital A +Escherichia coli +S +S +R +S +M -2011-05-31 -C8 +2016-11-19 +E10 +Hospital D +Streptococcus pneumoniae +S +S +S +S +M + + +2013-07-13 +G3 Hospital A Escherichia coli R @@ -355,45 +388,12 @@ S M - -2012-04-18 -Z6 -Hospital D -Escherichia coli -R -S -R -S -F - -2011-04-24 -W4 +2017-05-23 +V3 Hospital C Staphylococcus aureus S -R -R -S -F - - -2011-11-05 -A9 -Hospital C -Escherichia coli -R -S -R -S -M - - -2016-09-07 -Y6 -Hospital B -Staphylococcus aureus -S S S S @@ -409,7 +409,7 @@ Cleaning the data

Use the frequency table function freq() to look specifically for unique values in any variable. For example, for the gender variable:

data %>% freq(gender) # this would be the same: freq(data$gender)
-
# Frequency table of `gender` from a data.frame (20,000 x 9) 
+
# Frequency table of `gender` from `data` (20,000 x 9) 
 # 
 # Class:   factor (numeric)
 # Length:  20,000 (of which NA: 0 = 0.00%)
@@ -418,8 +418,8 @@
 # 
 #      Item     Count   Percent   Cum. Count   Cum. Percent
 # ---  -----  -------  --------  -----------  -------------
-# 1    M       10,407     52.0%       10,407          52.0%
-# 2    F        9,593     48.0%       20,000         100.0%
+# 1 M 10,368 51.8% 10,368 51.8% +# 2 F 9,632 48.2% 20,000 100.0%

So, we can draw at least two conclusions immediately. From a data scientist perspective, the data looks clean: only values M and F. From a researcher 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 %>%
@@ -449,14 +449,14 @@
 # Pasteurella multocida (no new changes)
 # Staphylococcus (no new changes)
 # Streptococcus groups A, B, C, G (no new changes)
-# Streptococcus pneumoniae (1431 new changes)
+# Streptococcus pneumoniae (1,496 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 (1230 new changes)
+# Table 01: Intrinsic resistance in Enterobacteriaceae (1,276 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 (2646 new changes)
+# Table 04: Intrinsic resistance in Gram-positive bacteria (2,809 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)
@@ -464,24 +464,24 @@
 # Table 13: Interpretive rules for quinolones (no new changes)
 # 
 # Other rules
-# Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (2197 new changes)
-# Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (99 new changes)
+# Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (2,244 new changes)
+# Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (111 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,284 out of 20,000 rows, making a total of 7,603 edits
+# EUCAST rules affected 6,565 out of 20,000 rows, making a total of 7,936 edits
 # => added 0 test results
 # 
-# => changed 7,603 test results
-#    - 111 test results changed from S to I
-#    - 4,561 test results changed from S to R
-#    - 1,028 test results changed from I to S
-#    - 292 test results changed from I to R
-#    - 1,595 test results changed from R to S
-#    - 16 test results changed from R to I
+# => changed 7,936 test results
+#    - 116 test results changed from S to I
+#    - 4,801 test results changed from S to R
+#    - 1,059 test results changed from I to S
+#    - 347 test results changed from I to R
+#    - 1,596 test results changed from R to S
+#    - 17 test results changed from R to I
 # --------------------------------------------------------------------------
 # 
 # Use verbose = TRUE to get a data.frame with all specified edits instead.
@@ -509,8 +509,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,652 first isolates (28.3% of total)
-

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

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

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

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

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

@@ -536,8 +536,8 @@ 1 -2010-03-08 -C7 +2010-01-16 +V9 B_ESCHR_COL S S @@ -547,10 +547,10 @@ 2 -2010-04-14 -C7 +2010-02-23 +V9 B_ESCHR_COL -R +S S S S @@ -558,8 +558,8 @@ 3 -2010-04-18 -C7 +2010-04-05 +V9 B_ESCHR_COL S S @@ -569,19 +569,19 @@ 4 -2010-04-22 -C7 +2010-04-28 +V9 B_ESCHR_COL S S -R +S S FALSE 5 -2010-05-30 -C7 +2010-05-20 +V9 B_ESCHR_COL S S @@ -591,19 +591,19 @@ 6 -2010-10-09 -C7 +2010-07-07 +V9 B_ESCHR_COL S S -S R +S FALSE 7 -2011-01-26 -C7 +2010-09-11 +V9 B_ESCHR_COL S S @@ -613,8 +613,8 @@ 8 -2011-02-19 -C7 +2010-09-19 +V9 B_ESCHR_COL S S @@ -624,29 +624,29 @@ 9 -2011-03-25 -C7 +2010-10-07 +V9 B_ESCHR_COL -R S S S -TRUE +S +FALSE 10 -2011-04-17 -C7 +2011-01-14 +V9 B_ESCHR_COL R S -R +S S FALSE -

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.

+

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.

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(.)) %>% 
@@ -657,7 +657,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,076 first weighted isolates (75.4% of total)
+# => Found 15,072 first weighted isolates (75.4% of total) @@ -674,8 +674,8 @@ - - + + @@ -686,68 +686,68 @@ - - + + - + - + - - + + - + - - + + - + - + - - + + - + - - + + - + - - + + @@ -758,8 +758,8 @@ - - + + @@ -770,35 +770,35 @@ - - + + - - - + + + - - + + - +
isolate
12010-03-08C72010-01-16V9 B_ESCHR_COL S S
22010-04-14C72010-02-23V9 B_ESCHR_COLRS S S S FALSETRUEFALSE
32010-04-18C72010-04-05V9 B_ESCHR_COL S S S S FALSETRUEFALSE
42010-04-22C72010-04-28V9 B_ESCHR_COL S SRS S FALSETRUEFALSE
52010-05-30C72010-05-20V9 B_ESCHR_COL S S S S FALSETRUEFALSE
62010-10-09C72010-07-07V9 B_ESCHR_COL S SS RS FALSE TRUE
72011-01-26C72010-09-11V9 B_ESCHR_COL S S
82011-02-19C72010-09-19V9 B_ESCHR_COL S S
92011-03-25C72010-10-07V9 B_ESCHR_COLR S S STRUETRUESFALSEFALSE
102011-04-17C72011-01-14V9 B_ESCHR_COL R SRS S FALSE TRUE
-

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

+

Instead of 1, now 4 isolates are flagged. In total, 75.4% 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,076 isolates for analysis.

+

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

We can remove unneeded columns:

data_1st <- data_1st %>% 
   select(-c(first, keyab))
@@ -806,6 +806,7 @@
head(data_1st)
+ @@ -822,13 +823,14 @@ - - - + + + + - - + + @@ -837,8 +839,41 @@ - - + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + @@ -852,63 +887,35 @@ - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - + + + + + + + + + + + + + + + + + + - + - - - + + + @@ -928,9 +935,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 a data.frame (15,076 x 13)

+

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

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

Shortest: 16
Longest: 24

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

- - - - + + + + - - - - + + + + - - - + + + - + - + @@ -984,7 +991,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.4678297
+# [1] 0.4620488

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

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

- + - + - + - +
date patient_id hospital
2010-12-01Y6Hospital C12010-01-26S3Hospital B B_ESCHR_COL RSSIR S F Gram negativeTRUE
2011-05-31C822010-08-26G7Hospital DB_ESCHR_COLRSSSMGram negativeEscherichiacoliTRUE
32016-05-04B8Hospital AB_ESCHR_COLSSRSMGram negativeEscherichiacoliTRUE
52013-07-13G3 Hospital A B_ESCHR_COL RTRUE
2012-04-18Z6Hospital DB_ESCHR_COLRSRSFGram negativeEscherichiacoliTRUE
2011-04-24W4Hospital CB_STPHY_AURSSRSFGram positiveStaphylococcusaureusTRUE
2011-11-05A9Hospital CB_ESCHR_COLRSRSMGram negativeEscherichiacoliTRUE
2016-09-0782016-11-20 Y6Hospital AB_ESCHR_COLSSRSFGram negativeEscherichiacoliTRUE
102015-11-03W8 Hospital BB_STPHY_AURB_ESCHR_COL S S S S FGram positiveStaphylococcusaureusGram negativeEscherichiacoli TRUE
1 Escherichia coli7,40249.1%7,40249.1%7,45149.4%7,45149.4%
2 Staphylococcus aureus3,88725.8%11,28974.9%3,71324.6%11,16474.1%
3 Streptococcus pneumoniae2,24414.9%13,5332,36715.7%13,531 89.8%
4 Klebsiella pneumoniae1,5431,541 10.2%15,07615,072 100.0%
Hospital A0.47009490.4472198
Hospital B0.46252180.4684564
Hospital C0.47152720.4662494
Hospital D0.47062660.4704907
@@ -1027,23 +1034,23 @@ Longest: 24

Hospital A -0.4700949 -4531 +0.4472198 +4604 Hospital B -0.4625218 -5163 +0.4684564 +5215 Hospital C -0.4715272 -2318 +0.4662494 +2237 Hospital D -0.4706266 -3064 +0.4704907 +3016 @@ -1063,27 +1070,27 @@ Longest: 24

Escherichia -0.9297487 -0.8940827 -0.9944610 +0.9256476 +0.8916924 +0.9938263 Klebsiella -0.8243681 -0.9047310 -0.9831497 +0.8208955 +0.8974692 +0.9883193 Staphylococcus -0.9248778 -0.9253923 -0.9935683 +0.9237813 +0.9165096 +0.9929976 Streptococcus -0.6114082 +0.6138572 0.0000000 -0.6114082 +0.6138572 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 aeeea9f1..cdba2c03 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 c3caf76a..0da9a2a4 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 48dd2689..65f4096e 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 b867f89b..1d5f719a 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 9e72a119..fadee99f 100644 --- a/docs/articles/EUCAST.html +++ b/docs/articles/EUCAST.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0 + 0.7.0.9000 @@ -199,7 +199,7 @@

How to apply EUCAST rules

Matthijs S. Berends

-

03 June 2019

+

07 June 2019

diff --git a/docs/articles/MDR.html b/docs/articles/MDR.html index f79866d9..2ae79f6e 100644 --- a/docs/articles/MDR.html +++ b/docs/articles/MDR.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0 + 0.7.0.9000 @@ -199,7 +199,7 @@

How to determine multi-drug resistance (MDR)

Matthijs S. Berends

-

03 June 2019

+

07 June 2019

@@ -242,18 +242,18 @@

The data set looks like this now:

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

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

my_TB_data$mdr <- mdr_tb(my_TB_data)
@@ -263,8 +263,7 @@
 # Version:   WHO/HTM/TB/2014.11
 # Author:    WHO (World Health Organization)
 # Source:    https://www.who.int/tb/publications/pmdt_companionhandbook/en/
-# Warning: Reliability might be improved if these antimicrobial results would
-# be available too: CAP (capreomycin), RIB (rifabutin), RFP (rifapentine)
+# NOTE: Reliability might be improved if these antimicrobial results would be available too: CAP (capreomycin), RIB (rifabutin), RFP (rifapentine)

And review the result with a frequency table:

freq(my_TB_data$mdr)

Frequency table of mdr from my_TB_data (5,000 x 8)

@@ -285,40 +284,40 @@ Unique: 5

1 Mono-resistance -3,238 -64.8% -3,238 -64.8% +3,283 +65.7% +3,283 +65.7% 2 Negative -662 -13.2% -3,900 -78.0% +650 +13.0% +3,933 +78.7% 3 Multidrug resistance -613 -12.3% -4,513 -90.3% +593 +11.9% +4,526 +90.5% 4 Poly-resistance -279 -5.6% -4,792 -95.8% +259 +5.2% +4,785 +95.7% 5 Extensive drug resistance -208 -4.2% +215 +4.3% 5,000 100.0% diff --git a/docs/articles/SPSS.html b/docs/articles/SPSS.html index 10b96a79..05da7bf4 100644 --- a/docs/articles/SPSS.html +++ b/docs/articles/SPSS.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0 + 0.7.0.9000 @@ -199,7 +199,7 @@

How to import data from SPSS / SAS / Stata

Matthijs S. Berends

-

03 June 2019

+

07 June 2019

diff --git a/docs/articles/WHONET.html b/docs/articles/WHONET.html index 4c15a0f4..ee88f81a 100644 --- a/docs/articles/WHONET.html +++ b/docs/articles/WHONET.html @@ -199,7 +199,7 @@

How to work with WHONET data

Matthijs S. Berends

-

03 June 2019

+

07 June 2019

@@ -238,7 +238,7 @@

No errors or warnings, so all values are transformed succesfully. Let’s check it though, with a couple of frequency tables:

# our newly created `mo` variable
 data %>% freq(mo, nmax = 10)
-

Frequency table of mo from a data.frame (500 x 54)

+

Frequency table of mo from data (500 x 54)

Class: mo (character)
Length: 500 (of which NA: 0 = 0.00%)
Unique: 39

@@ -342,7 +342,7 @@ Species: 38

# our transformed antibiotic columns # amoxicillin/clavulanic acid (J01CR02) as an example data %>% freq(AMC_ND2) -

Frequency table of AMC_ND2 from a data.frame (500 x 54)

+

Frequency table of AMC_ND2 from data (500 x 54)

Class: factor > ordered > rsi (numeric)
Length: 500 (of which NA: 19 = 3.80%)
Levels: 3: S < I < R
diff --git a/docs/articles/ab_property.html b/docs/articles/ab_property.html index 817153d9..f9c7b7cf 100644 --- a/docs/articles/ab_property.html +++ b/docs/articles/ab_property.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0 + 0.7.0.9000 @@ -199,7 +199,7 @@

How to get properties of an antibiotic

Matthijs S. Berends

-

03 June 2019

+

07 June 2019

diff --git a/docs/articles/benchmarks.html b/docs/articles/benchmarks.html index 22970be1..323fcb5b 100644 --- a/docs/articles/benchmarks.html +++ b/docs/articles/benchmarks.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0 + 0.7.0.9000 @@ -199,7 +199,7 @@

Benchmarks

Matthijs S. Berends

-

03 June 2019

+

07 June 2019

@@ -224,14 +224,14 @@ times = 10) print(S.aureus, unit = "ms", signif = 2) # Unit: milliseconds -# expr min lq mean median uq max neval -# as.mo("sau") 18 18 22.0 18.0 18.0 62 10 -# as.mo("stau") 48 48 53.0 48.0 48.0 93 10 -# as.mo("staaur") 17 18 22.0 18.0 18.0 62 10 -# as.mo("STAAUR") 18 18 22.0 18.0 18.0 62 10 -# as.mo("S. aureus") 28 28 29.0 28.0 29.0 29 10 -# as.mo("S. aureus") 28 28 57.0 51.0 73.0 130 10 -# as.mo("Staphylococcus aureus") 8 8 9.3 8.1 8.3 20 10 +# expr min lq mean median uq max neval +# as.mo("sau") 18 18.0 18 18.0 18.0 19 10 +# as.mo("stau") 41 41.0 50 42.0 43.0 86 10 +# as.mo("staaur") 18 18.0 22 18.0 18.0 64 10 +# as.mo("STAAUR") 18 18.0 40 19.0 63.0 97 10 +# as.mo("S. aureus") 28 28.0 33 28.0 29.0 73 10 +# as.mo("S. aureus") 28 28.0 37 28.0 28.0 120 10 +# as.mo("Staphylococcus aureus") 8 8.1 13 8.1 8.3 53 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"),
@@ -243,12 +243,12 @@
 print(T.islandicus, unit = "ms", signif = 2)
 # Unit: milliseconds
 #                         expr min  lq mean median  uq max neval
-#              as.mo("theisl") 470 470  500    510 520 530    10
-#              as.mo("THEISL") 470 470  480    470 510 520    10
-#       as.mo("T. islandicus")  74  75   84     75  77 120    10
-#      as.mo("T.  islandicus")  74  74   93     74 120 120    10
-#  as.mo("Thermus islandicus")  72  73   84     74  77 120    10
-

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

+# as.mo("theisl") 370 370 390 370 420 420 10 +# as.mo("THEISL") 370 420 420 420 420 440 10 +# as.mo("T. islandicus") 190 190 200 190 230 250 10 +# as.mo("T. islandicus") 190 190 210 210 230 240 10 +# as.mo("Thermus islandicus") 73 73 83 74 74 120 10 +

That takes 8.6 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)
 
@@ -294,8 +294,8 @@
 print(run_it, unit = "ms", signif = 3)
 # Unit: milliseconds
 #            expr  min   lq mean median   uq  max neval
-#  mo_fullname(x) 1120 1150 1210   1190 1220 1430    10
-

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

+# mo_fullname(x) 1220 1320 1410 1390 1540 1570 10 +

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

@@ -307,11 +307,11 @@ times = 10) print(run_it, unit = "ms", signif = 3) # Unit: milliseconds -# expr min lq mean median uq max neval -# A 13.20 13.4 13.80 13.70 14.20 14.40 10 -# B 25.50 25.9 31.00 26.20 27.60 72.30 10 -# C 1.78 1.8 1.89 1.84 2.03 2.06 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:

+# expr min lq mean median uq max neval +# A 13.70 13.90 14.40 14.40 14.60 15.30 10 +# B 25.60 26.10 26.80 26.80 27.40 28.30 10 +# C 1.59 1.78 1.95 1.96 2.06 2.39 10 +

So going from mo_fullname("Staphylococcus aureus") to "Staphylococcus aureus" takes 0.002 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"),
@@ -324,14 +324,14 @@
 print(run_it, unit = "ms", signif = 3)
 # Unit: milliseconds
 #  expr   min    lq  mean median    uq   max neval
-#     A 0.526 0.606 0.652  0.639 0.721 0.771    10
-#     B 0.575 0.582 0.665  0.658 0.689 0.898    10
-#     C 1.820 1.870 1.940  1.950 2.020 2.070    10
-#     D 0.547 0.596 0.702  0.665 0.850 0.891    10
-#     E 0.521 0.560 0.624  0.625 0.655 0.843    10
-#     F 0.487 0.518 0.596  0.559 0.720 0.754    10
-#     G 0.483 0.573 0.621  0.605 0.667 0.762    10
-#     H 0.196 0.270 0.304  0.314 0.348 0.418    10
+# A 0.555 0.585 0.666 0.619 0.777 0.788 10 +# B 0.574 0.653 0.771 0.740 0.857 1.080 10 +# C 1.630 1.790 1.950 1.930 2.120 2.280 10 +# D 0.571 0.671 0.726 0.702 0.725 1.090 10 +# E 0.528 0.569 0.704 0.762 0.807 0.833 10 +# F 0.511 0.556 0.618 0.580 0.694 0.752 10 +# G 0.481 0.538 0.649 0.674 0.736 0.791 10 +# H 0.213 0.282 0.336 0.298 0.348 0.636 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.

@@ -358,13 +358,13 @@ print(run_it, unit = "ms", signif = 4) # Unit: milliseconds # expr min lq mean median uq max neval -# en 18.45 18.62 18.93 18.81 19.03 20.02 10 -# de 21.13 21.19 21.67 21.26 21.37 25.28 10 -# nl 34.19 34.39 34.74 34.55 34.93 35.99 10 -# es 20.92 21.03 25.70 21.26 21.47 65.90 10 -# it 20.79 20.94 25.96 21.23 21.88 65.69 10 -# fr 20.97 21.04 21.30 21.27 21.44 21.86 10 -# pt 20.81 20.91 25.66 21.01 21.24 66.88 10
+# en 18.63 19.06 19.30 19.19 19.41 20.33 10 +# de 21.18 21.46 21.63 21.54 21.97 22.09 10 +# nl 34.84 35.19 40.04 35.54 36.43 80.26 10 +# es 21.00 21.17 21.58 21.49 21.62 23.30 10 +# it 21.10 21.26 30.82 21.66 22.58 67.88 10 +# fr 20.99 21.25 21.88 21.54 22.50 23.15 10 +# pt 21.11 21.24 21.59 21.55 21.91 22.34 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 bd29751e..df4a0b10 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 23d55f44..94217729 100644 --- a/docs/articles/freq.html +++ b/docs/articles/freq.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0 + 0.7.0.9000 @@ -199,7 +199,7 @@

How to create frequency tables

Matthijs S. Berends

-

03 June 2019

+

07 June 2019

@@ -228,7 +228,7 @@ # Probably the fastest and easiest: septic_patients %>% freq(gender) -

Frequency table of gender from a data.frame (2,000 x 49)

+

Frequency table of gender from septic_patients (2,000 x 49)

Class: character
Length: 2,000 (of which NA: 0 = 0.00%)
Unique: 2

@@ -285,7 +285,7 @@ Longest: 1

So now the genus and species variables are available. A frequency table of these combined variables can be created like this:

my_patients %>%
   freq(genus, species, nmax = 15)
-

Frequency table of genus and species from a data.frame (2,000 x 64)

+

Frequency table of genus and species from my_patients (2,000 x 64)

Columns: 2
Length: 2,000 (of which NA: 0 = 0.00%)
Unique: 95

@@ -515,7 +515,7 @@ Outliers: 15 (unique count: 12)

sort.count is TRUE by default. Compare this default behaviour…

septic_patients %>%
   freq(hospital_id)
-

Frequency table of hospital_id from a data.frame (2,000 x 49)

+

Frequency table of hospital_id from septic_patients (2,000 x 49)

Class: factor (numeric)
Length: 2,000 (of which NA: 0 = 0.00%)
Levels: 4: A, B, C, D
@@ -567,7 +567,7 @@ Unique: 4

… to this, where items are now sorted on factor levels:

septic_patients %>%
   freq(hospital_id, sort.count = FALSE)
-

Frequency table of hospital_id from a data.frame (2,000 x 49)

+

Frequency table of hospital_id from septic_patients (2,000 x 49)

Class: factor (numeric)
Length: 2,000 (of which NA: 0 = 0.00%)
Levels: 4: A, B, C, D
@@ -619,7 +619,7 @@ Unique: 4

All classes will be printed into the header. Variables with the new rsi class of this AMR package are actually ordered factors and have three classes (look at Class in the header):

septic_patients %>%
   freq(AMX, header = TRUE)
-

Frequency table of AMX from a data.frame (2,000 x 49)

+

Frequency table of AMX from septic_patients (2,000 x 49)

Class: factor > ordered > rsi (numeric)
Length: 2,000 (of which NA: 771 = 38.55%)
Levels: 3: S < I < R
@@ -670,7 +670,7 @@ Group: Beta-lactams/penicillins

Frequencies of dates will show the oldest and newest date in the data, and the amount of days between them:

septic_patients %>%
   freq(date, nmax = 5, header = TRUE)
-

Frequency table of date from a data.frame (2,000 x 49)

+

Frequency table of date from septic_patients (2,000 x 49)

Class: Date (numeric)
Length: 2,000 (of which NA: 0 = 0.00%)
Unique: 1,140

@@ -752,7 +752,7 @@ Median: 31 July 2009 (47.39%)

With the na.rm parameter you can remove NA values from the frequency table (defaults to TRUE, but the number of NA values will always be shown into the header):

septic_patients %>%
   freq(AMX, na.rm = FALSE)
-

Frequency table of AMX from a data.frame (2,000 x 49)

+

Frequency table of AMX from septic_patients (2,000 x 49)

Class: factor > ordered > rsi (numeric)
Length: 2,000 (of which NA: 771 = 38.55%)
Levels: 3: S < I < R
@@ -812,7 +812,7 @@ Group: Beta-lactams/penicillins

A frequency table shows row indices. To remove them, use row.names = FALSE:

septic_patients %>%
   freq(hospital_id, row.names = FALSE)
-

Frequency table of hospital_id from a data.frame (2,000 x 49)

+

Frequency table of hospital_id from septic_patients (2,000 x 49)

Class: factor (numeric)
Length: 2,000 (of which NA: 0 = 0.00%)
Levels: 4: A, B, C, D
@@ -864,7 +864,7 @@ Unique: 4

The markdown parameter is TRUE at default in non-interactive sessions, like in reports created with R Markdown. This will always print all rows, unless nmax is set. Without markdown (like in regular R), a frequency table would print like:

septic_patients %>%
   freq(hospital_id, markdown = FALSE)
-# Frequency table of `hospital_id` from a data.frame (2,000 x 49) 
+# Frequency table of `hospital_id` from `septic_patients` (2,000 x 49) 
 # 
 # Class:   factor (numeric)
 # Length:  2,000 (of which NA: 0 = 0.00%)
diff --git a/docs/articles/index.html b/docs/articles/index.html
index e110a408..db8a1e95 100644
--- a/docs/articles/index.html
+++ b/docs/articles/index.html
@@ -78,7 +78,7 @@
       
       
         AMR (for R)
-        0.7.0.9000
+        0.7.0.9001
       
     
diff --git a/docs/articles/mo_property.html b/docs/articles/mo_property.html index edf1ccef..2f83d642 100644 --- a/docs/articles/mo_property.html +++ b/docs/articles/mo_property.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0 + 0.7.0.9000 @@ -199,7 +199,7 @@

How to get properties of a microorganism

Matthijs S. Berends

-

03 June 2019

+

07 June 2019

diff --git a/docs/articles/resistance_predict.html b/docs/articles/resistance_predict.html index 2b641df0..078e9755 100644 --- a/docs/articles/resistance_predict.html +++ b/docs/articles/resistance_predict.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0 + 0.7.0.9000 @@ -199,7 +199,7 @@

How to predict antimicrobial resistance

Matthijs S. Berends

-

03 June 2019

+

07 June 2019

diff --git a/docs/authors.html b/docs/authors.html index b0c8c44e..01952881 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.0.9000 + 0.7.0.9001 diff --git a/docs/extra.css b/docs/extra.css index b9112266..1ab8e530 100644 --- a/docs/extra.css +++ b/docs/extra.css @@ -202,13 +202,3 @@ table a:not(.btn):hover, .table a:not(.btn):hover { color: black; font-weight: bold; } - -#collapseDisqus { - padding: 2%; - border: 2px #2c3e50 dashed; - margin-top: 1%; -} -#btn_collapseDisqus { - white-space: normal; -} - diff --git a/docs/extra.js b/docs/extra.js index 11554706..63f504a9 100644 --- a/docs/extra.js +++ b/docs/extra.js @@ -23,8 +23,6 @@ // Add updated Font Awesome 5.8.2 library $('head').append(''); -// Add Disqus -$('head').append(''); // Email template for new GitLab issues //https://stackoverflow.com/a/33190494/4575331 @@ -32,6 +30,13 @@ $('head').append(''); + + // add link to survey at home sidebar + $('.template-home #sidebar .list-unstyled:first').append('
  • Please fill in our survey at
    https://www.surveymonkey.com/r/AMR_for_R
  • '); + + // remove version label from header $(".version.label").remove(); @@ -56,18 +61,6 @@ $( document ).ready(function() { ''); } - // add Disqus to all pages - var disqus = - '' + - '
    ' + - '
    ' + - '
    '; - - $(disqus).insertBefore('footer'); - $('#disqus_thread footer').remove(); - // edit footer $('footer').html( '
    ' + diff --git a/docs/index.html b/docs/index.html index f1d859e4..debacf8b 100644 --- a/docs/index.html +++ b/docs/index.html @@ -42,7 +42,7 @@ AMR (for R) - 0.7.0.9000 + 0.7.0.9001
    diff --git a/docs/news/index.html b/docs/news/index.html index ea82e73f..10011e85 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.0.9000 + 0.7.0.9001 @@ -239,21 +239,45 @@ -
    +

    -AMR 0.7.0.9000 Unreleased +AMR 0.7.0.9001 Unreleased

    New

    +
      +
    • +

      Support for all scientifically published pathotypes of E. coli to date. Supported are: AIEC (Adherent-Invasive E. coli), ATEC (Atypical Entero-pathogenic E. coli), DAEC (Diffusely Adhering E. coli), EAEC (Entero-Aggresive E. coli), EHEC (Entero-Haemorrhagic E. coli), EIEC (Entero-Invasive E. coli), EPEC (Entero-Pathogenic E. coli), ETEC (Entero-Toxigenic E. coli), NMEC (Neonatal Meningitis‐causing E. coli), STEC (Shiga-toxin producing E. coli) and UPEC (Uropathogenic E. coli). All these lead to the microbial ID of E. coli:

      + +
    • +

    Changed

    +
      +
    • Fixed bug in translation of microorganism names
    • +
    • Fixed bug in determining taxonomic kingdoms
    • +
    • Algorithm improvements for as.ab() and as.mo() to understand even more severe misspelled input
    • +
    • Added ggplot2 methods for automatically determining the scale type of classes mo and ab +
    • +
    • Added names of object in the header in frequency tables, even when using pipes
    • +
    • Prevented "bacteria" from getting coerced by as.ab() because Bacterial is a brand name of trimethoprim (TMP)
    • +
    • Fixed a bug where setting an antibiotic would not work for eucast_rules() and mdro() +
    • +
    • Fixed a EUCAST rule for Staphylococci, where amikacin resistance would not be inferred from tobramycin
    • +

    Other

    +
      +
    • Fixed a note thrown by CRAN tests
    • +
    + @@ -406,32 +430,32 @@ This data is updated annually - check the included version with the new function
  • New filters for antimicrobial classes. Use these functions to filter isolates on results in one of more antibiotics from a specific class:

    - +

    The antibiotics data set will be searched, after which the input data will be checked for column names with a value in any abbreviations, codes or official names found in the antibiotics data set. For example:

    - +
  • All ab_* functions are deprecated and replaced by atc_* functions:

    - + These functions use as.atc() internally. The old atc_property has been renamed atc_online_property(). This is done for two reasons: firstly, not all ATC codes are of antibiotics (ab) but can also be of antivirals or antifungals. Secondly, the input must have class atc or must be coerable to this class. Properties of these classes should start with the same class name, analogous to as.mo() and e.g. mo_genus.
  • New functions set_mo_source() and get_mo_source() to use your own predefined MO codes as input for as.mo() and consequently all mo_* functions
  • Support for the upcoming dplyr version 0.8.0
  • @@ -443,20 +467,20 @@ These functions use as.atc()
  • New function age_groups() to split ages into custom or predefined groups (like children or elderly). This allows for easier demographic antimicrobial resistance analysis per age group.
  • New function ggplot_rsi_predict() as well as the base R plot() function can now be used for resistance prediction calculated with resistance_predict():

    -
    x <- resistance_predict(septic_patients, col_ab = "amox")
    -plot(x)
    -ggplot_rsi_predict(x)
    +
    x <- resistance_predict(septic_patients, col_ab = "amox")
    +plot(x)
    +ggplot_rsi_predict(x)
  • Functions filter_first_isolate() and filter_first_weighted_isolate() to shorten and fasten filtering on data sets with antimicrobial results, e.g.:

    - +

    is equal to:

    -
    septic_patients %>%
    -  mutate(only_firsts = first_isolate(septic_patients, ...)) %>%
    -  filter(only_firsts == TRUE) %>%
    -  select(-only_firsts)
    +
    septic_patients %>%
    +  mutate(only_firsts = first_isolate(septic_patients, ...)) %>%
    +  filter(only_firsts == TRUE) %>%
    +  select(-only_firsts)
  • New function availability() to check the number of available (non-empty) results in a data.frame
  • @@ -485,33 +509,33 @@ These functions use as.atc()

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

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

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

    - +
  • Functions count_R, count_IR, count_I, count_SI and count_S to selectively count resistant or susceptible isolates
  • @@ -1084,7 +1108,7 @@ Using as.mo(..., allow_uncertain = 3)

    Contents