diff --git a/DESCRIPTION b/DESCRIPTION index 361e0a89..01431cae 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 1.5.0.9014 -Date: 2021-02-02 +Version: 1.5.0.9015 +Date: 2021-02-04 Title: Antimicrobial Resistance Data Analysis Authors@R: c( person(role = c("aut", "cre"), diff --git a/NEWS.md b/NEWS.md index 389e5dfc..a66aa7ee 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,5 @@ -# AMR 1.5.0.9014 -## Last updated: 2 February 2021 +# AMR 1.5.0.9015 +## Last updated: 4 February 2021 ### Breaking * Functions that are applied to a data set containing antibiotic columns gained the argument `only_rsi_columns`, which defaults to `TRUE` if any of the columns are of class `` (i.e., transformed with `as.rsi()`). This increases reliability of automatic determination of antibiotic columns (so only columns that are defined to be `` will be affected). @@ -48,8 +48,9 @@ ``` ### Changed -* `is.rsi()` now returns a vector of `TRUE`/`FALSE` when the input is a data set, in case it will iterate over all columns +* `is.rsi()` and `is.rsi.eligible()` now return a vector of `TRUE`/`FALSE` when the input is a data set, by iterating over all columns * Using functions without setting a data set (e.g., `mo_is_gram_negative()`, `mo_is_gram_positive()`, `mo_is_intrinsic_resistant()`, `first_isolate()`, `mdro()`) now work with `dplyr`s `group_by()` again +* `first_isolate()` can be used with `group_by()` (also when using a dot `.` as input for the data) and now returns the names of the groups * Updated the data set `microorganisms.codes` (which contains popular LIS and WHONET codes for microorganisms) for some species of *Mycobacterium* that previously incorrectly returned *M. africanum* * Added Pretomanid (PMD, J04AK08) to the `antibiotics` data set * WHONET code `"PNV"` will now correctly be interpreted as `PHN`, the antibiotic code for phenoxymethylpenicillin ('peni V') diff --git a/R/aa_helper_functions.R b/R/aa_helper_functions.R index e3287c38..9ad53dcd 100755 --- a/R/aa_helper_functions.R +++ b/R/aa_helper_functions.R @@ -85,7 +85,7 @@ check_dataset_integrity <- function() { warning_(ifelse(length(overwritten) == 1, "The following data set is overwritten by your global environment and prevents the AMR package from working correctly: ", "The following data sets are overwritten by your global environment and prevent the AMR package from working correctly: "), - paste0("'", overwritten, "'", collapse = ", "), + vector_and(overwritten, quotes = "'"), ".\nPlease rename your object(s).", call = FALSE) } # check if other packages did not overwrite our data sets @@ -442,29 +442,38 @@ create_ab_documentation <- function(ab) { out } -vector_or <- function(v, quotes = TRUE, reverse = FALSE, last_sep = " or ") { +vector_or <- function(v, quotes = TRUE, reverse = FALSE, sort = TRUE, last_sep = " or ") { # makes unique and sorts, and this also removed NAs - v <- sort(unique(v)) - if (length(v) == 1) { - return(paste0(ifelse(quotes, '"', ""), v, ifelse(quotes, '"', ""))) + v <- unique(v) + if (isTRUE(sort)) { + v <- sort(v) } - if (reverse == TRUE) { + if (isTRUE(reverse)) { v <- rev(v) } - if (identical(v, c("I", "R", "S"))) { - # class should be sorted like this - v <- c("R", "S", "I") - } if (isTRUE(quotes)) { quotes <- '"' } else if (isFALSE(quotes)) { quotes <- "" + } else { + quotes <- quotes[1L] + } + if (length(v) == 1) { + return(paste0(quotes, v, quotes)) + } + if (identical(v, c("I", "R", "S"))) { + # class should be sorted like this + v <- c("R", "S", "I") } # all commas except for last item, so will become '"val1", "val2", "val3" or "val4"' paste0(paste0(quotes, v[seq_len(length(v) - 1)], quotes, collapse = ", "), last_sep, paste0(quotes, v[length(v)], quotes)) } +vector_and <- function(v, quotes = TRUE, reverse = FALSE, sort = TRUE) { + vector_or(v = v, quotes = quotes, reverse = reverse, sort = sort, last_sep = " and ") +} + format_class <- function(class, plural) { class.bak <- class class[class == "numeric"] <- "number" diff --git a/R/ab.R b/R/ab.R index 8c8f617a..4275476b 100755 --- a/R/ab.R +++ b/R/ab.R @@ -134,7 +134,7 @@ as.ab <- function(x, flag_multiple_results = TRUE, info = TRUE, ...) { } if (length(abnames) > 1) { message_("More than one result was found for item ", index, ": ", - paste0(abnames, collapse = ", ")) + vector_and(abnames, quotes = FALSE)) } } found[1L] @@ -454,14 +454,13 @@ as.ab <- function(x, flag_multiple_results = TRUE, info = TRUE, ...) { x_unknown <- x_unknown[!x_unknown %in% x_unknown_ATCs] if (length(x_unknown_ATCs) > 0) { warning_("These ATC codes are not (yet) in the antibiotics data set: ", - paste('"', sort(unique(x_unknown_ATCs)), '"', sep = "", collapse = ", "), - ".", + vector_and(x_unknown_ATCs), ".", call = FALSE) } if (length(x_unknown) > 0 & fast_mode == FALSE) { warning_("These values could not be coerced to a valid antimicrobial ID: ", - paste('"', sort(unique(x_unknown)), '"', sep = "", collapse = ", "), + vector_and(x_unknown), ".", ".", call = FALSE) } diff --git a/R/ab_class_selectors.R b/R/ab_class_selectors.R index aa5e5ee7..e82343dc 100644 --- a/R/ab_class_selectors.R +++ b/R/ab_class_selectors.R @@ -82,13 +82,13 @@ #' } ab_class <- function(ab_class, only_rsi_columns = NULL) { - ab_selector(ab_class, function_name = "ab_class") + ab_selector(ab_class, function_name = "ab_class", only_rsi_columns = only_rsi_columns) } #' @rdname antibiotic_class_selectors #' @export aminoglycosides <- function(only_rsi_columns = NULL) { - ab_selector("aminoglycoside", function_name = "aminoglycosides") + ab_selector("aminoglycoside", function_name = "aminoglycosides", only_rsi_columns = only_rsi_columns) } #' @rdname antibiotic_class_selectors @@ -217,7 +217,7 @@ ab_selector <- function(ab_class, need_name <- tolower(gsub("[^a-zA-Z]", "", agents)) != tolower(gsub("[^a-zA-Z]", "", agents_names)) agents_formatted[need_name] <- paste0(agents_formatted[need_name], " (", agents_names[need_name], ")") - message_("Selecting ", ab_group, ": ", paste(agents_formatted, collapse = ", "), + message_("Selecting ", ab_group, ": ", vector_and(agents_formatted, quotes = FALSE), as_note = FALSE, extra_indent = 4) } diff --git a/R/ab_from_text.R b/R/ab_from_text.R index 236b770f..59decc1a 100644 --- a/R/ab_from_text.R +++ b/R/ab_from_text.R @@ -29,7 +29,7 @@ #' @inheritSection lifecycle Maturing Lifecycle #' @param text text to analyse #' @param type type of property to search for, either `"drug"`, `"dose"` or `"administration"`, see *Examples* -#' @param collapse character to pass on to `paste(..., collapse = ...)` to only return one character per element of `text`, see *Examples* +#' @param collapse character to pass on to `paste(, collapse = ...)` to only return one character per element of `text`, see *Examples* #' @param translate_ab if `type = "drug"`: a column name of the [antibiotics] data set to translate the antibiotic abbreviations to, using [ab_property()]. Defaults to `FALSE`. Using `TRUE` is equal to using "name". #' @param thorough_search logical to indicate whether the input must be extensively searched for misspelling and other faulty input values. Setting this to `TRUE` will take considerably more time than when using `FALSE`. At default, it will turn `TRUE` when all input elements contain a maximum of three words. #' @param ... arguments passed on to [as.ab()] diff --git a/R/ab_property.R b/R/ab_property.R index d7de3d4d..5c201adf 100644 --- a/R/ab_property.R +++ b/R/ab_property.R @@ -225,7 +225,7 @@ ab_url <- function(x, open = FALSE, ...) { NAs <- ab_name(ab, tolower = TRUE, language = NULL)[!is.na(ab) & is.na(ab_atc(ab))] if (length(NAs) > 0) { - warning_("No ATC code available for ", paste0(NAs, collapse = ", "), ".") + warning_("No ATC code available for ", vector_and(NAs, quotes = FALSE), ".") } if (open == TRUE) { diff --git a/R/disk.R b/R/disk.R index a849be0a..895912ff 100644 --- a/R/disk.R +++ b/R/disk.R @@ -98,8 +98,8 @@ as.disk <- function(x, na.rm = FALSE) { if (na_before != na_after) { list_missing <- x.bak[is.na(x) & !is.na(x.bak)] %pm>% unique() %pm>% - sort() - list_missing <- paste0('"', list_missing, '"', collapse = ", ") + sort() %pm>% + vector_and(quotes = TRUE) warning_(na_after - na_before, " results truncated (", round(((na_after - na_before) / length(x)) * 100), "%) that were invalid disk zones: ", diff --git a/R/eucast_rules.R b/R/eucast_rules.R index 569987e9..3660d3c3 100755 --- a/R/eucast_rules.R +++ b/R/eucast_rules.R @@ -57,7 +57,8 @@ format_eucast_version_nr <- function(version, markdown = TRUE) { " (", lst[[v]]$year, ")")) } } - paste0(txt, collapse = ", ") + + vector_and(txt, quotes = FALSE) } #' Apply EUCAST Rules @@ -73,7 +74,7 @@ format_eucast_version_nr <- function(version, markdown = TRUE) { #' @param verbose a [logical] to turn Verbose mode on and off (default is off). In Verbose mode, the function does not apply rules to the data, but instead returns a data set in logbook form with extensive info about which rows and columns would be effected and in which way. Using Verbose mode takes a lot more time. #' @param version_breakpoints the version number to use for the EUCAST Clinical Breakpoints guideline. Can be either `r vector_or(names(EUCAST_VERSION_BREAKPOINTS), reverse = TRUE)`. #' @param version_expertrules the version number to use for the EUCAST Expert Rules and Intrinsic Resistance guideline. Can be either `r vector_or(names(EUCAST_VERSION_EXPERT_RULES), reverse = TRUE)`. -#' @param ampc_cephalosporin_resistance a character value that should be applied for AmpC de-repressed cephalosporin-resistant mutants, defaults to `NA`. Currently only works when `version_expertrules` is `3.2`; '*EUCAST Expert Rules v3.2 on Enterobacterales*' states that results of cefotaxime, ceftriaxone and ceftazidime should be reported with a note, or results should be suppressed (emptied) for these agents. A value of `NA` for this argument will remove results for these agents, while e.g. a value of `"R"` will make the results for these agents resistant. Use `NULL` to not alter the results for AmpC de-repressed cephalosporin-resistant mutants. \cr For *EUCAST Expert Rules* v3.2, this rule applies to: `r vector_or(gsub("[^a-zA-Z ]+", "", unlist(strsplit(eucast_rules_file[which(eucast_rules_file$reference.version == 3.2 & eucast_rules_file$reference.rule %like% "ampc"), "this_value"][1], "|", fixed = TRUE))), quotes = "*", last_sep = " and ")`. +#' @param ampc_cephalosporin_resistance a character value that should be applied for AmpC de-repressed cephalosporin-resistant mutants, defaults to `NA`. Currently only works when `version_expertrules` is `3.2`; '*EUCAST Expert Rules v3.2 on Enterobacterales*' states that results of cefotaxime, ceftriaxone and ceftazidime should be reported with a note, or results should be suppressed (emptied) for these agents. A value of `NA` for this argument will remove results for these agents, while e.g. a value of `"R"` will make the results for these agents resistant. Use `NULL` to not alter the results for AmpC de-repressed cephalosporin-resistant mutants. \cr For *EUCAST Expert Rules* v3.2, this rule applies to: `r vector_and(gsub("[^a-zA-Z ]+", "", unlist(strsplit(eucast_rules_file[which(eucast_rules_file$reference.version == 3.2 & eucast_rules_file$reference.rule %like% "ampc"), "this_value"][1], "|", fixed = TRUE))), quotes = "*")`. #' @param ... column name of an antibiotic, see section *Antibiotics* below #' @param ab any (vector of) text that can be coerced to a valid antibiotic code with [as.ab()] #' @param administration route of administration, either `r vector_or(dosage$administration)` @@ -282,6 +283,16 @@ eucast_rules <- function(x, only_rsi_columns = only_rsi_columns, ...) + + if (only_rsi_columns == TRUE && !paste0(sys.calls()[1], collapse = "") %like% "only_rsi_columns") { + cols_rsi_eligible <- colnames(x[, is.rsi.eligible(x), drop = FALSE]) + if (length(cols_rsi_eligible) > 0) { + message_("These columns might be eligible for EUCAST rules, but are ignored since `only_rsi_columns` is `TRUE`: ", + vector_and(cols_rsi_eligible, quotes = TRUE, sort = FALSE), + as_note = TRUE, add_fn = font_red) + } + } + AMC <- cols_ab["AMC"] AMK <- cols_ab["AMK"] AMP <- cols_ab["AMP"] @@ -737,12 +748,8 @@ eucast_rules <- function(x, } else { if (info == TRUE) { - message_("\n\nSkipping inheritance rules defined by this package, such as setting trimethoprim (TMP) = R where trimethoprim/sulfamethoxazole (SXT) = R.", - as_note = FALSE, - add_fn = font_red) - message_("Use eucast_rules(..., rules = \"all\") to also apply those rules.", - as_note = FALSE, - add_fn = font_red) + cat("\n") + message_("Skipping inheritance rules defined by this package, such as setting trimethoprim (TMP) = R where trimethoprim/sulfamethoxazole (SXT) = R. Use `eucast_rules(..., rules = \"all\")` to also apply those rules.") } } diff --git a/R/first_isolate.R b/R/first_isolate.R index 072af442..d266e623 100755 --- a/R/first_isolate.R +++ b/R/first_isolate.R @@ -100,24 +100,27 @@ #' # See ?example_isolates. #' #' # basic filtering on first isolates -#' example_isolates[first_isolate(example_isolates), ] +#' example_isolates[first_isolate(), ] #' -#' # filtering based on isolates ---------------------------------------------- #' \donttest{ +#' # get all first Gram-negatives +#' example_isolates[which(first_isolate() & mo_is_gram_negative()), ] +#' #' if (require("dplyr")) { -#' # filter on first isolates: +#' # filter on first isolates using dplyr: #' example_isolates %>% -#' mutate(first_isolate = first_isolate(.)) %>% -#' filter(first_isolate == TRUE) +#' filter(first_isolate()) #' #' # short-hand versions: #' example_isolates %>% -#' filter(first_isolate()) -#' example_isolates %>% #' filter_first_isolate() -#' #' example_isolates %>% #' filter_first_weighted_isolate() +#' +#' # grouped determination of first isolates (also prints group names): +#' example_isolates %>% +#' group_by(hospital_id) %>% +#' mutate(first = first_isolate()) #' #' # now let's see if first isolates matter: #' A <- example_isolates %>% @@ -194,6 +197,14 @@ first_isolate <- function(x, } } + # fix for using a grouped df as input (a dot as first argument) + # such as example_isolates %>% group_by(hospital_id) %>% mutate(first_isolate = first_isolate(.)) + if (inherits(x, "grouped_df")) { + # get_current_data() contains dplyr::cur_data_all() + x <- tryCatch(get_current_data(arg_name = "x", 0), + error = function(e) x) + } + # remove data.table, grouping from tibbles, etc. x <- as.data.frame(x, stringsAsFactors = FALSE) @@ -427,12 +438,33 @@ first_isolate <- function(x, decimal.mark <- getOption("OutDec") big.mark <- ifelse(decimal.mark != ",", ",", ".") + if (info == TRUE) { + # print group name if used in dplyr::group_by() + cur_group <- import_fn("cur_group", "dplyr", error_on_fail = FALSE) + if (!is.null(cur_group)) { + group_df <- tryCatch(cur_group(), error = function(e) data.frame()) + if (NCOL(group_df) > 0) { + # transform factors to characters + group <- vapply(FUN.VALUE = character(1), group_df, function(x) { + if (is.numeric(x)) { + format(x) + } else if (is.logical(x)) { + as.character(x) + } else { + paste0('"', x, '"') + } + }) + cat("\nGroup: ", paste0(names(group), " = ", group, collapse = ", "), "\n", sep = "") + } + } + } + # handle empty microorganisms if (any(x$newvar_mo == "UNKNOWN", na.rm = TRUE) & info == TRUE) { message_(ifelse(include_unknown == TRUE, "Included ", "Excluded "), format(sum(x$newvar_mo == "UNKNOWN", na.rm = TRUE), decimal.mark = decimal.mark, big.mark = big.mark), - " isolates with a microbial ID 'UNKNOWN' (column '", font_bold(col_mo), "')") + " isolates with a microbial ID 'UNKNOWN' (in column '", font_bold(col_mo), "')") } x[which(x$newvar_mo == "UNKNOWN"), "newvar_first_isolate"] <- include_unknown @@ -440,7 +472,7 @@ first_isolate <- function(x, if (any(is.na(x$newvar_mo)) & info == TRUE) { message_("Excluded ", format(sum(is.na(x$newvar_mo), na.rm = TRUE), decimal.mark = decimal.mark, big.mark = big.mark), - " isolates with a microbial ID 'NA' (column '", font_bold(col_mo), "')") + " isolates with a microbial ID 'NA' (in column '", font_bold(col_mo), "')") } x[which(is.na(x$newvar_mo)), "newvar_first_isolate"] <- FALSE diff --git a/R/guess_ab_col.R b/R/guess_ab_col.R index a804532f..d995706b 100755 --- a/R/guess_ab_col.R +++ b/R/guess_ab_col.R @@ -67,6 +67,7 @@ guess_ab_col <- function(x = NULL, search_string = NULL, verbose = FALSE, only_r meet_criteria(x, allow_class = "data.frame", allow_NULL = TRUE) meet_criteria(search_string, allow_class = "character", has_length = 1, allow_NULL = TRUE) meet_criteria(verbose, allow_class = "logical", has_length = 1) + meet_criteria(only_rsi_columns, allow_class = "logical", has_length = 1) if (is.null(x) & is.null(search_string)) { return(as.name("guess_ab_col")) @@ -225,9 +226,9 @@ get_column_abx <- function(x, if (info == TRUE & !all(soft_dependencies %in% names(x))) { # missing a soft dependency may lower the reliability missing <- soft_dependencies[!soft_dependencies %in% names(x)] - missing_msg <- paste(paste0(ab_name(missing, tolower = TRUE, language = NULL), - " (", font_bold(missing, collapse = NULL), ")"), - collapse = ", ") + missing_msg <- vector_and(paste0(ab_name(missing, tolower = TRUE, language = NULL), + " (", font_bold(missing, collapse = NULL), ")"), + quotes = FALSE) message_("Reliability would be improved if these antimicrobial results would be available too: ", missing_msg) } @@ -243,7 +244,7 @@ generate_warning_abs_missing <- function(missing, any = FALSE) { any_txt <- c("", "are") } warning_(paste0("Introducing NAs since", any_txt[1], " these antimicrobials ", any_txt[2], " required: ", - paste(missing, collapse = ", ")), + vector_and(missing, quotes = FALSE)), immediate = TRUE, call = FALSE) } diff --git a/R/mdro.R b/R/mdro.R index 1b89bd6e..600e1411 100755 --- a/R/mdro.R +++ b/R/mdro.R @@ -497,6 +497,15 @@ mdro <- function(x, ...) } + if (only_rsi_columns == TRUE) { + cols_rsi_eligible <- colnames(x[, is.rsi.eligible(x), drop = FALSE]) + if (length(cols_rsi_eligible) > 0) { + message_("These columns might be eligible for determining ", guideline$type, ", but are ignored since `only_rsi_columns` is `TRUE`: ", + vector_and(cols_rsi_eligible, quotes = TRUE, sort = FALSE), + as_note = TRUE, add_fn = font_red) + } + } + # nolint start AMC <- cols_ab["AMC"] AMK <- cols_ab["AMK"] diff --git a/R/mic.R b/R/mic.R index b6424a01..318f5959 100755 --- a/R/mic.R +++ b/R/mic.R @@ -123,8 +123,8 @@ as.mic <- function(x, na.rm = FALSE) { if (na_before != na_after) { list_missing <- x.bak[is.na(x) & !is.na(x.bak) & x.bak != ""] %pm>% unique() %pm>% - sort() - list_missing <- paste0('"', list_missing, '"', collapse = ", ") + sort() %pm>% + vector_and(quotes = TRUE) warning_(na_after - na_before, " results truncated (", round(((na_after - na_before) / length(x)) * 100), "%) that were invalid MICs: ", diff --git a/R/mo.R b/R/mo.R index 470db247..847254af 100755 --- a/R/mo.R +++ b/R/mo.R @@ -1418,7 +1418,7 @@ exec_as.mo <- function(x, " (covering ", percentage(total_failures / total_n), ") could not be coerced and ", plural[3], " considered 'unknown'") if (pm_n_distinct(failures) <= 10) { - msg <- paste0(msg, ": ", paste('"', unique(failures), '"', sep = "", collapse = ", ")) + msg <- paste0(msg, ": ", vector_and(failures, quotes = TRUE)) } msg <- paste0(msg, ".\nUse mo_failures() to review ", plural[2], ". Edit the `allow_uncertain` argument if needed (see ?as.mo).\n", @@ -1450,7 +1450,7 @@ exec_as.mo <- function(x, # - Becker et al. 2014, PMID 25278577 # - Becker et al. 2019, PMID 30872103 # - Becker et al. 2020, PMID 32056452 - post_Becker <- character(0) # 2020-10-20 currently all are mentioned in above papers (otherwise uncomment below) + post_Becker <- character(0) # 2020-10-20 currently all are mentioned in above papers (otherwise uncomment the section below) # nolint start # if (any(x %in% MO_lookup[which(MO_lookup$species %in% post_Becker), property])) { @@ -1796,7 +1796,6 @@ print.mo_uncertainties <- function(x, ...) { return(NULL) } message_("Matching scores are based on human pathogenic prevalence and the resemblance between the input and the full taxonomic name. See ?mo_matching_score.", as_note = FALSE) - cat("\n") msg <- "" for (i in seq_len(nrow(x))) { @@ -1807,7 +1806,7 @@ print.mo_uncertainties <- function(x, ...) { candidates <- candidates[order(1 - scores)] scores_formatted <- trimws(formatC(round(scores, 3), format = "f", digits = 3)) n_candidates <- length(candidates) - candidates <- paste0(candidates, " (", scores_formatted[order(1 - scores)], ")", collapse = ", ") + candidates <- vector_and(paste0(candidates, " (", scores_formatted[order(1 - scores)], ")"), quotes = FALSE) # align with input after arrow candidates <- paste0("\n", strwrap(paste0("Also matched", @@ -1987,9 +1986,8 @@ replace_ignore_pattern <- function(x, ignore_pattern) { ignore_cases <- x %like% ignore_pattern if (sum(ignore_cases) > 0) { message_("The following input was ignored by `ignore_pattern = \"", ignore_pattern, "\"`: ", - paste0("'", sort(unique(x[x %like% ignore_pattern])), "'", collapse = ", "), - collapse = ", ") - x[x %like% ignore_pattern] <- NA_character_ + vector_and(x[ignore_cases], quotes = TRUE)) + x[ignore_cases] <- NA_character_ } } x diff --git a/R/mo_property.R b/R/mo_property.R index ab4c9ba5..1a08e56d 100755 --- a/R/mo_property.R +++ b/R/mo_property.R @@ -28,7 +28,7 @@ #' Use these functions to return a specific property of a microorganism based on the latest accepted taxonomy. All input values will be evaluated internally with [as.mo()], which makes it possible to use microbial abbreviations, codes and names as input. See *Examples*. #' @inheritSection lifecycle Stable Lifecycle #' @param x any character (vector) that can be coerced to a valid microorganism code with [as.mo()]. Can be left blank for auto-guessing the column containing microorganism codes if used in a data set, see *Examples*. -#' @param property one of the column names of the [microorganisms] data set: `r paste0('"``', colnames(microorganisms), '\``"', collapse = ", ")`, or must be `"shortname"` +#' @param property one of the column names of the [microorganisms] data set: `r vector_or(colnames(microorganisms), sort = FALSE, quotes = TRUE)`, or must be `"shortname"` #' @param language language of the returned text, defaults to system language (see [get_locale()]) and can be overwritten by setting the option `AMR_locale`, e.g. `options(AMR_locale = "de")`, see [translate]. Also used to translate text like "no growth". Use `language = NULL` or `language = ""` to prevent translation. #' @param ... other arguments passed on to [as.mo()], such as 'allow_uncertain' and 'ignore_pattern' #' @param ab any (vector of) text that can be coerced to a valid antibiotic code with [as.ab()] diff --git a/R/mo_source.R b/R/mo_source.R index 183338db..afc17655 100644 --- a/R/mo_source.R +++ b/R/mo_source.R @@ -283,9 +283,9 @@ check_validity_mo_source <- function(x, refer_to_name = "`reference_df`", stop_o } else { plural <- "" } - stop_("Value", plural, " ", paste0("'", invalid[, 1, drop = TRUE], "'", collapse = ", "), + stop_("Value", plural, " ", vector_and(invalid[, 1, drop = TRUE], quotes = TRUE), " found in ", tolower(refer_to_name), - ", but with invalid microorganism code", plural, " ", paste0("'", invalid$mo, "'", collapse = ", "), + ", but with invalid microorganism code", plural, " ", vector_and(invalid$mo, quotes = TRUE), call = FALSE) } else { return(FALSE) diff --git a/R/pca.R b/R/pca.R index be185d8f..5a06a132 100755 --- a/R/pca.R +++ b/R/pca.R @@ -117,9 +117,7 @@ pca <- function(x, pca_data <- x[, which(vapply(FUN.VALUE = logical(1), x, function(x) is.numeric(x)))] - message_("Columns selected for PCA: ", vector_or(font_bold(colnames(pca_data), collapse = NULL), - quotes = "'", - last_sep = " and "), + message_("Columns selected for PCA: ", vector_and(font_bold(colnames(pca_data), collapse = NULL), quotes = TRUE), ". Total observations available: ", nrow(pca_data), ".") if (as.double(R.Version()$major) + (as.double(R.Version()$minor) / 10) < 3.4) { diff --git a/R/rsi.R b/R/rsi.R index 7957f643..4922301f 100755 --- a/R/rsi.R +++ b/R/rsi.R @@ -65,7 +65,7 @@ #' #' ## Supported Guidelines #' -#' For interpreting MIC values as well as disk diffusion diameters, supported guidelines to be used as input for the `guideline` argument are: `r paste0('"', sort(unique(AMR::rsi_translation$guideline)), '"', collapse = ", ")`. +#' For interpreting MIC values as well as disk diffusion diameters, supported guidelines to be used as input for the `guideline` argument are: `r vector_and(AMR::rsi_translation$guideline, quotes = TRUE, reverse = TRUE)`. #' #' Simply using `"CLSI"` or `"EUCAST"` as input will automatically select the latest version of that guideline. You can set your own data set using the `reference_data` argument. The `guideline` argument will then be ignored. #' @@ -79,9 +79,9 @@ #' #' ## Other #' -#' The function [is.rsi()] detects if the input contains class ``. If the input is a data.frame, it returns a vector in which all columns are checked for this class. +#' The function [is.rsi()] detects if the input contains class ``. If the input is a data.frame, it iterates over all columns and returns a logical vector. #' -#' The function [is.rsi.eligible()] returns `TRUE` when a columns contains at most 5% invalid antimicrobial interpretations (not S and/or I and/or R), and `FALSE` otherwise. The threshold of 5% can be set with the `threshold` argument. +#' The function [is.rsi.eligible()] returns `TRUE` when a columns contains at most 5% invalid antimicrobial interpretations (not S and/or I and/or R), and `FALSE` otherwise. The threshold of 5% can be set with the `threshold` argument. If the input is a data.frame, it iterates over all columns and returns a logical vector. #' @section Interpretation of R and S/I: #' In 2019, the European Committee on Antimicrobial Susceptibility Testing (EUCAST) has decided to change the definitions of susceptibility testing categories R and S/I as shown below (). #' @@ -203,6 +203,10 @@ is.rsi <- function(x) { is.rsi.eligible <- function(x, threshold = 0.05) { meet_criteria(threshold, allow_class = "numeric", has_length = 1) + if (inherits(x, "data.frame")) { + return(unname(vapply(FUN.VALUE = logical(1), x, is.rsi.eligible))) + } + stop_if(NCOL(x) > 1, "`x` must be a one-dimensional vector.") if (any(c("numeric", "integer", @@ -294,8 +298,8 @@ as.rsi.default <- function(x, ...) { if (na_before != na_after) { list_missing <- x.bak[is.na(x) & !is.na(x.bak) & x.bak != ""] %pm>% unique() %pm>% - sort() - list_missing <- paste0('"', list_missing, '"', collapse = ", ") + sort() %pm>% + vector_and(quotes = TRUE) warning_(na_after - na_before, " results truncated (", round(((na_after - na_before) / length(x)) * 100), "%) that were invalid antimicrobial interpretations: ", @@ -551,7 +555,7 @@ as.rsi.data.frame <- function(x, plural <- c("", "s", "a ") } message_("Assuming value", plural[1], " ", - paste(paste0('"', values, '"'), collapse = ", "), + vector_and(values, quotes = TRUE), " in column '", font_bold(col_specimen), "' reflect", plural[2], " ", plural[3], "urinary tract infection", plural[1], ".\n Use `as.rsi(uti = FALSE)` to prevent this.") @@ -682,10 +686,9 @@ get_guideline <- function(guideline, reference_data) { stop_ifnot(guideline_param %in% reference_data$guideline, "invalid guideline: '", guideline, - "'.\nValid guidelines are: ", paste0("'", unique(reference_data$guideline), "'", collapse = ", "), call = FALSE) + "'.\nValid guidelines are: ", vector_and(reference_data$guideline, quotes = TRUE, reverse = TRUE), call = FALSE) guideline_param - } exec_as.rsi <- function(method, diff --git a/R/rsi_calc.R b/R/rsi_calc.R index 9551cb63..5e0c81e3 100755 --- a/R/rsi_calc.R +++ b/R/rsi_calc.R @@ -27,7 +27,7 @@ dots2vars <- function(...) { # this function is to give more informative output about # variable names in count_* and proportion_* functions dots <- substitute(list(...)) - paste(as.character(dots)[2:length(dots)], collapse = ", ") + vector_and(as.character(dots)[2:length(dots)], quotes = FALSE) } rsi_calc <- function(..., @@ -78,7 +78,7 @@ rsi_calc <- function(..., dots <- c(dots[dots %in% colnames(dots_df)], eval(parse(text = dots[!dots %in% colnames(dots_df)]), envir = dots_df, enclos = globalenv())) dots_not_exist <- dots[!dots %in% colnames(dots_df)] - stop_if(length(dots_not_exist) > 0, "column(s) not found: ", paste0("'", dots_not_exist, "'", collapse = ", "), call = -2) + stop_if(length(dots_not_exist) > 0, "column(s) not found: ", vector_and(dots_not_exist, quotes = TRUE), call = -2) x <- dots_df[, dots, drop = FALSE] } } else if (ndots == 1) { diff --git a/R/translate.R b/R/translate.R index 77657278..2ad6b02f 100755 --- a/R/translate.R +++ b/R/translate.R @@ -29,7 +29,7 @@ #' @inheritSection lifecycle Stable Lifecycle #' @details Strings will be translated to foreign languages if they are defined in a local translation file. Additions to this file can be suggested at our repository. The file can be found here: . This file will be read by all functions where a translated output can be desired, like all [`mo_*`][mo_property()] functions (such as [mo_name()], [mo_gramstain()], [mo_type()], etc.) and [`ab_*`][ab_property()] functions (such as [ab_name()], [ab_group()], etc.). #' -#' Currently supported languages are: `r paste(sort(gsub(";.*", "", ISOcodes::ISO_639_2[which(ISOcodes::ISO_639_2$Alpha_2 %in% LANGUAGES_SUPPORTED), "Name"])), collapse = ", ")`. Please note that currently not all these languages have translations available for all antimicrobial agents and colloquial microorganism names. +#' Currently supported languages are: `r vector_and(gsub(";.*", "", ISOcodes::ISO_639_2[which(ISOcodes::ISO_639_2$Alpha_2 %in% LANGUAGES_SUPPORTED), "Name"]), quotes = FALSE)`. Please note that currently not all these languages have translations available for all antimicrobial agents and colloquial microorganism names. #' #' Please suggest your own translations [by creating a new issue on our repository](https://github.com/msberends/AMR/issues/new?title=Translations). #' @@ -83,8 +83,8 @@ get_locale <- function() { if (lang %in% LANGUAGES_SUPPORTED) { return(lang) } else { - stop_("unsupported language set as option 'AMR_locale': '", lang, "' - use one of: ", - paste0("'", LANGUAGES_SUPPORTED, "'", collapse = ", ")) + stop_("unsupported language set as option 'AMR_locale': \"", lang, "\" - use either ", + vector_or(LANGUAGES_SUPPORTED, quotes = TRUE)) } } else { # we now support the LANGUAGE system variable - return it if set @@ -138,8 +138,8 @@ translate_AMR <- function(from, language = get_locale(), only_unknown = FALSE) { from_unique_translated <- from_unique stop_ifnot(language %in% LANGUAGES_SUPPORTED, - "unsupported language: '", language, "' - use one of: ", - paste0("'", LANGUAGES_SUPPORTED, "'", collapse = ", "), + "unsupported language: \"", language, "\" - use either ", + vector_or(LANGUAGES_SUPPORTED, quotes = TRUE), call = FALSE) df_trans <- subset(df_trans, lang == language) diff --git a/data-raw/AMR_1.5.0.9014.tar.gz b/data-raw/AMR_1.5.0.9015.tar.gz similarity index 86% rename from data-raw/AMR_1.5.0.9014.tar.gz rename to data-raw/AMR_1.5.0.9015.tar.gz index 55cd27c8..0ee172a0 100644 Binary files a/data-raw/AMR_1.5.0.9014.tar.gz and b/data-raw/AMR_1.5.0.9015.tar.gz differ diff --git a/docs/404.html b/docs/404.html index a100be89..47317f00 100644 --- a/docs/404.html +++ b/docs/404.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9014 + 1.5.0.9015 diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index e08b08e7..45c14a42 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9014 + 1.5.0.9015 diff --git a/docs/articles/datasets.html b/docs/articles/datasets.html index ed3a0aec..c89747eb 100644 --- a/docs/articles/datasets.html +++ b/docs/articles/datasets.html @@ -39,7 +39,7 @@ AMR (for R) - 1.5.0.9008 + 1.5.0.9015 @@ -208,7 +208,7 @@ If you are reading this page from within R, please

Microorganisms (currently accepted names)

-

A data set with 67,151 rows and 16 columns, containing the following column names:
‘mo’, ‘fullname’, ‘kingdom’, ‘phylum’, ‘class’, ‘order’, ‘family’, ‘genus’, ‘species’, ‘subspecies’, ‘rank’, ‘ref’, ‘species_id’, ‘source’, ‘prevalence’, ‘snomed’.

+

A data set with 67,151 rows and 16 columns, containing the following column names:
class, family, fullname, genus, kingdom, mo, order, phylum, prevalence, rank, ref, snomed, source, species, species_id and subspecies.

This data set is in R available as microorganisms, after you load the AMR package.

It was last updated on 3 September 2020 20:59:45 CEST. Find more info about the structure of this data set here.

Direct download links:

@@ -426,7 +426,7 @@ If you are reading this page from within R, please

Microorganisms (previously accepted names)

-

A data set with 12,708 rows and 4 columns, containing the following column names:
‘fullname’, ‘fullname_new’, ‘ref’, ‘prevalence’.

+

A data set with 12,708 rows and 4 columns, containing the following column names:
fullname, fullname_new, prevalence and ref.

Note: remember that the ‘ref’ columns contains the scientific reference to the old taxonomic entries, i.e. of column ‘fullname’. For the scientific reference of the new names, i.e. of column ‘fullname_new’, see the microorganisms data set.

This data set is in R available as microorganisms.old, after you load the AMR package.

It was last updated on 28 May 2020 11:17:56 CEST. Find more info about the structure of this data set here.

@@ -492,7 +492,7 @@ If you are reading this page from within R, please

Antibiotic agents

-

A data set with 456 rows and 14 columns, containing the following column names:
‘ab’, ‘atc’, ‘cid’, ‘name’, ‘group’, ‘atc_group1’, ‘atc_group2’, ‘abbreviations’, ‘synonyms’, ‘oral_ddd’, ‘oral_units’, ‘iv_ddd’, ‘iv_units’, ‘loinc’.

+

A data set with 456 rows and 14 columns, containing the following column names:
ab, abbreviations, atc, atc_group1, atc_group2, cid, group, iv_ddd, iv_units, loinc, name, oral_ddd, oral_units and synonyms.

This data set is in R available as antibiotics, after you load the AMR package.

It was last updated on 14 January 2021 16:04:41 CET. Find more info about the structure of this data set here.

Direct download links:

@@ -515,7 +515,7 @@ If you are reading this page from within R, please ATC/DDD index from WHO Collaborating Centre for Drug Statistics Methodology (note: this may not be used for commercial purposes, but is frelly available from the WHO CC website for personal use) +ATC/DDD index from WHO Collaborating Centre for Drug Statistics Methodology (note: this may not be used for commercial purposes, but is freely available from the WHO CC website for personal use)
  • PubChem by the US National Library of Medicine
  • WHONET software 2019
  • @@ -660,7 +660,7 @@ If you are reading this page from within R, please

    Antiviral agents

    -

    A data set with 102 rows and 9 columns, containing the following column names:
    ‘atc’, ‘cid’, ‘name’, ‘atc_group’, ‘synonyms’, ‘oral_ddd’, ‘oral_units’, ‘iv_ddd’, ‘iv_units’.

    +

    A data set with 102 rows and 9 columns, containing the following column names:
    atc, atc_group, cid, iv_ddd, iv_units, name, oral_ddd, oral_units and synonyms.

    This data set is in R available as antivirals, after you load the AMR package.

    It was last updated on 29 August 2020 21:53:07 CEST. Find more info about the structure of this data set here.

    Direct download links:

    @@ -683,7 +683,7 @@ If you are reading this page from within R, please ATC/DDD index from WHO Collaborating Centre for Drug Statistics Methodology (note: this may not be used for commercial purposes, but is frelly available from the WHO CC website for personal use) +ATC/DDD index from WHO Collaborating Centre for Drug Statistics Methodology (note: this may not be used for commercial purposes, but is freely available from the WHO CC website for personal use)
  • PubChem by the US National Library of Medicine
  • @@ -787,7 +787,7 @@ If you are reading this page from within R, please

    Intrinsic bacterial resistance

    -

    A data set with 93,892 rows and 2 columns, containing the following column names:
    ‘microorganism’, ‘antibiotic’.

    +

    A data set with 93,892 rows and 2 columns, containing the following column names:
    antibiotic and microorganism.

    This data set is in R available as intrinsic_resistant, after you load the AMR package.

    It was last updated on 24 September 2020 00:50:35 CEST. Find more info about the structure of this data set here.

    Direct download links:

    @@ -807,7 +807,7 @@ If you are reading this page from within R, please

    Source

    -

    This data set contains all defined intrinsic resistance by EUCAST of all bug-drug combinations, and is based on ‘’EUCAST Expert Rules’ and ‘EUCAST Intrinsic Resistance and Unusual Phenotypes’’, v3.2 from 2020.

    +

    This data set contains all defined intrinsic resistance by EUCAST of all bug-drug combinations, and is based on ‘EUCAST Expert Rules’ and ‘EUCAST Intrinsic Resistance and Unusual Phenotypes’ v3.2 (2020).

    @@ -1002,7 +1002,7 @@ If you are reading this page from within R, please

    Interpretation from MIC values / disk diameters to R/SI

    -

    A data set with 20,486 rows and 10 columns, containing the following column names:
    ‘guideline’, ‘method’, ‘site’, ‘mo’, ‘ab’, ‘ref_tbl’, ‘disk_dose’, ‘breakpoint_S’, ‘breakpoint_R’, ‘uti’.

    +

    A data set with 20,486 rows and 10 columns, containing the following column names:
    ab, breakpoint_R, breakpoint_S, disk_dose, guideline, method, mo, ref_tbl, site and uti.

    This data set is in R available as rsi_translation, after you load the AMR package.

    It was last updated on 14 January 2021 16:04:41 CET. Find more info about the structure of this data set here.

    Direct download links:

    @@ -1132,22 +1132,22 @@ If you are reading this page from within R, please

    Dosage guidelines from EUCAST

    -

    A data set with 135 rows and 9 columns, containing the following column names:
    ‘ab’, ‘name’, ‘type’, ‘dose’, ‘dose_times’, ‘administration’, ‘notes’, ‘original_txt’, ‘eucast_version’.

    +

    A data set with 169 rows and 9 columns, containing the following column names:
    ab, administration, dose, dose_times, eucast_version, name, notes, original_txt and type.

    This data set is in R available as dosage, after you load the AMR package.

    -

    It was last updated on 14 January 2021 16:04:41 CET. Find more info about the structure of this data set here.

    +

    It was last updated on 25 January 2021 21:58:20 CET. Find more info about the structure of this data set here.

    Direct download links:

    diff --git a/docs/articles/index.html b/docs/articles/index.html index c9709aef..72636d25 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9014 + 1.5.0.9015

    diff --git a/docs/authors.html b/docs/authors.html index d210832f..9dd8acb9 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9014 + 1.5.0.9015

    diff --git a/docs/index.html b/docs/index.html index bb1904d2..b2d3b2e1 100644 --- a/docs/index.html +++ b/docs/index.html @@ -43,7 +43,7 @@ AMR (for R) - 1.5.0.9014 + 1.5.0.9015 diff --git a/docs/news/index.html b/docs/news/index.html index cfcd19f4..4e350e63 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9014 + 1.5.0.9015 @@ -236,13 +236,13 @@ Source: NEWS.md -
    -

    -AMR 1.5.0.9014 Unreleased +
    +

    +AMR 1.5.0.9015 Unreleased

    -
    +

    -Last updated: 2 February 2021 +Last updated: 4 February 2021

    @@ -306,8 +306,10 @@ Changed

    • -is.rsi() now returns a vector of TRUE/FALSE when the input is a data set, in case it will iterate over all columns
    • +is.rsi() and is.rsi.eligible() now return a vector of TRUE/FALSE when the input is a data set, by iterating over all columns
    • Using functions without setting a data set (e.g., mo_is_gram_negative(), mo_is_gram_positive(), mo_is_intrinsic_resistant(), first_isolate(), mdro()) now work with dplyrs group_by() again
    • +
    • +first_isolate() can be used with group_by() (also when using a dot . as input for the data) and now returns the names of the groups
    • Updated the data set microorganisms.codes (which contains popular LIS and WHONET codes for microorganisms) for some species of Mycobacterium that previously incorrectly returned M. africanum
    • Added Pretomanid (PMD, J04AK08) to the antibiotics data set
    • @@ -648,7 +650,7 @@

      Making this package independent of especially the tidyverse (e.g. packages dplyr and tidyr) tremendously increases sustainability on the long term, since tidyverse functions change quite often. Good for users, but hard for package maintainers. Most of our functions are replaced with versions that only rely on base R, which keeps this package fully functional for many years to come, without requiring a lot of maintenance to keep up with other packages anymore. Another upside it that this package can now be used with all versions of R since R-3.0.0 (April 2013). Our package is being used in settings where the resources are very limited. Fewer dependencies on newer software is helpful for such settings.

      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().
      • +
      • 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.
      • 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.
      • @@ -985,7 +987,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ #> invalid microorganism code, NA generated

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

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

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

  • Renamed data set septic_patients to example_isolates

  • @@ -1254,7 +1256,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
  • The age() function gained a new argument exact to determine ages with decimals
  • Removed deprecated functions guess_mo(), guess_atc(), EUCAST_rules(), interpretive_reading(), rsi()
  • -
  • Frequency tables (freq()): +
  • Frequency tables (freq()):
    • speed improvement for microbial IDs

    • fixed factor level names for R Markdown

    • @@ -1264,12 +1266,12 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
       
       septic_patients %>% 
      -  freq(age) %>% 
      +  freq(age) %>% 
         boxplot()
       # grouped boxplots:
       septic_patients %>% 
         group_by(hospital_id) %>% 
      -  freq(age) %>%
      +  freq(age) %>%
         boxplot()
    @@ -1279,7 +1281,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
  • Added ceftazidim intrinsic resistance to Streptococci
  • Changed default settings for age_groups(), to let groups of fives and tens end with 100+ instead of 120+
  • -
  • Fix for freq() for when all values are NA +
  • Fix for freq() for when all values are NA
  • Fix for first_isolate() for when dates are missing
  • Improved speed of guess_ab_col() @@ -1520,7 +1522,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
  • -
  • Frequency tables (freq() function): +
  • Frequency tables (freq() function):
    • Support for tidyverse quasiquotation! Now you can create frequency tables of function outcomes:

      @@ -1530,15 +1532,15 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ # OLD WAY septic_patients %>% mutate(genus = mo_genus(mo)) %>% - freq(genus) + freq(genus) # NEW WAY septic_patients %>% - freq(mo_genus(mo)) + freq(mo_genus(mo)) # Even supports grouping variables: septic_patients %>% group_by(gender) %>% - freq(mo_genus(mo))
  • + freq(mo_genus(mo))
  • Header info is now available as a list, with the header function

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

  • @@ -1621,7 +1623,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
  • Using portion_* functions now throws a warning when total available isolate is below argument minimum

  • Functions as.mo, as.rsi, as.mic, as.atc and freq will not set package name as attribute anymore

  • -

    Frequency tables - freq():

    +

    Frequency tables - freq():

    • Support for grouping variables, test with:

      @@ -1629,14 +1631,14 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ septic_patients %>% group_by(hospital_id) %>% - freq(gender)
  • + freq(gender)
  • Support for (un)selecting columns:

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

  • @@ -1654,7 +1656,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
  • Removed diacritics from all authors (columns microorganisms$ref and microorganisms.old$ref) to comply with CRAN policy to only allow ASCII characters

  • Fix for mo_property not working properly

  • Fix for eucast_rules where some Streptococci would become ceftazidime R in EUCAST rule 4.5

  • -
  • Support for named vectors of class mo, useful for top_freq()

  • +
  • Support for named vectors of class mo, useful for top_freq()

  • ggplot_rsi and scale_y_percent have breaks argument

  • AI improvements for as.mo:

    @@ -1822,13 +1824,13 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
     
     my_matrix = with(septic_patients, matrix(c(age, gender), ncol = 2))
    -freq(my_matrix)
    +freq(my_matrix)

    For lists, subsetting is possible:

     
     my_list = list(age = septic_patients$age, gender = septic_patients$gender)
    -my_list %>% freq(age)
    -my_list %>% freq(gender)
    +my_list %>% freq(age) +my_list %>% freq(gender)
  • @@ -1902,13 +1904,13 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
    • A vignette to explain its usage
    • Support for rsi (antimicrobial resistance) to use as input
    • -
    • Support for table to use as input: freq(table(x, y)) +
    • Support for table to use as input: freq(table(x, y))
    • Support for existing functions hist and plot to use a frequency table as input: hist(freq(df$age))
    • Support for as.vector, as.data.frame, as_tibble and format
    • -
    • Support for quasiquotation: freq(mydata, mycolumn) is the same as mydata %>% freq(mycolumn) +
    • Support for quasiquotation: freq(mydata, mycolumn) is the same as mydata %>% freq(mycolumn)
    • Function top_freq function to return the top/below n items as vector
    • Header of frequency tables now also show Mean Absolute Deviaton (MAD) and Interquartile Range (IQR)
    • diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index 9e3f2f65..50d65fa8 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -12,7 +12,7 @@ articles: datasets: datasets.html resistance_predict: resistance_predict.html welcome_to_AMR: welcome_to_AMR.html -last_built: 2021-02-02T22:56Z +last_built: 2021-02-04T15:47Z urls: reference: https://msberends.github.io/AMR//reference article: https://msberends.github.io/AMR//articles diff --git a/docs/reference/ab_from_text.html b/docs/reference/ab_from_text.html index 8a532033..17066236 100644 --- a/docs/reference/ab_from_text.html +++ b/docs/reference/ab_from_text.html @@ -82,7 +82,7 @@ AMR (for R) - 1.5.0.9014 + 1.5.0.9015 @@ -264,7 +264,7 @@ collapse -

      character to pass on to paste(..., collapse = ...) to only return one character per element of text, see Examples

      +

      character to pass on to paste(, collapse = ...) to only return one character per element of text, see Examples

      translate_ab diff --git a/docs/reference/as.rsi.html b/docs/reference/as.rsi.html index 0e39d227..15b8497d 100644 --- a/docs/reference/as.rsi.html +++ b/docs/reference/as.rsi.html @@ -82,7 +82,7 @@ AMR (for R) - 1.5.0.9014 + 1.5.0.9015 @@ -363,7 +363,7 @@

      Supported Guidelines

      -

      For interpreting MIC values as well as disk diffusion diameters, supported guidelines to be used as input for the guideline argument are: "CLSI 2010", "CLSI 2011", "CLSI 2012", "CLSI 2013", "CLSI 2014", "CLSI 2015", "CLSI 2016", "CLSI 2017", "CLSI 2018", "CLSI 2019", "EUCAST 2011", "EUCAST 2012", "EUCAST 2013", "EUCAST 2014", "EUCAST 2015", "EUCAST 2016", "EUCAST 2017", "EUCAST 2018", "EUCAST 2019", "EUCAST 2020", "EUCAST 2021".

      +

      For interpreting MIC values as well as disk diffusion diameters, supported guidelines to be used as input for the guideline argument are: "EUCAST 2021", "EUCAST 2020", "EUCAST 2019", "EUCAST 2018", "EUCAST 2017", "EUCAST 2016", "EUCAST 2015", "EUCAST 2014", "EUCAST 2013", "EUCAST 2012", "EUCAST 2011", "CLSI 2019", "CLSI 2018", "CLSI 2017", "CLSI 2016", "CLSI 2015", "CLSI 2014", "CLSI 2013", "CLSI 2012", "CLSI 2011" and "CLSI 2010".

      Simply using "CLSI" or "EUCAST" as input will automatically select the latest version of that guideline. You can set your own data set using the reference_data argument. The guideline argument will then be ignored.

      After Interpretation

      @@ -379,8 +379,8 @@

      Other

      -

      The function is.rsi() detects if the input contains class <rsi>. If the input is a data.frame, it returns a vector in which all columns are checked for this class.

      -

      The function is.rsi.eligible() returns TRUE when a columns contains at most 5% invalid antimicrobial interpretations (not S and/or I and/or R), and FALSE otherwise. The threshold of 5% can be set with the threshold argument.

      +

      The function is.rsi() detects if the input contains class <rsi>. If the input is a data.frame, it iterates over all columns and returns a logical vector.

      +

      The function is.rsi.eligible() returns TRUE when a columns contains at most 5% invalid antimicrobial interpretations (not S and/or I and/or R), and FALSE otherwise. The threshold of 5% can be set with the threshold argument. If the input is a data.frame, it iterates over all columns and returns a logical vector.

      Interpretation of R and S/I

      diff --git a/docs/reference/first_isolate.html b/docs/reference/first_isolate.html index c8b6e380..813aaab0 100644 --- a/docs/reference/first_isolate.html +++ b/docs/reference/first_isolate.html @@ -82,7 +82,7 @@ AMR (for R) - 1.5.0.9014 + 1.5.0.9015 @@ -423,24 +423,27 @@ The lifecycle of this function is stable# See ?example_isolates. # basic filtering on first isolates -example_isolates[first_isolate(example_isolates), ] +example_isolates[first_isolate(), ] -# filtering based on isolates ---------------------------------------------- # \donttest{ +# get all first Gram-negatives +example_isolates[which(first_isolate() & mo_is_gram_negative()), ] + if (require("dplyr")) { - # filter on first isolates: + # filter on first isolates using dplyr: example_isolates %>% - mutate(first_isolate = first_isolate(.)) %>% - filter(first_isolate == TRUE) + filter(first_isolate()) # short-hand versions: - example_isolates %>% - filter(first_isolate()) example_isolates %>% filter_first_isolate() - example_isolates %>% filter_first_weighted_isolate() + + # grouped determination of first isolates (also prints group names): + example_isolates %>% + group_by(hospital_id) %>% + mutate(first = first_isolate()) # now let's see if first isolates matter: A <- example_isolates %>% diff --git a/docs/reference/index.html b/docs/reference/index.html index 7e6cbaeb..59740f86 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9014 + 1.5.0.9015 diff --git a/docs/reference/mo_property.html b/docs/reference/mo_property.html index cae71a74..46c08ec6 100644 --- a/docs/reference/mo_property.html +++ b/docs/reference/mo_property.html @@ -82,7 +82,7 @@ AMR (for R) - 1.5.0.9014 + 1.5.0.9015 @@ -323,7 +323,7 @@ property -

      one of the column names of the microorganisms data set: "mo", "fullname", "kingdom", "phylum", "class", "order", "family", "genus", "species", "subspecies", "rank", "ref", "species_id", "source", "prevalence", "snomed", or must be "shortname"

      +

      one of the column names of the microorganisms data set: "mo", "fullname", "kingdom", "phylum", "class", "order", "family", "genus", "species", "subspecies", "rank", "ref", "species_id", "source", "prevalence" or "snomed", or must be "shortname"

      diff --git a/docs/reference/translate.html b/docs/reference/translate.html index 343ac64c..16209a9b 100644 --- a/docs/reference/translate.html +++ b/docs/reference/translate.html @@ -82,7 +82,7 @@ AMR (for R) - 1.5.0.9014 + 1.5.0.9015 @@ -248,7 +248,7 @@

      Details

      Strings will be translated to foreign languages if they are defined in a local translation file. Additions to this file can be suggested at our repository. The file can be found here: https://github.com/msberends/AMR/blob/master/data-raw/translations.tsv. This file will be read by all functions where a translated output can be desired, like all mo_* functions (such as mo_name(), mo_gramstain(), mo_type(), etc.) and ab_* functions (such as ab_name(), ab_group(), etc.).

      -

      Currently supported languages are: Dutch, English, French, German, Italian, Portuguese, Spanish. Please note that currently not all these languages have translations available for all antimicrobial agents and colloquial microorganism names.

      +

      Currently supported languages are: Dutch, English, French, German, Italian, Portuguese and Spanish. Please note that currently not all these languages have translations available for all antimicrobial agents and colloquial microorganism names.

      Please suggest your own translations by creating a new issue on our repository.

      Changing the Default Language

      diff --git a/docs/survey.html b/docs/survey.html index 54032592..0ba3b116 100644 --- a/docs/survey.html +++ b/docs/survey.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9014 + 1.5.0.9015 diff --git a/man/ab_from_text.Rd b/man/ab_from_text.Rd index e41fa4b0..044feec8 100644 --- a/man/ab_from_text.Rd +++ b/man/ab_from_text.Rd @@ -18,7 +18,7 @@ ab_from_text( \item{type}{type of property to search for, either \code{"drug"}, \code{"dose"} or \code{"administration"}, see \emph{Examples}} -\item{collapse}{character to pass on to \code{paste(..., collapse = ...)} to only return one character per element of \code{text}, see \emph{Examples}} +\item{collapse}{character to pass on to \code{paste(, collapse = ...)} to only return one character per element of \code{text}, see \emph{Examples}} \item{translate_ab}{if \code{type = "drug"}: a column name of the \link{antibiotics} data set to translate the antibiotic abbreviations to, using \code{\link[=ab_property]{ab_property()}}. Defaults to \code{FALSE}. Using \code{TRUE} is equal to using "name".} diff --git a/man/as.rsi.Rd b/man/as.rsi.Rd index b6e099b9..fe6c4787 100755 --- a/man/as.rsi.Rd +++ b/man/as.rsi.Rd @@ -104,7 +104,7 @@ your_data \%>\% mutate(across((is.disk), as.rsi)) # since dplyr 1.0.0 \subsection{Supported Guidelines}{ -For interpreting MIC values as well as disk diffusion diameters, supported guidelines to be used as input for the \code{guideline} argument are: "CLSI 2010", "CLSI 2011", "CLSI 2012", "CLSI 2013", "CLSI 2014", "CLSI 2015", "CLSI 2016", "CLSI 2017", "CLSI 2018", "CLSI 2019", "EUCAST 2011", "EUCAST 2012", "EUCAST 2013", "EUCAST 2014", "EUCAST 2015", "EUCAST 2016", "EUCAST 2017", "EUCAST 2018", "EUCAST 2019", "EUCAST 2020", "EUCAST 2021". +For interpreting MIC values as well as disk diffusion diameters, supported guidelines to be used as input for the \code{guideline} argument are: "EUCAST 2021", "EUCAST 2020", "EUCAST 2019", "EUCAST 2018", "EUCAST 2017", "EUCAST 2016", "EUCAST 2015", "EUCAST 2014", "EUCAST 2013", "EUCAST 2012", "EUCAST 2011", "CLSI 2019", "CLSI 2018", "CLSI 2017", "CLSI 2016", "CLSI 2015", "CLSI 2014", "CLSI 2013", "CLSI 2012", "CLSI 2011" and "CLSI 2010". Simply using \code{"CLSI"} or \code{"EUCAST"} as input will automatically select the latest version of that guideline. You can set your own data set using the \code{reference_data} argument. The \code{guideline} argument will then be ignored. } @@ -121,9 +121,9 @@ The repository of this package \href{https://github.com/msberends/AMR/blob/maste \subsection{Other}{ -The function \code{\link[=is.rsi]{is.rsi()}} detects if the input contains class \verb{}. If the input is a data.frame, it returns a vector in which all columns are checked for this class. +The function \code{\link[=is.rsi]{is.rsi()}} detects if the input contains class \verb{}. If the input is a data.frame, it iterates over all columns and returns a logical vector. -The function \code{\link[=is.rsi.eligible]{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} argument. +The function \code{\link[=is.rsi.eligible]{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} argument. If the input is a data.frame, it iterates over all columns and returns a logical vector. } } \section{Interpretation of R and S/I}{ diff --git a/man/first_isolate.Rd b/man/first_isolate.Rd index 0c92021e..5fb0a309 100755 --- a/man/first_isolate.Rd +++ b/man/first_isolate.Rd @@ -152,24 +152,27 @@ On our website \url{https://msberends.github.io/AMR/} you can find \href{https:/ # See ?example_isolates. # basic filtering on first isolates -example_isolates[first_isolate(example_isolates), ] +example_isolates[first_isolate(), ] -# filtering based on isolates ---------------------------------------------- \donttest{ +# get all first Gram-negatives +example_isolates[which(first_isolate() & mo_is_gram_negative()), ] + if (require("dplyr")) { - # filter on first isolates: + # filter on first isolates using dplyr: example_isolates \%>\% - mutate(first_isolate = first_isolate(.)) \%>\% - filter(first_isolate == TRUE) + filter(first_isolate()) # short-hand versions: - example_isolates \%>\% - filter(first_isolate()) example_isolates \%>\% filter_first_isolate() - example_isolates \%>\% filter_first_weighted_isolate() + + # grouped determination of first isolates (also prints group names): + example_isolates \%>\% + group_by(hospital_id) \%>\% + mutate(first = first_isolate()) # now let's see if first isolates matter: A <- example_isolates \%>\% diff --git a/man/mo_property.Rd b/man/mo_property.Rd index 3d6e3395..c683ad8f 100644 --- a/man/mo_property.Rd +++ b/man/mo_property.Rd @@ -98,7 +98,7 @@ mo_property(x, property = "fullname", language = get_locale(), ...) \item{open}{browse the URL using \code{\link[utils:browseURL]{browseURL()}}} -\item{property}{one of the column names of the \link{microorganisms} data set: "\code{mo}", "\code{fullname}", "\code{kingdom}", "\code{phylum}", "\code{class}", "\code{order}", "\code{family}", "\code{genus}", "\code{species}", "\code{subspecies}", "\code{rank}", "\code{ref}", "\code{species_id}", "\code{source}", "\code{prevalence}", "\code{snomed}", or must be \code{"shortname"}} +\item{property}{one of the column names of the \link{microorganisms} data set: "mo", "fullname", "kingdom", "phylum", "class", "order", "family", "genus", "species", "subspecies", "rank", "ref", "species_id", "source", "prevalence" or "snomed", or must be \code{"shortname"}} } \value{ \itemize{ diff --git a/man/translate.Rd b/man/translate.Rd index 58d7e40a..7307bd88 100644 --- a/man/translate.Rd +++ b/man/translate.Rd @@ -13,7 +13,7 @@ For language-dependent output of AMR functions, like \code{\link[=mo_name]{mo_na \details{ Strings will be translated to foreign languages if they are defined in a local translation file. Additions to this file can be suggested at our repository. The file can be found here: \url{https://github.com/msberends/AMR/blob/master/data-raw/translations.tsv}. This file will be read by all functions where a translated output can be desired, like all \code{\link[=mo_property]{mo_*}} functions (such as \code{\link[=mo_name]{mo_name()}}, \code{\link[=mo_gramstain]{mo_gramstain()}}, \code{\link[=mo_type]{mo_type()}}, etc.) and \code{\link[=ab_property]{ab_*}} functions (such as \code{\link[=ab_name]{ab_name()}}, \code{\link[=ab_group]{ab_group()}}, etc.). -Currently supported languages are: Dutch, English, French, German, Italian, Portuguese, Spanish. Please note that currently not all these languages have translations available for all antimicrobial agents and colloquial microorganism names. +Currently supported languages are: Dutch, English, French, German, Italian, Portuguese and Spanish. Please note that currently not all these languages have translations available for all antimicrobial agents and colloquial microorganism names. Please suggest your own translations \href{https://github.com/msberends/AMR/issues/new?title=Translations}{by creating a new issue on our repository}. \subsection{Changing the Default Language}{ diff --git a/tests/testthat/test-eucast_rules.R b/tests/testthat/test-eucast_rules.R index 6e97ea74..471c05d9 100755 --- a/tests/testthat/test-eucast_rules.R +++ b/tests/testthat/test-eucast_rules.R @@ -96,7 +96,8 @@ test_that("EUCAST rules work", { AZM = as.rsi("R"), CLR = factor("R"), stringsAsFactors = FALSE), - version_expertrules = 3.1)$CLR)) + version_expertrules = 3.1, + only_rsi_columns = FALSE)$CLR)) b <- example_isolates$ERY expect_identical(a[!is.na(b)], b[!is.na(b)]) diff --git a/tests/testthat/test-first_isolate.R b/tests/testthat/test-first_isolate.R index ef3fb446..e20df1f8 100755 --- a/tests/testthat/test-first_isolate.R +++ b/tests/testthat/test-first_isolate.R @@ -212,4 +212,9 @@ test_that("first isolates work", { # only one isolate, so return fast expect_true(first_isolate(data.frame(mo = "Escherichia coli", date = Sys.Date(), patient = "patient"), info = TRUE)) + # groups + x <- example_isolates %>% group_by(ward_icu) %>% mutate(first = first_isolate()) + y <- example_isolates %>% group_by(ward_icu) %>% mutate(first = first_isolate(.)) + expect_identical(x, y) + }) diff --git a/vignettes/datasets.Rmd b/vignettes/datasets.Rmd index b9803716..6949eb42 100644 --- a/vignettes/datasets.Rmd +++ b/vignettes/datasets.Rmd @@ -29,8 +29,8 @@ options(knitr.kable.NA = '') structure_txt <- function(dataset) { paste0("A data set with ", format(nrow(dataset), big.mark = ","), " rows and ", - ncol(dataset), " columns, containing the following column names: \n*", - paste0("'", colnames(dataset), "'", collapse = ", "), "*.") + ncol(dataset), " columns, containing the following column names: \n", + AMR:::vector_or(colnames(dataset), quotes = "*", last_sep = " and "), ".") } download_txt <- function(filename) { @@ -172,7 +172,7 @@ This data set is in R available as `antibiotics`, after you load the `AMR` packa This data set contains all EARS-Net and ATC codes gathered from WHO and WHONET, and all compound IDs from PubChem. It also contains all brand names (synonyms) as found on PubChem and Defined Daily Doses (DDDs) for oral and parenteral administration. -* [ATC/DDD index from WHO Collaborating Centre for Drug Statistics Methodology](https://www.whocc.no/atc_ddd_index/) (note: this may not be used for commercial purposes, but is frelly available from the WHO CC website for personal use) +* [ATC/DDD index from WHO Collaborating Centre for Drug Statistics Methodology](https://www.whocc.no/atc_ddd_index/) (note: this may not be used for commercial purposes, but is freely available from the WHO CC website for personal use) * [PubChem by the US National Library of Medicine](https://pubchem.ncbi.nlm.nih.gov) * [WHONET software 2019](https://whonet.org) @@ -197,7 +197,7 @@ This data set is in R available as `antivirals`, after you load the `AMR` packag This data set contains all ATC codes gathered from WHO and all compound IDs from PubChem. It also contains all brand names (synonyms) as found on PubChem and Defined Daily Doses (DDDs) for oral and parenteral administration. -* [ATC/DDD index from WHO Collaborating Centre for Drug Statistics Methodology](https://www.whocc.no/atc_ddd_index/) (note: this may not be used for commercial purposes, but is frelly available from the WHO CC website for personal use) +* [ATC/DDD index from WHO Collaborating Centre for Drug Statistics Methodology](https://www.whocc.no/atc_ddd_index/) (note: this may not be used for commercial purposes, but is freely available from the WHO CC website for personal use) * [PubChem by the US National Library of Medicine](https://pubchem.ncbi.nlm.nih.gov) ### Example content @@ -218,7 +218,7 @@ This data set is in R available as `intrinsic_resistant`, after you load the `AM ### Source -This data set contains all defined intrinsic resistance by EUCAST of all bug-drug combinations, and is based on '`r AMR:::EUCAST_VERSION_EXPERT_RULES[["3.2"]]$title`', `r AMR:::EUCAST_VERSION_EXPERT_RULES[["3.2"]]$version_txt` from `r AMR:::EUCAST_VERSION_EXPERT_RULES[["3.2"]]$year`. +This data set contains all defined intrinsic resistance by EUCAST of all bug-drug combinations, and is based on `r AMR:::format_eucast_version_nr("3.2")`. ### Example content