diff --git a/DESCRIPTION b/DESCRIPTION index bf4c251ad..93a620041 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 1.3.0.9009 -Date: 2020-08-26 +Version: 1.3.0.9010 +Date: 2020-08-28 Title: Antimicrobial Resistance Analysis Authors@R: c( person(role = c("aut", "cre"), diff --git a/NAMESPACE b/NAMESPACE index 967d8a920..d189314fa 100755 --- a/NAMESPACE +++ b/NAMESPACE @@ -40,11 +40,6 @@ S3method(format,bug_drug_combinations) S3method(kurtosis,data.frame) S3method(kurtosis,default) S3method(kurtosis,matrix) -S3method(pillar_shaft,ab) -S3method(pillar_shaft,disk) -S3method(pillar_shaft,mic) -S3method(pillar_shaft,mo) -S3method(pillar_shaft,rsi) S3method(plot,mic) S3method(plot,resistance_predict) S3method(plot,rsi) @@ -63,11 +58,6 @@ S3method(skewness,matrix) S3method(summary,mic) S3method(summary,mo) S3method(summary,rsi) -S3method(type_sum,ab) -S3method(type_sum,disk) -S3method(type_sum,mic) -S3method(type_sum,mo) -S3method(type_sum,rsi) export("%like%") export("%like_case%") export(ab_atc) diff --git a/NEWS.md b/NEWS.md index 9325353b8..5beff68ad 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,7 +1,8 @@ -# AMR 1.3.0.9009 -## Last updated: 26 August 2020 +# AMR 1.3.0.9010 +## Last updated: 28 August 2020 ### New +* A new vignette and website page with info about all our public and freely available data sets, that can be downloaded as flat files or in formats for use in R, SPSS, SAS, Stata and Excel: https://msberends.github.io/AMR/articles/datasets.html * Data set `intrinsic_resistant`. This data set contains all bug-drug combinations where the 'bug' is intrinsic resistant to the 'drug' according to the latest EUCAST insights. It contains just two columns: `microorganism` and `antibiotic`. Curious about which enterococci are actually intrinsic resistant to vancomycin? @@ -38,7 +39,7 @@ * Overall speed improvement by tweaking joining functions * Function `mo_shortname()` now returns the genus for input where the species is unknown * BORSA is now recognised as an abbreviation for *Staphylococcus aureus*, meaning that e.g. `mo_genus("BORSA")` will return "Staphylococcus" -* Support for coloured `tibble` printing of classes `ab`, `mo`, `rsi`, `mic` and `disk` +* Added a feature from AMR 1.1.0 and earlier again, but now without other package dependencies: `tibble` printing support for classes ``, ``, ``, `` and ``. When using `tibble`s containing antimicrobial columns (class ``), "S" will print in green, "I" will print in yellow and "R" will print in red. Microbial IDs (class ``) will emphasise on the genus and species, not on the kingdom. # AMR 1.3.0 @@ -102,8 +103,8 @@ Negative effects of this change are: * Function `freq()` that was borrowed from the `cleaner` package was removed. Use `cleaner::freq()`, or run `library("cleaner")` before you use `freq()`. - * Printing values of class `mo` or `rsi` in a tibble will no longer be in colour and printing `rsi` in a tibble will show the class ``, not `` anymore. This is purely a visual effect. - * All functions from the `mo_*` family (like `mo_name()` and `mo_gramstain()`) are noticeably slower when running on hundreds of thousands of rows. + * ~~Printing values of class `mo` or `rsi` in a tibble will no longer be in colour and printing `rsi` in a tibble will show the class ``, not `` anymore. This is purely a visual effect.~~ + * ~~All functions from the `mo_*` family (like `mo_name()` and `mo_gramstain()`) are noticeably slower when running on hundreds of thousands of rows.~~ * For developers: classes `mo` and `ab` now both also inherit class `character`, to support any data transformation. This change invalidates code that checks for class length == 1. ### Changed diff --git a/R/aa_helper_functions.R b/R/aa_helper_functions.R index 9c00ce8c2..d163e286a 100755 --- a/R/aa_helper_functions.R +++ b/R/aa_helper_functions.R @@ -444,6 +444,9 @@ font_red_bg <- function(..., collapse = " ") { font_yellow_bg <- function(..., collapse = " ") { try_colour(..., before = "\033[43m", after = "\033[49m", collapse = collapse) } +font_na <- function(..., collapse = " ") { + font_red(..., collapse = collapse) +} font_bold <- function(..., collapse = " ") { try_colour(..., before = "\033[1m", after = "\033[22m", collapse = collapse) } @@ -477,6 +480,61 @@ progress_estimated <- function(n = 1, n_min = 0, ...) { } } +create_pillar_column <- function(x, ...) { + new_pillar_shaft_simple <- import_fn("new_pillar_shaft_simple", "pillar", error_on_fail = FALSE) + if (!is.null(new_pillar_shaft_simple)) { + new_pillar_shaft_simple(x, ...) + } else { + # does not exist in package 'pillar' anymore + structure(list(x), + class = "pillar_shaft_simple", + ...) + } +} + +# copied from vctrs::s3_register by their permission +s3_register <- function(generic, class, method = NULL) { + stopifnot(is.character(generic), length(generic) == 1) + stopifnot(is.character(class), length(class) == 1) + pieces <- strsplit(generic, "::")[[1]] + stopifnot(length(pieces) == 2) + package <- pieces[[1]] + generic <- pieces[[2]] + caller <- parent.frame() + get_method_env <- function() { + top <- topenv(caller) + if (isNamespace(top)) { + asNamespace(environmentName(top)) + } + else { + caller + } + } + get_method <- function(method, env) { + if (is.null(method)) { + get(paste0(generic, ".", class), envir = get_method_env()) + } + else { + method + } + } + method_fn <- get_method(method) + stopifnot(is.function(method_fn)) + setHook(packageEvent(package, "onLoad"), function(...) { + ns <- asNamespace(package) + method_fn <- get_method(method) + registerS3method(generic, class, method_fn, envir = ns) + }) + if (!isNamespaceLoaded(package)) { + return(invisible()) + } + envir <- asNamespace(package) + if (exists(generic, envir)) { + registerS3method(generic, class, method_fn, envir = envir) + } + invisible() +} + # works exactly like round(), but rounds `round2(44.55, 1)` to 44.6 instead of 44.5 # and adds decimal zeroes until `digits` is reached when force_zero = TRUE round2 <- function(x, digits = 0, force_zero = TRUE) { diff --git a/R/ab.R b/R/ab.R index 52469f9ed..93220bf27 100755 --- a/R/ab.R +++ b/R/ab.R @@ -467,22 +467,14 @@ is.ab <- function(x) { inherits(x, "ab") } - -#' @method pillar_shaft ab -#' @export +# will be exported using s3_register() in R/zzz.R pillar_shaft.ab <- function(x, ...) { - # import from the pillar package, without being dependent on it! - style_na <- import_fn("style_na", "pillar", error_on_fail = FALSE) - new_pillar_shaft_simple <- import_fn("new_pillar_shaft_simple", "pillar", error_on_fail = FALSE) - out <- format(x) - out[is.na(x)] <- style_na(NA) - new_pillar_shaft_simple(out, - align = "left", - min_width = 4) + out <- trimws(format(x)) + out[is.na(x)] <- font_na(NA) + create_pillar_column(out, align = "left", min_width = 4) } -#' @method type_sum ab -#' @export +# will be exported using s3_register() in R/zzz.R type_sum.ab <- function(x, ...) { "ab" } diff --git a/R/disk.R b/R/disk.R index fadbabcea..50f331f5a 100644 --- a/R/disk.R +++ b/R/disk.R @@ -114,18 +114,14 @@ is.disk <- function(x) { inherits(x, "disk") } -#' @method pillar_shaft disk -#' @export +# will be exported using s3_register() in R/zzz.R pillar_shaft.disk <- function(x, ...) { - style_na <- import_fn("style_na", "pillar", error_on_fail = FALSE) - new_pillar_shaft_simple <- import_fn("new_pillar_shaft_simple", "pillar", error_on_fail = FALSE) out <- trimws(format(x)) - out[is.na(x)] <- style_na(NA) - new_pillar_shaft_simple(out, align = "right", min_width = 3) + out[is.na(x)] <- font_na(NA) + create_pillar_column(out, align = "right", width = 2) } -#' @method type_sum disk -#' @export +# will be exported using s3_register() in R/zzz.R type_sum.disk <- function(x, ...) { "disk" } diff --git a/R/mic.R b/R/mic.R index daa796354..1118c5e58 100755 --- a/R/mic.R +++ b/R/mic.R @@ -171,18 +171,14 @@ droplevels.mic <- function(x, exclude = ifelse(anyNA(levels(x)), NULL, NA), ...) x } -#' @method pillar_shaft mic -#' @export +# will be exported using s3_register() in R/zzz.R pillar_shaft.mic <- function(x, ...) { - style_na <- import_fn("style_na", "pillar", error_on_fail = FALSE) - new_pillar_shaft_simple <- import_fn("new_pillar_shaft_simple", "pillar", error_on_fail = FALSE) out <- trimws(format(x)) - out[is.na(x)] <- style_na(NA) - new_pillar_shaft_simple(out, align = "right", min_width = 4) + out[is.na(x)] <- font_na(NA) + create_pillar_column(out, align = "right", min_width = 4) } -#' @method type_sum mic -#' @export +# will be exported using s3_register() in R/zzz.R type_sum.mic <- function(x, ...) { "mic" } diff --git a/R/mo.R b/R/mo.R index 0a0486548..3af0e7055 100755 --- a/R/mo.R +++ b/R/mo.R @@ -181,7 +181,7 @@ as.mo <- function(x, x <- parse_and_convert(x) # replace mo codes used in older package versions x <- replace_old_mo_codes(x, property = "mo") - + # WHONET: xxx = no growth x[tolower(as.character(paste0(x, ""))) %in% c("", "xxx", "na", "nan")] <- NA_character_ # Laboratory systems: remove entries like "no growth" etc @@ -384,7 +384,7 @@ exec_as.mo <- function(x, x <- data.frame(fullname = x, stringsAsFactors = FALSE) %>% left_join_MO_lookup(by = "fullname") %>% pull(property) - + } else if (all(toupper(x) %in% microorganisms.codes$code)) { # commonly used MO codes x <- data.frame(code = toupper(x), stringsAsFactors = FALSE) %>% @@ -1526,41 +1526,54 @@ format_uncertainty_as_df <- function(uncertainty_level, df } -#' @method pillar_shaft mo -#' @export +# will be exported using s3_register() in R/zzz.R pillar_shaft.mo <- function(x, ...) { - # import from the pillar package, without being dependent on it! - style_na <- import_fn("style_na", "pillar", error_on_fail = FALSE) - style_subtle <- import_fn("style_subtle", "pillar", error_on_fail = FALSE) - new_pillar_shaft_simple <- import_fn("new_pillar_shaft_simple", "pillar", error_on_fail = FALSE) - if (is.null(style_na) | is.null(style_subtle) | is.null(new_pillar_shaft_simple)) { - return(x) - } - out <- format(x) # grey out the kingdom (part until first "_") - out[!is.na(x)] <- gsub("^([A-Z]+_)(.*)", paste0(style_subtle("\\1"), "\\2"), out[!is.na(x)]) + out[!is.na(x)] <- gsub("^([A-Z]+_)(.*)", paste0(font_subtle("\\1"), "\\2"), out[!is.na(x)]) # and grey out every _ - out[!is.na(x)] <- gsub("_", style_subtle("_"), out[!is.na(x)]) + out[!is.na(x)] <- gsub("_", font_subtle("_"), out[!is.na(x)]) # markup NA and UNKNOWN - out[is.na(x)] <- style_na(" NA") - out[x == "UNKNOWN"] <- style_na(" UNKNOWN") + out[is.na(x)] <- font_na(" NA") + out[x == "UNKNOWN"] <- font_na(" UNKNOWN") # make it always fit exactly - new_pillar_shaft_simple(out, - align = "left", - width = max(nchar(x)) + ifelse(length(x[x %in% c(NA, "UNKNOWN")]) > 0, - 2, - 0)) + create_pillar_column(out, + align = "left", + width = max(nchar(x)) + ifelse(any(x %in% c(NA, "UNKNOWN")), 2, 0)) } -#' @method type_sum mo -#' @export +# will be exported using s3_register() in R/zzz.R type_sum.mo <- function(x, ...) { "mo" } +# will be exported using s3_register() in R/zzz.R +freq.mo <- function(x, ...) { + x_noNA <- as.mo(x[!is.na(x)]) # as.mo() to get the newest mo codes + grams <- mo_gramstain(x_noNA, language = NULL) + digits <- list(...)$digits + if (is.null(digits)) { + digits <- 2 + } + freq.default <- import_fn("freq.default", "cleaner", error_on_fail = FALSE) + freq.default(x = x, ..., + .add_header = list(`Gram-negative` = paste0(format(sum(grams == "Gram-negative", na.rm = TRUE), + big.mark = ",", + decimal.mark = "."), + " (", percentage(sum(grams == "Gram-negative", na.rm = TRUE) / length(grams), digits = digits), + ")"), + `Gram-positive` = paste0(format(sum(grams == "Gram-positive", na.rm = TRUE), + big.mark = ",", + decimal.mark = "."), + " (", percentage(sum(grams == "Gram-positive", na.rm = TRUE) / length(grams), digits = digits), + ")"), + `No. of genera` = n_distinct(mo_genus(x_noNA, language = NULL)), + `No. of species` = n_distinct(paste(mo_genus(x_noNA, language = NULL), + mo_species(x_noNA, language = NULL))))) +} + #' @method print mo #' @export #' @noRd @@ -1584,11 +1597,11 @@ summary.mo <- function(object, ...) { top <- as.data.frame(table(x), responseName = "n", stringsAsFactors = FALSE) top_3 <- top[order(-top$n), 1][1:3] value <- c("Class" = "mo", - "" = length(x[is.na(x)]), - "Unique" = n_distinct(x[!is.na(x)]), - "#1" = top_3[1], - "#2" = top_3[2], - "#3" = top_3[3]) + "" = length(x[is.na(x)]), + "Unique" = n_distinct(x[!is.na(x)]), + "#1" = top_3[1], + "#2" = top_3[2], + "#3" = top_3[3]) class(value) <- c("summaryDefault", "table") value } diff --git a/R/rsi.R b/R/rsi.R index 5af30b38f..2698a445e 100755 --- a/R/rsi.R +++ b/R/rsi.R @@ -670,24 +670,42 @@ exec_as.rsi <- function(method, class = c("rsi", "ordered", "factor")) } -#' @method pillar_shaft rsi -#' @export +# will be exported using s3_register() in R/zzz.R pillar_shaft.rsi <- function(x, ...) { out <- trimws(format(x)) out[is.na(x)] <- font_grey(" NA") - out[x == "S"] <- font_green_bg(font_white(" S ")) - out[x == "I"] <- font_yellow_bg(font_black(" I ")) - out[x == "R"] <- font_red_bg(font_white(" R ")) - new_pillar_shaft_simple <- import_fn("new_pillar_shaft_simple", "pillar", error_on_fail = FALSE) - new_pillar_shaft_simple(out, align = "left", width = 3) + out[x == "S"] <- font_green_bg(font_white(" S ")) + out[x == "I"] <- font_yellow_bg(font_black(" I ")) + out[x == "R"] <- font_red_bg(font_white(" R ")) + create_pillar_column(out, align = "left", width = 5) } -#' @method type_sum rsi -#' @export +# will be exported using s3_register() in R/zzz.R type_sum.rsi <- function(x, ...) { "rsi" } +# will be exported using s3_register() in R/zzz.R +freq.rsi <- function(x, ...) { + x_name <- deparse(substitute(x)) + x_name <- gsub(".*[$]", "", x_name) + ab <- suppressMessages(suppressWarnings(as.ab(x_name))) + freq.default <- import_fn("freq.default", "cleaner", error_on_fail = FALSE) + digits <- list(...)$digits + if (is.null(digits)) { + digits <- 2 + } + if (!is.na(ab)) { + freq.default(x = x, ..., + .add_header = list(Drug = paste0(ab_name(ab, language = NULL), " (", ab, ", ", ab_atc(ab), ")"), + `Drug group` = ab_group(ab, language = NULL), + `%SI` = percentage(susceptibility(x, minimum = 0, as_percent = FALSE), digits = digits))) + } else { + freq.default(x = x, ..., + .add_header = list(`%SI` = percentage(susceptibility(x, minimum = 0, as_percent = FALSE), digits = digits))) + } +} + #' @method print rsi #' @export #' @noRd diff --git a/R/zzz.R b/R/zzz.R index 1e0738015..49375558f 100755 --- a/R/zzz.R +++ b/R/zzz.R @@ -29,6 +29,7 @@ envir = asNamespace("AMR")) # support for tibble headers (type_sum) and tibble columns content (pillar_shaft) + # without the need to depend on other packages s3_register("pillar::pillar_shaft", "ab") s3_register("tibble::type_sum", "ab") s3_register("pillar::pillar_shaft", "mo") @@ -39,9 +40,10 @@ s3_register("tibble::type_sum", "mic") s3_register("pillar::pillar_shaft", "disk") s3_register("tibble::type_sum", "disk") + # support for frequency tables + s3_register("cleaner::freq", "mo") + s3_register("cleaner::freq", "rsi") } -pillar_shaft <- import_fn("pillar_shaft", "pillar", error_on_fail = FALSE) -type_sum <- import_fn("type_sum", "tibble", error_on_fail = FALSE) .onAttach <- function(...) { if (!interactive() || stats::runif(1) > 0.1 || isTRUE(as.logical(Sys.getenv("AMR_silentstart", FALSE)))) { @@ -66,9 +68,9 @@ create_MO_lookup <- function() { MO_lookup$fullname_lower <- tolower(trimws(paste(MO_lookup$genus, MO_lookup$species, MO_lookup$subspecies))) - MO_lookup[MO_lookup$genus == "" | grepl("^[(]unknown ", MO_lookup$fullname), "fullname_lower"] <- tolower(trimws(MO_lookup[MO_lookup$genus == "" | grepl("^[(]unknown ", MO_lookup$fullname), - "fullname"])) - MO_lookup$fullname_lower <- gsub("[^.a-z0-9/ \\-]+", "", MO_lookup$fullname_lower) + ind <- MO_lookup$genus == "" | grepl("^[(]unknown ", MO_lookup$fullname) + MO_lookup[ind, "fullname_lower"] <- tolower(MO_lookup[ind, "fullname"]) + MO_lookup$fullname_lower <- trimws(gsub("[^.a-z0-9/ \\-]+", "", MO_lookup$fullname_lower)) # add a column with only "e coli" like combinations MO_lookup$g_species <- gsub("^([a-z])[a-z]+ ([a-z]+) ?.*", "\\1 \\2", MO_lookup$fullname_lower) @@ -79,54 +81,11 @@ create_MO_lookup <- function() { create_MO.old_lookup <- function() { MO.old_lookup <- AMR::microorganisms.old - MO.old_lookup$fullname_lower <- gsub("[^.a-z0-9/ \\-]+", "", tolower(trimws(MO.old_lookup$fullname))) + MO.old_lookup$fullname_lower <- trimws(gsub("[^.a-z0-9/ \\-]+", "", tolower(trimws(MO.old_lookup$fullname)))) - # add a column with only "e coli" like combinations - MO.old_lookup$g_species <- gsub("^([a-z])[a-z]+ ([a-z]+) ?.*", "\\1 \\2", MO.old_lookup$fullname_lower) + # add a column with only "e coli"-like combinations + MO.old_lookup$g_species <- trimws(gsub("^([a-z])[a-z]+ ([a-z]+) ?.*", "\\1 \\2", MO.old_lookup$fullname_lower)) # so arrange data on prevalence first, then full name MO.old_lookup[order(MO.old_lookup$prevalence, MO.old_lookup$fullname_lower), ] } - -# copied from vctrs::s3_register -s3_register <- function(generic, class, method = NULL) { - stopifnot(is.character(generic), length(generic) == 1) - stopifnot(is.character(class), length(class) == 1) - pieces <- strsplit(generic, "::")[[1]] - stopifnot(length(pieces) == 2) - package <- pieces[[1]] - generic <- pieces[[2]] - caller <- parent.frame() - get_method_env <- function() { - top <- topenv(caller) - if (isNamespace(top)) { - asNamespace(environmentName(top)) - } - else { - caller - } - } - get_method <- function(method, env) { - if (is.null(method)) { - get(paste0(generic, ".", class), envir = get_method_env()) - } - else { - method - } - } - method_fn <- get_method(method) - stopifnot(is.function(method_fn)) - setHook(packageEvent(package, "onLoad"), function(...) { - ns <- asNamespace(package) - method_fn <- get_method(method) - registerS3method(generic, class, method_fn, envir = ns) - }) - if (!isNamespaceLoaded(package)) { - return(invisible()) - } - envir <- asNamespace(package) - if (exists(generic, envir)) { - registerS3method(generic, class, method_fn, envir = envir) - } - invisible() -} diff --git a/data-raw/antibiotics.dta b/data-raw/antibiotics.dta index 65a397118..e945d313e 100644 Binary files a/data-raw/antibiotics.dta and b/data-raw/antibiotics.dta differ diff --git a/data-raw/antibiotics.sas b/data-raw/antibiotics.sas index 22667b8b8..969749e92 100644 Binary files a/data-raw/antibiotics.sas and b/data-raw/antibiotics.sas differ diff --git a/data-raw/antibiotics.sav b/data-raw/antibiotics.sav index 9ed8bad5f..4e750fe4b 100644 Binary files a/data-raw/antibiotics.sav and b/data-raw/antibiotics.sav differ diff --git a/data-raw/antibiotics.xlsx b/data-raw/antibiotics.xlsx index 744fbc7b4..9c2bfa2ef 100644 Binary files a/data-raw/antibiotics.xlsx and b/data-raw/antibiotics.xlsx differ diff --git a/data-raw/antivirals.dta b/data-raw/antivirals.dta index adfb02c63..218c46d6f 100644 Binary files a/data-raw/antivirals.dta and b/data-raw/antivirals.dta differ diff --git a/data-raw/antivirals.sas b/data-raw/antivirals.sas index e6dab17da..6ad865b28 100644 Binary files a/data-raw/antivirals.sas and b/data-raw/antivirals.sas differ diff --git a/data-raw/antivirals.sav b/data-raw/antivirals.sav index 5a96ebca1..a5d07a1c3 100644 Binary files a/data-raw/antivirals.sav and b/data-raw/antivirals.sav differ diff --git a/data-raw/antivirals.xlsx b/data-raw/antivirals.xlsx index eb444e214..76d1af99e 100644 Binary files a/data-raw/antivirals.xlsx and b/data-raw/antivirals.xlsx differ diff --git a/data-raw/intrinsic_resistant.dta b/data-raw/intrinsic_resistant.dta index 41548e794..a8f1af78f 100644 Binary files a/data-raw/intrinsic_resistant.dta and b/data-raw/intrinsic_resistant.dta differ diff --git a/data-raw/intrinsic_resistant.sas b/data-raw/intrinsic_resistant.sas index 0e1782e18..f340dbd92 100644 Binary files a/data-raw/intrinsic_resistant.sas and b/data-raw/intrinsic_resistant.sas differ diff --git a/data-raw/intrinsic_resistant.sav b/data-raw/intrinsic_resistant.sav index ab1f33f1e..d2857e18e 100644 Binary files a/data-raw/intrinsic_resistant.sav and b/data-raw/intrinsic_resistant.sav differ diff --git a/data-raw/intrinsic_resistant.xlsx b/data-raw/intrinsic_resistant.xlsx index 4a428bce6..609e1aa8d 100644 Binary files a/data-raw/intrinsic_resistant.xlsx and b/data-raw/intrinsic_resistant.xlsx differ diff --git a/data-raw/microorganisms.dta b/data-raw/microorganisms.dta index dea339d5a..68a42f6df 100644 Binary files a/data-raw/microorganisms.dta and b/data-raw/microorganisms.dta differ diff --git a/data-raw/microorganisms.old.dta b/data-raw/microorganisms.old.dta index 0251d0aa6..bde82fd10 100644 Binary files a/data-raw/microorganisms.old.dta and b/data-raw/microorganisms.old.dta differ diff --git a/data-raw/microorganisms.old.sas b/data-raw/microorganisms.old.sas index 4f5fbec71..30572c941 100644 Binary files a/data-raw/microorganisms.old.sas and b/data-raw/microorganisms.old.sas differ diff --git a/data-raw/microorganisms.old.sav b/data-raw/microorganisms.old.sav index 6d47a322b..5c0655d54 100644 Binary files a/data-raw/microorganisms.old.sav and b/data-raw/microorganisms.old.sav differ diff --git a/data-raw/microorganisms.old.xlsx b/data-raw/microorganisms.old.xlsx index 426744d8b..34a70422b 100644 Binary files a/data-raw/microorganisms.old.xlsx and b/data-raw/microorganisms.old.xlsx differ diff --git a/data-raw/microorganisms.sas b/data-raw/microorganisms.sas index d8c6bc37c..1c7fe5e49 100644 Binary files a/data-raw/microorganisms.sas and b/data-raw/microorganisms.sas differ diff --git a/data-raw/microorganisms.sav b/data-raw/microorganisms.sav index 0a776bd0c..5ca51f1ff 100644 Binary files a/data-raw/microorganisms.sav and b/data-raw/microorganisms.sav differ diff --git a/data-raw/microorganisms.xlsx b/data-raw/microorganisms.xlsx index 96ec13409..a6fe8c1f4 100644 Binary files a/data-raw/microorganisms.xlsx and b/data-raw/microorganisms.xlsx differ diff --git a/data-raw/rsi_translation.dta b/data-raw/rsi_translation.dta index 9b1db5160..80950c971 100644 Binary files a/data-raw/rsi_translation.dta and b/data-raw/rsi_translation.dta differ diff --git a/data-raw/rsi_translation.sas b/data-raw/rsi_translation.sas index 596709944..ab5d21b0d 100644 Binary files a/data-raw/rsi_translation.sas and b/data-raw/rsi_translation.sas differ diff --git a/data-raw/rsi_translation.sav b/data-raw/rsi_translation.sav index e28c702eb..f7ea73e7d 100644 Binary files a/data-raw/rsi_translation.sav and b/data-raw/rsi_translation.sav differ diff --git a/data-raw/rsi_translation.xlsx b/data-raw/rsi_translation.xlsx index b5b522903..0a6e67305 100644 Binary files a/data-raw/rsi_translation.xlsx and b/data-raw/rsi_translation.xlsx differ diff --git a/docs/404.html b/docs/404.html index 882dab7d6..f28619d6a 100644 --- a/docs/404.html +++ b/docs/404.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9009 + 1.3.0.9010 diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index 5d38cbaf1..0de18688d 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9009 + 1.3.0.9010 diff --git a/docs/articles/index.html b/docs/articles/index.html index 0c6d799bb..af3bb758a 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9009 + 1.3.0.9010 diff --git a/docs/authors.html b/docs/authors.html index d2a570c00..ea305e82b 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9009 + 1.3.0.9010 diff --git a/docs/index.html b/docs/index.html index 2793708dd..fee483d93 100644 --- a/docs/index.html +++ b/docs/index.html @@ -43,7 +43,7 @@ AMR (for R) - 1.3.0.9009 + 1.3.0.9010 diff --git a/docs/news/index.html b/docs/news/index.html index 5ed025704..771aa3e1e 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9009 + 1.3.0.9010 @@ -236,18 +236,19 @@ Source: NEWS.md -
-

-AMR 1.3.0.9009 Unreleased +
+

+AMR 1.3.0.9010 Unreleased

-
+

-Last updated: 26 August 2020 +Last updated: 28 August 2020

New

    +
  • A new vignette and website page with info about all our public and freely available data sets, that can be downloaded as flat files or in formats for use in R, SPSS, SAS, Stata and Excel: https://msberends.github.io/AMR/articles/datasets.html

  • Data set intrinsic_resistant. This data set contains all bug-drug combinations where the ‘bug’ is intrinsic resistant to the ‘drug’ according to the latest EUCAST insights. It contains just two columns: microorganism and antibiotic.

    Curious about which enterococci are actually intrinsic resistant to vancomycin?

    @@ -297,7 +298,7 @@
  • Overall speed improvement by tweaking joining functions

  • Function mo_shortname() now returns the genus for input where the species is unknown

  • BORSA is now recognised as an abbreviation for Staphylococcus aureus, meaning that e.g. mo_genus("BORSA") will return “Staphylococcus”

  • -
  • Support for coloured tibble printing of classes ab, mo, rsi, mic and disk

  • +
  • Added a feature from AMR 1.1.0 and earlier again, but now without other package dependencies: tibble printing support for classes <rsi>, <mic>, <disk>, <ab> and <mo>. When using tibbles containing antimicrobial columns (class <rsi>), “S” will print in green, “I” will print in yellow and “R” will print in red. Microbial IDs (class <mo>) will emphasise on the genus and species, not on the kingdom.

@@ -399,8 +400,8 @@

Negative effects of this change are:

  • Function freq() that was borrowed from the cleaner package was removed. Use cleaner::freq(), or run library("cleaner") before you use freq().
  • -
  • Printing values of class mo or rsi in a tibble will no longer be in colour and printing rsi in a tibble will show the class <ord>, not <rsi> anymore. This is purely a visual effect.
  • -
  • All functions from the mo_* family (like mo_name() and mo_gramstain()) are noticeably slower when running on hundreds of thousands of rows.
  • +
  • Printing values of class mo or rsi in a tibble will no longer be in colour and printing rsi in a tibble will show the class <ord>, not <rsi> anymore. This is purely a visual effect.
  • +
  • All functions from the mo_* family (like mo_name() and mo_gramstain()) are noticeably slower when running on hundreds of thousands of rows.
  • For developers: classes mo and ab now both also inherit class character, to support any data transformation. This change invalidates code that checks for class length == 1.
diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index 89692fc9d..2206fdffb 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -2,7 +2,7 @@ pandoc: 2.7.3 pkgdown: 1.5.1.9000 pkgdown_sha: eae56f08694abebf93cdfc0dd8e9ede06d8c815f articles: [] -last_built: 2020-08-26T14:13Z +last_built: 2020-08-28T19:54Z urls: reference: https://msberends.github.io/AMR/reference article: https://msberends.github.io/AMR/articles diff --git a/docs/reference/antibiotic_class_selectors.html b/docs/reference/antibiotic_class_selectors.html index ee9c10906..c685b61c4 100644 --- a/docs/reference/antibiotic_class_selectors.html +++ b/docs/reference/antibiotic_class_selectors.html @@ -82,7 +82,7 @@ AMR (for R) - 1.3.0.9009 + 1.3.0.9010
diff --git a/docs/reference/as.mo.html b/docs/reference/as.mo.html index 221077b32..8b167a169 100644 --- a/docs/reference/as.mo.html +++ b/docs/reference/as.mo.html @@ -82,7 +82,7 @@ AMR (for R) - 1.3.0.9007 + 1.3.0.9010
diff --git a/docs/reference/bug_drug_combinations.html b/docs/reference/bug_drug_combinations.html index 90a1a538e..60bdbea37 100644 --- a/docs/reference/bug_drug_combinations.html +++ b/docs/reference/bug_drug_combinations.html @@ -82,7 +82,7 @@ AMR (for R) - 1.3.0.9009 + 1.3.0.9010

diff --git a/docs/reference/eucast_rules.html b/docs/reference/eucast_rules.html index f43976ce0..fb0c7d22a 100644 --- a/docs/reference/eucast_rules.html +++ b/docs/reference/eucast_rules.html @@ -83,7 +83,7 @@ To improve the interpretation of the antibiogram before EUCAST rules are applied AMR (for R) - 1.3.0.9008 + 1.3.0.9010 diff --git a/docs/reference/index.html b/docs/reference/index.html index 4d15e24c1..ee58310da 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9009 + 1.3.0.9010 diff --git a/docs/reference/microorganisms.codes.html b/docs/reference/microorganisms.codes.html index 1656464f8..1d5be99c4 100644 --- a/docs/reference/microorganisms.codes.html +++ b/docs/reference/microorganisms.codes.html @@ -82,7 +82,7 @@ AMR (for R) - 1.3.0.9007 + 1.3.0.9010 diff --git a/docs/survey.html b/docs/survey.html index cccb70a9a..cb919ef22 100644 --- a/docs/survey.html +++ b/docs/survey.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9009 + 1.3.0.9010 diff --git a/tests/testthat/test-import_fn.R b/tests/testthat/test-import_fn.R new file mode 100644 index 000000000..ce1fed337 --- /dev/null +++ b/tests/testthat/test-import_fn.R @@ -0,0 +1,47 @@ +# ==================================================================== # +# TITLE # +# Antimicrobial Resistance (AMR) Analysis # +# # +# SOURCE # +# https://github.com/msberends/AMR # +# # +# LICENCE # +# (c) 2018-2020 Berends MS, Luz CF et al. # +# # +# This R package is free software; you can freely use and distribute # +# it for both personal and commercial purposes under the terms of the # +# GNU General Public License version 2.0 (GNU GPL-2), as published by # +# the Free Software Foundation. # +# # +# We created this package for both routine data analysis and academic # +# research and it was publicly released in the hope that it will be # +# useful, but it comes WITHOUT ANY WARRANTY OR LIABILITY. # +# Visit our website for more info: https://msberends.github.io/AMR. # +# ==================================================================== # + +test_that("imports work", { + skip_on_cran() + + import_functions <- c( + cleaner = "freq.default", + curl = "has_internet", + dplyr = "cur_column", + dplyr = "peek_mask", + readxl = "read_excel", + rstudioapi = "showQuestion", + rvest = "html_attr", + rvest = "html_children", + rvest = "html_node", + rvest = "html_nodes", + rvest = "html_table", + rvest = "html_text", + tidyselect = "peek_vars", + xml2 = "read_html") + + for (i in seq_len(length(import_functions))) { + pkg <- names(import_functions)[i] + fn <- unname(import_functions[i]) + expect(!is.null(import_fn(name = fn, pkg = pkg, error_on_fail = FALSE)), + failure_message = paste0("Function ", pkg, "::", fn, "() does not exist")) + } +})