diff --git a/DESCRIPTION b/DESCRIPTION index e290c931..72ec77bd 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 1.4.0.9045 -Date: 2020-12-25 +Version: 1.4.0.9046 +Date: 2020-12-27 Title: Antimicrobial Resistance Analysis Authors@R: c( person(role = c("aut", "cre"), diff --git a/NAMESPACE b/NAMESPACE index 803a5fb1..872de409 100755 --- a/NAMESPACE +++ b/NAMESPACE @@ -137,6 +137,7 @@ export(fluoroquinolones) export(full_join_microorganisms) export(g.test) export(geom_rsi) +export(get_episode) export(get_locale) export(get_mo_source) export(ggplot_pca) diff --git a/NEWS.md b/NEWS.md index 37c70f45..0a8b0da5 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,9 +1,8 @@ -# AMR 1.4.0.9045 -## Last updated: 25 December 2020 +# AMR 1.4.0.9046 +## Last updated: 27 December 2020 ### New -* Function `is_new_episode()` to determine patient episodes which are not necessarily based on microorganisms. It also supports grouped variables with e.g. `mutate()`, `filter()` and `summarise()` of the `dplyr` package: - +* Functions `get_episode()` and `is_new_episode()` to determine (patient) episodes which are not necessarily based on microorganisms. The `get_episode()` function returns the index number of the episode per group, while the `is_new_episode()` function returns values `TRUE`/`FALSE` to indicate whether an item in a vector is the start of a new episode. They also support `dplyr`s grouping (i.e. using `group_by()`): ```r library(dplyr) example_isolates %>% @@ -23,7 +22,6 @@ * If using `as.rsi()` on MICs or disk diffusion while there is intrinsic antimicrobial resistance, a warning will be thrown to remind about this * Fix for using `as.rsi()` on a `data.frame` that only contains one column for antibiotic interpretations * Some functions are now context-aware when used inside `dplyr` verbs, such as `filter()`, `mutate()` and `summarise()`. This means that then the data argument does not need to be set anymore. This is the case for the new functions `mo_is_gram_negative()`, `mo_is_gram_positive()`, `mo_is_intrinsic_resistant()` and for the existing functions `first_isolate()`, `key_antibiotics()`, `mdro()`, `brmo()`, `mrgn()`, `mdr_tb()`, `mdr_cmi2012()`, `eucast_exceptional_phenotypes()`. This was already the case for antibiotic selection functions (such as using `penicillins()` in `dplyr::select()`). - ```r # to select first isolates that are Gram-negative # and view results of cephalosporins and aminoglycosides: diff --git a/R/aa_helper_functions.R b/R/aa_helper_functions.R index b0536c0f..95310d95 100755 --- a/R/aa_helper_functions.R +++ b/R/aa_helper_functions.R @@ -536,22 +536,39 @@ get_current_data <- function(arg_name, call) { call = call - 4)) } -get_root_env_address <- function() { - sub("", "\\1", utils::capture.output(sys.frames()[[1]])) +unique_call_id <- function() { + # combination of environment ID (like "0x7fed4ee8c848") + # and highest system call + c(envir = gsub("", "\\1", utils::capture.output(sys.frames()[[1]])), + call = paste0(deparse(sys.calls()[[1]]), collapse = "")) } remember_thrown_message <- function(fn) { - assign(x = paste0("address_", fn), - value = get_root_env_address(), - envir = mo_env) + # this is to prevent that messages/notes will be printed for every dplyr group + # e.g. this would show a msg 4 times: example_isolates %>% group_by(hospital_id) %>% filter(mo_is_gram_negative()) + assign(x = paste0("uniquecall_", fn), + value = unique_call_id(), + envir = pkg_env) } message_not_thrown_before <- function(fn) { - is.null(mo_env[[paste0("address_", fn)]]) || !identical(mo_env[[paste0("address_", fn)]], get_root_env_address()) + is.null(pkg_env[[paste0("uniquecall_", fn)]]) || !identical(pkg_env[[paste0("uniquecall_", fn)]], unique_call_id()) +} + +reset_all_thrown_messages <- function() { + # for unit tests, where the environment and highest system call do not change + pkg_env_contents <- ls(envir = pkg_env) + rm(list = pkg_env_contents[pkg_env_contents %like% "^uniquecall_"], + envir = pkg_env) } has_colour <- function() { - # this is a base R version of crayon::has_color + # this is a base R version of crayon::has_color, but disables colours on emacs + + if (Sys.getenv("EMACS") != "" || Sys.getenv("INSIDE_EMACS") != "") { + # disable on emacs, only supports 8 colours + return(FALSE) + } enabled <- getOption("crayon.enabled") if (!is.null(enabled)) { return(isTRUE(enabled)) @@ -581,20 +598,6 @@ has_colour <- function() { } return(FALSE) } - emacs_version <- function() { - ver <- Sys.getenv("INSIDE_EMACS") - if (ver == "") { - return(NA_integer_) - } - ver <- gsub("'", "", ver) - ver <- strsplit(ver, ",", fixed = TRUE)[[1]] - ver <- strsplit(ver, ".", fixed = TRUE)[[1]] - as.numeric(ver) - } - if ((Sys.getenv("EMACS") != "" || Sys.getenv("INSIDE_EMACS") != "") && - !is.na(emacs_version()[1]) && emacs_version()[1] >= 23) { - return(TRUE) - } if ("COLORTERM" %in% names(Sys.getenv())) { return(TRUE) } @@ -656,6 +659,15 @@ font_grey_bg <- function(..., collapse = " ") { font_green_bg <- function(..., collapse = " ") { try_colour(..., before = "\033[42m", after = "\033[49m", collapse = collapse) } +font_rsi_R_bg <- function(..., collapse = " ") { + try_colour(..., before = "\033[48;5;202m", after = "\033[49m", collapse = collapse) +} +font_rsi_S_bg <- function(..., collapse = " ") { + try_colour(..., before = "\033[48;5;76m", after = "\033[49m", collapse = collapse) +} +font_rsi_I_bg <- function(..., collapse = " ") { + try_colour(..., before = "\033[48;5;148m", after = "\033[49m", collapse = collapse) +} font_red_bg <- function(..., collapse = " ") { try_colour(..., before = "\033[41m", after = "\033[49m", collapse = collapse) } diff --git a/R/is_new_episode.R b/R/episode.R similarity index 62% rename from R/is_new_episode.R rename to R/episode.R index 48677216..775e4820 100644 --- a/R/is_new_episode.R +++ b/R/episode.R @@ -25,26 +25,34 @@ #' Determine (new) episodes for patients #' -#' This function determines which items in a vector can be considered (the start of) a new episode, based on the argument `episode_days`. This can be used to determine clinical episodes for any epidemiological analysis. +#' These functions determine which items in a vector can be considered (the start of) a new episode, based on the argument `episode_days`. This can be used to determine clinical episodes for any epidemiological analysis. The [get_episode()] function returns the index number of the episode per group, while the [is_new_episode()] function returns values `TRUE`/`FALSE` to indicate whether an item in a vector is the start of a new episode. #' @inheritSection lifecycle Stable lifecycle #' @param x vector of dates (class `Date` or `POSIXt`) -#' @param episode_days length of the required episode in days, defaults to 365. Every element in the input will return `TRUE` after this number of days has passed since the last included date, independent of calendar years. Please see *Details*. +#' @param episode_days length of the required episode in days, please see *Details* #' @param ... arguments passed on to [as.Date()] #' @details #' Dates are first sorted from old to new. The oldest date will mark the start of the first episode. After this date, the next date will be marked that is at least `episode_days` days later than the start of the first episode. From that second marked date on, the next date will be marked that is at least `episode_days` days later than the start of the second episode which will be the start of the third episode, and so on. Before the vector is being returned, the original order will be restored. #' -#' The [first_isolate()] function is a wrapper around the [is_new_episode()] function, but more efficient for data sets containing microorganism codes or names. +#' The [first_isolate()] function is a wrapper around the [is_new_episode()] function, but is more efficient for data sets containing microorganism codes or names. #' -#' The `dplyr` package is not required for this function to work, but this function works conveniently inside `dplyr` verbs such as [`filter()`][dplyr::filter()], [`mutate()`][dplyr::mutate()] and [`summarise()`][dplyr::summarise()]. -#' @return a [logical] vector +#' The `dplyr` package is not required for these functions to work, but these functions support [variable grouping][dplyr::group_by()] and work conveniently inside `dplyr` verbs such as [`filter()`][dplyr::filter()], [`mutate()`][dplyr::mutate()] and [`summarise()`][dplyr::summarise()]. +#' @return +#' * [get_episode()]: a [double] vector +#' * [is_new_episode()]: a [logical] vector +#' @seealso [first_isolate()] +#' @rdname get_episode #' @export #' @inheritSection AMR Read more on our website! #' @examples #' # `example_isolates` is a dataset available in the AMR package. #' # See ?example_isolates. #' -#' is_new_episode(example_isolates$date) +#' get_episode(example_isolates$date, episode_days = 60) #' is_new_episode(example_isolates$date, episode_days = 60) +#' +#' # filter on results from the third 60-day episode using base R +#' example_isolates[which(get_episode(example_isolates$date, 60) == 3), ] +#' #' \donttest{ #' if (require("dplyr")) { #' # is_new_episode() can also be used in dplyr verbs to determine patient @@ -54,7 +62,15 @@ #' size = 2000, #' replace = TRUE)) %>% #' group_by(condition) %>% -#' mutate(new_episode = is_new_episode(date)) +#' mutate(new_episode = is_new_episode(date, 365)) +#' +#' example_isolates %>% +#' group_by(hospital_id, patient_id) %>% +#' transmute(date, +#' patient_id, +#' new_index = get_episode(date, 60), +#' new_logical = is_new_episode(date, 60)) +#' #' #' example_isolates %>% #' group_by(hospital_id) %>% @@ -71,7 +87,7 @@ #' #' y <- example_isolates %>% #' group_by(patient_id, mo) %>% -#' filter(is_new_episode(date)) +#' filter(is_new_episode(date, 365)) #' #' identical(x$patient_id, y$patient_id) #' @@ -79,21 +95,52 @@ #' # since you can now group on anything that seems relevant: #' example_isolates %>% #' group_by(patient_id, mo, hospital_id, ward_icu) %>% -#' mutate(flag_episode = is_new_episode(date)) +#' mutate(flag_episode = is_new_episode(date, 365)) #' } #' } -is_new_episode <- function(x, episode_days = 365, ...) { +get_episode <- function(x, episode_days, ...) { meet_criteria(x, allow_class = c("Date", "POSIXt")) meet_criteria(episode_days, allow_class = c("numeric", "double", "integer"), has_length = 1) + exec_episode(type = "sequential", + x = x, + episode_days = episode_days, + ... = ...) +} + +#' @rdname get_episode +#' @export +is_new_episode <- function(x, episode_days, ...) { + meet_criteria(x, allow_class = c("Date", "POSIXt")) + meet_criteria(episode_days, allow_class = c("numeric", "double", "integer"), has_length = 1) + + exec_episode(type = "logical", + x = x, + episode_days = episode_days, + ... = ...) +} + +exec_episode <- function(type, x, episode_days, ...) { x <- as.double(as.Date(x, ...)) # as.Date() for POSIX classes if (length(x) == 1) { - return(TRUE) + if (type == "logical") { + return(TRUE) + } else if (type == "sequential") { + return(1) + } } else if (length(x) == 2) { if (max(x) - min(x) >= episode_days) { - return(c(TRUE, TRUE)) + if (type == "logical") { + return(c(TRUE, TRUE)) + } else if (type == "sequential") { + return(c(1, 2)) + } } else { - return(c(TRUE, FALSE)) + if (type == "logical") { + return(c(TRUE, FALSE)) + } else if (type == "sequential") { + return(c(1, 1)) + } } } @@ -107,13 +154,22 @@ is_new_episode <- function(x, episode_days = 365, ...) { for (i in 2:length(x)) { if (isTRUE((x[i] - start) >= episode_days)) { ind <- ind + 1 - indices[ind] <- i + if (type == "logical") { + indices[ind] <- i + } start <- x[i] } + if (type == "sequential") { + indices[i] <- ind + } + } + if (type == "logical") { + result <- rep(FALSE, length(x)) + result[indices] <- TRUE + result + } else if (type == "sequential") { + indices } - result <- rep(FALSE, length(x)) - result[indices] <- TRUE - result } df <- data.frame(x = x, diff --git a/R/mo.R b/R/mo.R index 6a4e8475..bae0d36c 100755 --- a/R/mo.R +++ b/R/mo.R @@ -361,11 +361,11 @@ exec_as.mo <- function(x, # keep track of time - give some hints to improve speed if it takes a long time start_time <- Sys.time() - mo_env$mo_failures <- NULL - mo_env$mo_uncertainties <- NULL - mo_env$mo_renamed <- NULL + pkg_env$mo_failures <- NULL + pkg_env$mo_uncertainties <- NULL + pkg_env$mo_renamed <- NULL } - mo_env$mo_renamed_last_run <- NULL + pkg_env$mo_renamed_last_run <- NULL failures <- character(0) uncertainty_level <- translate_allow_uncertain(allow_uncertain) @@ -598,7 +598,7 @@ exec_as.mo <- function(x, } else { x[i] <- lookup(fullname == found["fullname_new"], haystack = MO_lookup) } - mo_env$mo_renamed_last_run <- found["fullname"] + pkg_env$mo_renamed_last_run <- found["fullname"] was_renamed(name_old = found["fullname"], name_new = lookup(fullname == found["fullname_new"], "fullname", haystack = MO_lookup), ref_old = found["ref"], @@ -973,7 +973,7 @@ exec_as.mo <- function(x, } else { x[i] <- lookup(fullname == found["fullname_new"], haystack = MO_lookup) } - mo_env$mo_renamed_last_run <- found["fullname"] + pkg_env$mo_renamed_last_run <- found["fullname"] was_renamed(name_old = found["fullname"], name_new = lookup(fullname == found["fullname_new"], "fullname", haystack = MO_lookup), ref_old = found["ref"], @@ -1025,7 +1025,7 @@ exec_as.mo <- function(x, ref_old = found["ref"], ref_new = lookup(fullname == found["fullname_new"], "ref", haystack = MO_lookup), mo = lookup(fullname == found["fullname_new"], "mo", haystack = MO_lookup)) - mo_env$mo_renamed_last_run <- found["fullname"] + pkg_env$mo_renamed_last_run <- found["fullname"] uncertainties <<- rbind(uncertainties, format_uncertainty_as_df(uncertainty_level = now_checks_for_uncertainty_level, input = a.x_backup, @@ -1396,7 +1396,7 @@ exec_as.mo <- function(x, # handling failures ---- failures <- failures[!failures %in% c(NA, NULL, NaN)] if (length(failures) > 0 & initial_search == TRUE) { - mo_env$mo_failures <- sort(unique(failures)) + pkg_env$mo_failures <- sort(unique(failures)) plural <- c("value", "it", "was") if (pm_n_distinct(failures) > 1) { plural <- c("values", "them", "were") @@ -1423,7 +1423,7 @@ exec_as.mo <- function(x, # handling uncertainties ---- if (NROW(uncertainties) > 0 & initial_search == TRUE) { uncertainties <- as.list(pm_distinct(uncertainties, input, .keep_all = TRUE)) - mo_env$mo_uncertainties <- uncertainties + pkg_env$mo_uncertainties <- uncertainties plural <- c("", "it", "was") if (length(uncertainties$input) > 1) { @@ -1559,13 +1559,13 @@ was_renamed <- function(name_old, name_new, ref_old = "", ref_new = "", mo = "") new_ref = ref_new, mo = mo, stringsAsFactors = FALSE) - already_set <- mo_env$mo_renamed + already_set <- pkg_env$mo_renamed if (!is.null(already_set)) { - mo_env$mo_renamed = rbind(already_set, + pkg_env$mo_renamed = rbind(already_set, newly_set, stringsAsFactors = FALSE) } else { - mo_env$mo_renamed <- newly_set + pkg_env$mo_renamed <- newly_set } } @@ -1573,9 +1573,9 @@ format_uncertainty_as_df <- function(uncertainty_level, input, result_mo, candidates = NULL) { - if (!is.null(mo_env$mo_renamed_last_run)) { - fullname <- mo_env$mo_renamed_last_run - mo_env$mo_renamed_last_run <- NULL + if (!is.null(pkg_env$mo_renamed_last_run)) { + fullname <- pkg_env$mo_renamed_last_run + pkg_env$mo_renamed_last_run <- NULL renamed_to <- MO_lookup[match(result_mo, MO_lookup$mo), "fullname", drop = TRUE][1] } else { fullname <- MO_lookup[match(result_mo, MO_lookup$mo), "fullname", drop = TRUE][1] @@ -1764,16 +1764,16 @@ unique.mo <- function(x, incomparables = FALSE, ...) { #' @rdname as.mo #' @export mo_failures <- function() { - mo_env$mo_failures + pkg_env$mo_failures } #' @rdname as.mo #' @export mo_uncertainties <- function() { - if (is.null(mo_env$mo_uncertainties)) { + if (is.null(pkg_env$mo_uncertainties)) { return(NULL) } - set_clean_class(as.data.frame(mo_env$mo_uncertainties, + set_clean_class(as.data.frame(pkg_env$mo_uncertainties, stringsAsFactors = FALSE), new_class = c("mo_uncertainties", "data.frame")) } @@ -1842,7 +1842,7 @@ print.mo_uncertainties <- function(x, ...) { #' @rdname as.mo #' @export mo_renamed <- function() { - items <- mo_env$mo_renamed + items <- pkg_env$mo_renamed if (is.null(items)) { items <- data.frame(stringsAsFactors = FALSE) } else { @@ -1906,20 +1906,20 @@ translate_allow_uncertain <- function(allow_uncertain) { } get_mo_failures_uncertainties_renamed <- function() { - remember <- list(failures = mo_env$mo_failures, - uncertainties = mo_env$mo_uncertainties, - renamed = mo_env$mo_renamed) + remember <- list(failures = pkg_env$mo_failures, + uncertainties = pkg_env$mo_uncertainties, + renamed = pkg_env$mo_renamed) # empty them, otherwise mo_shortname("Chlamydophila psittaci") will give 3 notes - mo_env$mo_failures <- NULL - mo_env$mo_uncertainties <- NULL - mo_env$mo_renamed <- NULL + pkg_env$mo_failures <- NULL + pkg_env$mo_uncertainties <- NULL + pkg_env$mo_renamed <- NULL remember } load_mo_failures_uncertainties_renamed <- function(metadata) { - mo_env$mo_failures <- metadata$failures - mo_env$mo_uncertainties <- metadata$uncertainties - mo_env$mo_renamed <- metadata$renamed + pkg_env$mo_failures <- metadata$failures + pkg_env$mo_uncertainties <- metadata$uncertainties + pkg_env$mo_renamed <- metadata$renamed } trimws2 <- function(x) { @@ -2007,4 +2007,4 @@ repair_reference_df <- function(reference_df) { reference_df } -mo_env <- new.env(hash = FALSE) +pkg_env <- new.env(hash = FALSE) diff --git a/R/mo_property.R b/R/mo_property.R index 41806f1e..276464ca 100755 --- a/R/mo_property.R +++ b/R/mo_property.R @@ -163,7 +163,7 @@ mo_name <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_name") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -180,7 +180,7 @@ mo_fullname <- mo_name mo_shortname <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_shortname") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -218,7 +218,7 @@ mo_shortname <- function(x, language = get_locale(), ...) { mo_subspecies <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_subspecies") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -231,7 +231,7 @@ mo_subspecies <- function(x, language = get_locale(), ...) { mo_species <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_species") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -244,7 +244,7 @@ mo_species <- function(x, language = get_locale(), ...) { mo_genus <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_genus") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -257,7 +257,7 @@ mo_genus <- function(x, language = get_locale(), ...) { mo_family <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_family") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -270,7 +270,7 @@ mo_family <- function(x, language = get_locale(), ...) { mo_order <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_order") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -283,7 +283,7 @@ mo_order <- function(x, language = get_locale(), ...) { mo_class <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_class") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -296,7 +296,7 @@ mo_class <- function(x, language = get_locale(), ...) { mo_phylum <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_phylum") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -309,7 +309,7 @@ mo_phylum <- function(x, language = get_locale(), ...) { mo_kingdom <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_kingdom") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -326,7 +326,7 @@ mo_domain <- mo_kingdom mo_type <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_type") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -339,7 +339,7 @@ mo_type <- function(x, language = get_locale(), ...) { mo_gramstain <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_gramstain") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -377,7 +377,7 @@ mo_gramstain <- function(x, language = get_locale(), ...) { mo_is_gram_negative <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_is_gram_negative") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -396,7 +396,7 @@ mo_is_gram_negative <- function(x, language = get_locale(), ...) { mo_is_gram_positive <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_is_gram_positive") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -450,7 +450,7 @@ mo_is_intrinsic_resistant <- function(x, ab, language = get_locale(), ...) { mo_snomed <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_snomed") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -463,7 +463,7 @@ mo_snomed <- function(x, language = get_locale(), ...) { mo_ref <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_ref") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -476,7 +476,7 @@ mo_ref <- function(x, language = get_locale(), ...) { mo_authors <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_authors") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -492,7 +492,7 @@ mo_authors <- function(x, language = get_locale(), ...) { mo_year <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_year") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -508,7 +508,7 @@ mo_year <- function(x, language = get_locale(), ...) { mo_rank <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_rank") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -521,7 +521,7 @@ mo_rank <- function(x, language = get_locale(), ...) { mo_taxonomy <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_taxonomy") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -547,7 +547,7 @@ mo_taxonomy <- function(x, language = get_locale(), ...) { mo_synonyms <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_synonyms") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -580,7 +580,7 @@ mo_synonyms <- function(x, language = get_locale(), ...) { mo_info <- function(x, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_info") } meet_criteria(x, allow_NA = TRUE) meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) @@ -610,7 +610,7 @@ mo_info <- function(x, language = get_locale(), ...) { mo_url <- function(x, open = FALSE, language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_url") } meet_criteria(x, allow_NA = TRUE) meet_criteria(open, allow_class = "logical", has_length = 1) @@ -647,7 +647,7 @@ mo_url <- function(x, open = FALSE, language = get_locale(), ...) { mo_property <- function(x, property = "fullname", language = get_locale(), ...) { if (missing(x)) { # this supports using in dplyr verbs: ... %>% filter(mo_is_intrinsic_resistant(ab = "amox")) - x <- find_mo_col("mo_is_intrinsic_resistant") + x <- find_mo_col("mo_property") } meet_criteria(x, allow_NA = TRUE) meet_criteria(property, allow_class = "character", has_length = 1, is_in = colnames(microorganisms)) diff --git a/R/mo_source.R b/R/mo_source.R index 97060b02..44da6bfd 100644 --- a/R/mo_source.R +++ b/R/mo_source.R @@ -132,7 +132,7 @@ set_mo_source <- function(path, destination = getOption("AMR_mo_source", "~/mo_s stop_ifnot(interactive(), "this function can only be used in interactive mode, since it must ask for the user's permission to write a file to their home folder.") if (is.null(path) || path %in% c(FALSE, "")) { - mo_env$mo_source <- NULL + pkg_env$mo_source <- NULL if (file.exists(mo_source_destination)) { unlink(mo_source_destination) message_("Removed mo_source file '", font_bold(mo_source_destination), "'", @@ -214,7 +214,7 @@ set_mo_source <- function(path, destination = getOption("AMR_mo_source", "~/mo_s attr(df, "mo_source_destination") <- mo_source_destination attr(df, "mo_source_timestamp") <- file.mtime(path) saveRDS(df, mo_source_destination) - mo_env$mo_source <- df + pkg_env$mo_source <- df message_(action, " mo_source file '", font_bold(mo_source_destination), "' (", formatted_filesize(mo_source_destination), ") from '", font_bold(path), @@ -232,17 +232,17 @@ get_mo_source <- function(destination = getOption("AMR_mo_source", "~/mo_source. } return(NULL) } - if (is.null(mo_env$mo_source)) { - mo_env$mo_source <- readRDS(path.expand(destination)) + if (is.null(pkg_env$mo_source)) { + pkg_env$mo_source <- readRDS(path.expand(destination)) } - old_time <- attributes(mo_env$mo_source)$mo_source_timestamp - new_time <- file.mtime(attributes(mo_env$mo_source)$mo_source_location) + old_time <- attributes(pkg_env$mo_source)$mo_source_timestamp + new_time <- file.mtime(attributes(pkg_env$mo_source)$mo_source_location) if (interactive() && !identical(old_time, new_time)) { # source file was updated, also update reference - set_mo_source(attributes(mo_env$mo_source)$mo_source_location) + set_mo_source(attributes(pkg_env$mo_source)$mo_source_location) } - mo_env$mo_source + pkg_env$mo_source } check_validity_mo_source <- function(x, refer_to_name = "`reference_df`", stop_on_error = TRUE) { @@ -251,7 +251,7 @@ check_validity_mo_source <- function(x, refer_to_name = "`reference_df`", stop_o if (paste(deparse(substitute(x)), collapse = "") == "get_mo_source()") { return(TRUE) } - if (is.null(mo_env$mo_source) && (identical(x, get_mo_source()))) { + if (is.null(pkg_env$mo_source) && (identical(x, get_mo_source()))) { return(TRUE) } if (is.null(x)) { diff --git a/R/rsi.R b/R/rsi.R index e8ba24e4..2486f29e 100755 --- a/R/rsi.R +++ b/R/rsi.R @@ -844,9 +844,9 @@ exec_as.rsi <- function(method, 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 ")) + out[x == "R"] <- font_rsi_R_bg(font_black(" R ")) + out[x == "S"] <- font_rsi_S_bg(font_black(" S ")) + out[x == "I"] <- font_rsi_I_bg(font_black(" I ")) create_pillar_column(out, align = "left", width = 5) } diff --git a/R/rsi_calc.R b/R/rsi_calc.R index f852ebf3..eceebcf6 100755 --- a/R/rsi_calc.R +++ b/R/rsi_calc.R @@ -147,12 +147,10 @@ rsi_calc <- function(..., } if (print_warning == TRUE) { - # since rsi_calc() is always called from a count() or proportion() function, we use -1: - cll <- gsub("[^a-zA-Z0-9_]+", "_", paste(deparse(sys.calls()[[length(sys.calls()) - 1]]), collapse = "")) - if (message_not_thrown_before(cll)) { + if (message_not_thrown_before("rsi_calc")) { warning_("Increase speed by transforming to class on beforehand: your_data %>% mutate_if(is.rsi.eligible, as.rsi)", call = FALSE) - remember_thrown_message(cll) + remember_thrown_message("rsi_calc") } } diff --git a/_pkgdown.yml b/_pkgdown.yml index d4c12e3c..00babeaa 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -217,4 +217,4 @@ template: assets: "pkgdown/logos" # use logos in this folder params: noindex: false - template: "flatly" + bootswatch: "flatly" diff --git a/docs/404.html b/docs/404.html index 27e08d40..b3f81387 100644 --- a/docs/404.html +++ b/docs/404.html @@ -19,8 +19,8 @@ + - @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9045 + 1.4.0.9046 diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index ae5834e9..039a377e 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -19,8 +19,8 @@ + - @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9045 + 1.4.0.9046 diff --git a/docs/articles/AMR.html b/docs/articles/AMR.html index 21170fd9..1b29aeb1 100644 --- a/docs/articles/AMR.html +++ b/docs/articles/AMR.html @@ -12,7 +12,7 @@ - + @@ -39,7 +39,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 @@ -193,7 +193,7 @@

How to conduct AMR analysis

Matthijs S. Berends

-

24 December 2020

+

26 December 2020

Source: vignettes/AMR.Rmd @@ -202,7 +202,7 @@ -

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

+

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

Introduction

@@ -233,21 +233,21 @@ -2020-12-24 +2020-12-26 abcd Escherichia coli S S -2020-12-24 +2020-12-26 abcd Escherichia coli S R -2020-12-24 +2020-12-26 efgh Escherichia coli R @@ -352,31 +352,9 @@ -2012-10-07 -D7 -Hospital B -Escherichia coli -R -S -R -S -M - - -2016-11-19 -V9 +2011-10-28 +I1 Hospital A -Klebsiella pneumoniae -R -S -S -S -F - - -2015-03-30 -D9 -Hospital D Staphylococcus aureus R S @@ -385,38 +363,60 @@ M -2012-06-28 -Z4 -Hospital B -Staphylococcus aureus -S -S -S -S -F - - -2014-03-04 -M4 -Hospital C -Staphylococcus aureus -S -S -S -S -M - - -2014-08-18 -D2 -Hospital B +2011-06-05 +G5 +Hospital A Escherichia coli R -R +S S S M + +2014-05-12 +X7 +Hospital D +Streptococcus pneumoniae +S +S +R +S +F + + +2011-02-23 +K5 +Hospital A +Staphylococcus aureus +S +S +S +S +M + + +2017-09-20 +T5 +Hospital B +Escherichia coli +S +S +R +S +F + + +2017-02-10 +Y6 +Hospital D +Escherichia coli +I +S +S +S +F +

Now, let’s start the cleaning and the analysis!

@@ -449,16 +449,16 @@ Longest: 1

1 M -10,392 -51.96% -10,392 -51.96% +10,426 +52.13% +10,426 +52.13% 2 F -9,608 -48.04% +9,574 +47.87% 20,000 100.00% @@ -515,7 +515,7 @@ Longest: 1

First weighted isolates

-

We made a slight twist to the CLSI algorithm, to take into account the antimicrobial susceptibility profile. Have a look at all isolates of patient M9, sorted on date:

+

We made a slight twist to the CLSI algorithm, to take into account the antimicrobial susceptibility profile. Have a look at all isolates of patient F3, sorted on date:

@@ -531,19 +531,19 @@ Longest: 1

- - + + - + - - + + @@ -553,21 +553,21 @@ Longest: 1

- - + + + - - + - - + + - + @@ -575,19 +575,19 @@ Longest: 1

- - + + - - - + + + - - + + @@ -597,19 +597,19 @@ Longest: 1

- - + + - - - + + + - - + + @@ -619,19 +619,8 @@ Longest: 1

- - - - - - - - - - - - - + + @@ -639,6 +628,17 @@ Longest: 1

+ + + + + + + + + + +
isolate
12010-01-25M92010-01-17F3 B_ESCHR_COLI S S RSR TRUE
22010-02-01M92010-03-13F3 B_ESCHR_COLI S S
32010-02-22M92010-04-21F3 B_ESCHR_COLIR SSSR S FALSE
42010-08-12M92010-06-24F3 B_ESCHR_COLIIS S S S
52010-08-17M92010-08-02F3 B_ESCHR_COLIRRRSSS S FALSE
62010-09-18M92010-08-14F3 B_ESCHR_COLI S S
72011-07-05M92010-10-06F3 B_ESCHR_COLIR SR STRUESSFALSE
82011-07-19M92010-10-17F3 B_ESCHR_COLI R R
92011-07-20M9B_ESCHR_COLISSSSFALSE
102011-09-04M92010-11-17F3 B_ESCHR_COLI R I S FALSE
102011-02-21F3B_ESCHR_COLIRRSRTRUE

Only 2 isolates are marked as ‘first’ according to CLSI guideline. But when reviewing the antibiogram, it is obvious that some isolates are absolutely different strains and should be included too. This is why we weigh isolates, based on their antibiogram. The key_antibiotics() function adds a vector with 18 key antibiotics: 6 broad spectrum ones, 6 small spectrum for Gram negatives and 6 small spectrum for Gram positives. These can be defined by the user.

@@ -665,20 +665,20 @@ Longest: 1

1 -2010-01-25 -M9 +2010-01-17 +F3 B_ESCHR_COLI S S R -S +R TRUE TRUE 2 -2010-02-01 -M9 +2010-03-13 +F3 B_ESCHR_COLI S S @@ -689,68 +689,68 @@ Longest: 1

3 -2010-02-22 -M9 +2010-04-21 +F3 B_ESCHR_COLI +R S -S -S +R S FALSE -FALSE +TRUE 4 -2010-08-12 -M9 +2010-06-24 +F3 B_ESCHR_COLI -I +S S S S FALSE -FALSE +TRUE 5 -2010-08-17 -M9 +2010-08-02 +F3 B_ESCHR_COLI -R -R -R +S +S +S S FALSE -TRUE +FALSE 6 -2010-09-18 -M9 +2010-08-14 +F3 B_ESCHR_COLI S S S S FALSE -TRUE +FALSE 7 -2011-07-05 -M9 +2010-10-06 +F3 B_ESCHR_COLI -R S -R S -TRUE -TRUE +S +S +FALSE +FALSE 8 -2011-07-19 -M9 +2010-10-17 +F3 B_ESCHR_COLI R R @@ -761,36 +761,36 @@ Longest: 1

9 -2011-07-20 -M9 -B_ESCHR_COLI -S -S -S -S -FALSE -TRUE - - -10 -2011-09-04 -M9 +2010-11-17 +F3 B_ESCHR_COLI R I S S FALSE +FALSE + + +10 +2011-02-21 +F3 +B_ESCHR_COLI +R +R +S +R +TRUE TRUE -

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

+

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

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

 data_1st <- data %>% 
   filter_first_weighted_isolate()
-

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

+

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

We can remove unneeded columns:

 data_1st <- data_1st %>% 
@@ -834,13 +834,29 @@ Longest: 1

1 -2012-10-07 -D7 -Hospital B +2011-10-28 +I1 +Hospital A +B_STPHY_AURS +R +S +S +S +M +Gram-positive +Staphylococcus +aureus +TRUE + + +2 +2011-06-05 +G5 +Hospital A B_ESCHR_COLI R S -R +S S M Gram-negative @@ -848,63 +864,15 @@ Longest: 1

coli TRUE - -2 -2016-11-19 -V9 -Hospital A -B_KLBSL_PNMN -R -S -S -S -F -Gram-negative -Klebsiella -pneumoniae -TRUE - 3 -2015-03-30 -D9 -Hospital D -B_STPHY_AURS -R -S -S -S -M -Gram-positive -Staphylococcus -aureus -TRUE - - -5 -2014-03-04 -M4 -Hospital C -B_STPHY_AURS -S -S -S -S -M -Gram-positive -Staphylococcus -aureus -TRUE - - -7 -2011-02-08 -S3 +2014-05-12 +X7 Hospital D B_STRPT_PNMN S S -S +R R F Gram-positive @@ -913,16 +881,48 @@ Longest: 1

TRUE -8 -2015-12-31 -I5 -Hospital D -B_ESCHR_COLI -R -R -R +4 +2011-02-23 +K5 +Hospital A +B_STPHY_AURS +S +S +S S M +Gram-positive +Staphylococcus +aureus +TRUE + + +5 +2017-09-20 +T5 +Hospital B +B_ESCHR_COLI +S +S +R +S +F +Gram-negative +Escherichia +coli +TRUE + + +7 +2017-12-17 +Z3 +Hospital B +B_ESCHR_COLI +S +S +S +S +F Gram-negative Escherichia coli @@ -949,8 +949,8 @@ Longest: 1

data_1st %>% freq(genus, species)

Frequency table

Class: character
-Length: 15,683
-Available: 15,683 (100%, NA: 0 = 0%)
+Length: 15,695
+Available: 15,695 (100%, NA: 0 = 0%)
Unique: 4

Shortest: 16
Longest: 24

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

1 Escherichia coli -7,815 -49.83% -7,815 -49.83% +7,828 +49.88% +7,828 +49.88% 2 Staphylococcus aureus -4,001 -25.51% -11,816 -75.34% +3,977 +25.34% +11,805 +75.22% 3 Streptococcus pneumoniae -2,330 -14.86% -14,146 -90.20% +2,320 +14.78% +14,125 +90.00% 4 Klebsiella pneumoniae -1,537 -9.80% -15,683 +1,570 +10.00% +15,695 100.00% @@ -1020,50 +1020,50 @@ Longest: 24

E. coli AMX -3744 -257 -3814 -7815 +3731 +275 +3822 +7828 E. coli AMC -6185 -294 -1336 -7815 +6146 +297 +1385 +7828 E. coli CIP -5934 +5918 0 -1881 -7815 +1910 +7828 E. coli GEN -7005 +7087 0 -810 -7815 +741 +7828 K. pneumoniae AMX 0 0 -1537 -1537 +1570 +1570 K. pneumoniae AMC -1225 -45 -267 -1537 +1231 +57 +282 +1570 @@ -1086,34 +1086,34 @@ Longest: 24

E. coli CIP -5934 +5918 0 -1881 -7815 +1910 +7828 K. pneumoniae CIP -1189 +1191 0 -348 -1537 +379 +1570 S. aureus CIP -3064 +3045 0 -937 -4001 +932 +3977 S. pneumoniae CIP -1780 +1785 0 -550 -2330 +535 +2320 @@ -1126,7 +1126,7 @@ Longest: 24

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

 data_1st %>% resistance(AMX)
-# [1] 0.5342728
+# [1] 0.536604

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

 data_1st %>% 
@@ -1141,19 +1141,19 @@ Longest: 24

Hospital A -0.5253802 +0.5429950 Hospital B -0.5367779 +0.5429998 Hospital C -0.5470814 +0.5283993 Hospital D -0.5334627 +0.5222153 @@ -1173,23 +1173,23 @@ Longest: 24

Hospital A -0.5253802 -4669 +0.5429950 +4768 Hospital B -0.5367779 -5574 +0.5429998 +5407 Hospital C -0.5470814 -2347 +0.5283993 +2324 Hospital D -0.5334627 -3093 +0.5222153 +3196 @@ -1211,27 +1211,27 @@ Longest: 24

Escherichia -0.8290467 -0.8963532 -0.9843890 +0.8230710 +0.9053398 +0.9872253 Klebsiella -0.8262850 -0.9095641 -0.9837345 +0.8203822 +0.9076433 +0.9847134 Staphylococcus -0.8307923 -0.9122719 -0.9872532 +0.8287654 +0.9192859 +0.9894393 Streptococcus -0.5351931 +0.5379310 0.0000000 -0.5351931 +0.5379310 diff --git a/docs/articles/AMR_files/figure-html/plot 1-1.png b/docs/articles/AMR_files/figure-html/plot 1-1.png index e63aea5e..74c7a605 100644 Binary files a/docs/articles/AMR_files/figure-html/plot 1-1.png and b/docs/articles/AMR_files/figure-html/plot 1-1.png differ diff --git a/docs/articles/AMR_files/figure-html/plot 3-1.png b/docs/articles/AMR_files/figure-html/plot 3-1.png index 39bcc147..38c86180 100644 Binary files a/docs/articles/AMR_files/figure-html/plot 3-1.png and b/docs/articles/AMR_files/figure-html/plot 3-1.png differ diff --git a/docs/articles/AMR_files/figure-html/plot 4-1.png b/docs/articles/AMR_files/figure-html/plot 4-1.png index b58a3e74..537e4ec2 100644 Binary files a/docs/articles/AMR_files/figure-html/plot 4-1.png and b/docs/articles/AMR_files/figure-html/plot 4-1.png differ diff --git a/docs/articles/AMR_files/figure-html/plot 5-1.png b/docs/articles/AMR_files/figure-html/plot 5-1.png index 5817821c..1d36ff57 100644 Binary files a/docs/articles/AMR_files/figure-html/plot 5-1.png and b/docs/articles/AMR_files/figure-html/plot 5-1.png differ diff --git a/docs/articles/EUCAST.html b/docs/articles/EUCAST.html index d1e919d3..83aad23a 100644 --- a/docs/articles/EUCAST.html +++ b/docs/articles/EUCAST.html @@ -12,7 +12,7 @@ - + @@ -39,7 +39,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046
diff --git a/docs/articles/MDR.html b/docs/articles/MDR.html index c638f0e5..5d6c140f 100644 --- a/docs/articles/MDR.html +++ b/docs/articles/MDR.html @@ -12,7 +12,7 @@ - + @@ -39,7 +39,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046
@@ -311,17 +311,17 @@ Unique: 2

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

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

@@ -354,40 +354,40 @@ Unique: 5

1 Mono-resistant -3214 -64.28% -3214 -64.28% +3219 +64.38% +3219 +64.38% 2 Negative -997 -19.94% -4211 -84.22% +982 +19.64% +4201 +84.02% 3 Multi-drug-resistant -442 -8.84% -4653 -93.06% +434 +8.68% +4635 +92.70% 4 Poly-resistant -239 -4.78% -4892 -97.84% +251 +5.02% +4886 +97.72% 5 Extensively drug-resistant -108 -2.16% +114 +2.28% 5000 100.00% diff --git a/docs/articles/PCA.html b/docs/articles/PCA.html index 58207a79..4d16497f 100644 --- a/docs/articles/PCA.html +++ b/docs/articles/PCA.html @@ -12,7 +12,7 @@ - + @@ -39,7 +39,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/articles/SPSS.html b/docs/articles/SPSS.html index 110bc6fa..8cfee5fe 100644 --- a/docs/articles/SPSS.html +++ b/docs/articles/SPSS.html @@ -12,7 +12,7 @@ - + @@ -39,7 +39,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 @@ -193,7 +193,7 @@

How to import data from SPSS / SAS / Stata

Matthijs S. Berends

-

24 December 2020

+

26 December 2020

Source: vignettes/SPSS.Rmd diff --git a/docs/articles/WHONET.html b/docs/articles/WHONET.html index 1e024b43..bdf56142 100644 --- a/docs/articles/WHONET.html +++ b/docs/articles/WHONET.html @@ -12,7 +12,7 @@ - + @@ -39,7 +39,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/articles/benchmarks.html b/docs/articles/benchmarks.html index 2da29ea7..5d223b31 100644 --- a/docs/articles/benchmarks.html +++ b/docs/articles/benchmarks.html @@ -12,7 +12,7 @@ - + @@ -39,7 +39,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 @@ -227,34 +227,20 @@ times = 10) print(S.aureus, unit = "ms", signif = 2) # Unit: milliseconds -# expr min lq mean median uq max -# as.mo("sau") 9.9 12.0 15.0 13.0 13.0 42.0 -# as.mo("stau") 100.0 100.0 130.0 120.0 140.0 190.0 -# as.mo("STAU") 110.0 110.0 130.0 130.0 140.0 150.0 -# as.mo("staaur") 9.8 12.0 26.0 13.0 41.0 60.0 -# as.mo("STAAUR") 11.0 11.0 15.0 13.0 13.0 41.0 -# as.mo("S. aureus") 26.0 28.0 50.0 58.0 63.0 75.0 -# as.mo("S aureus") 26.0 27.0 46.0 51.0 60.0 67.0 -# as.mo("Staphylococcus aureus") 1.9 2.2 2.5 2.5 2.8 3.1 -# as.mo("Staphylococcus aureus (MRSA)") 870.0 880.0 1100.0 910.0 1000.0 2400.0 -# as.mo("Sthafilokkockus aaureuz") 360.0 370.0 400.0 380.0 420.0 540.0 -# as.mo("MRSA") 9.7 11.0 17.0 12.0 13.0 66.0 -# as.mo("VISA") 19.0 19.0 36.0 35.0 53.0 56.0 -# as.mo("VRSA") 17.0 20.0 20.0 21.0 21.0 23.0 -# neval -# 10 -# 10 -# 10 -# 10 -# 10 -# 10 -# 10 -# 10 -# 10 -# 10 -# 10 -# 10 -# 10
+# expr min lq mean median uq max neval +# as.mo("sau") 9.9 11 19.0 12.0 13.0 47.0 10 +# as.mo("stau") 100.0 110 130.0 130.0 140.0 150.0 10 +# as.mo("STAU") 110.0 110 130.0 140.0 140.0 150.0 10 +# as.mo("staaur") 11.0 11 15.0 12.0 13.0 40.0 10 +# as.mo("STAAUR") 12.0 12 21.0 13.0 40.0 46.0 10 +# as.mo("S. aureus") 26.0 31 45.0 34.0 60.0 86.0 10 +# as.mo("S aureus") 26.0 29 36.0 31.0 33.0 58.0 10 +# as.mo("Staphylococcus aureus") 1.6 2 2.3 2.3 2.7 2.8 10 +# as.mo("Staphylococcus aureus (MRSA)") 880.0 900 910.0 910.0 920.0 950.0 10 +# as.mo("Sthafilokkockus aaureuz") 370.0 370 380.0 380.0 380.0 400.0 10 +# as.mo("MRSA") 9.9 11 18.0 13.0 14.0 47.0 10 +# as.mo("VISA") 17.0 19 29.0 21.0 48.0 50.0 10 +# as.mo("VRSA") 16.0 19 29.0 20.0 47.0 55.0 10

In the table above, all measurements are shown in milliseconds (thousands of seconds). A value of 5 milliseconds means it can determine 200 input values per second. It case of 100 milliseconds, this is only 10 input values per second. It is clear that accepted taxonomic names are extremely fast, but some variations can take up to 500-1000 times as much time.

To improve performance, two important calculations take almost no time at all: repetitive results and already precalculated results.

@@ -284,8 +270,8 @@ print(run_it, unit = "ms", signif = 3) # Unit: milliseconds # expr min lq mean median uq max neval -# mo_name(x) 134 167 201 179 207 310 10 -

So getting official taxonomic names of 2,000,000 (!!) items consisting of 90 unique values only takes 0.179 seconds. You only lose time on your unique input values.

+# mo_name(x) 136 169 210 198 247 317 10 +

So getting official taxonomic names of 2,000,000 (!!) items consisting of 90 unique values only takes 0.198 seconds. You only lose time on your unique input values.

@@ -299,10 +285,10 @@ print(run_it, unit = "ms", signif = 3) # Unit: milliseconds # expr min lq mean median uq max neval -# A 7.59 7.93 8.24 8.09 8.66 9.06 10 -# B 23.60 23.70 29.20 24.30 27.10 66.10 10 -# C 1.84 2.13 2.22 2.19 2.35 2.62 10

-

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

+# A 7.21 7.32 7.92 7.69 8.49 9.43 10 +# B 22.60 23.50 28.90 24.70 26.10 69.20 10 +# C 1.87 1.92 2.10 2.08 2.27 2.34 10 +

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

 run_it <- microbenchmark(A = mo_species("aureus"),
                          B = mo_genus("Staphylococcus"),
@@ -316,14 +302,14 @@
 print(run_it, unit = "ms", signif = 3)
 # Unit: milliseconds
 #  expr  min   lq mean median   uq  max neval
-#     A 1.69 1.77 1.82   1.83 1.86 1.92    10
-#     B 1.78 1.79 1.89   1.91 1.95 2.06    10
-#     C 1.74 1.79 1.88   1.87 1.94 2.06    10
-#     D 1.75 1.77 1.94   1.95 1.99 2.41    10
-#     E 1.70 1.75 1.84   1.81 1.87 2.08    10
-#     F 1.66 1.70 1.76   1.74 1.80 1.89    10
-#     G 1.68 1.70 1.82   1.75 1.93 2.09    10
-#     H 1.66 1.69 1.75   1.74 1.80 1.92    10
+# A 1.34 1.59 1.66 1.65 1.74 2.18 10 +# B 1.34 1.63 1.73 1.72 1.85 2.31 10 +# C 1.41 1.61 1.65 1.65 1.72 1.83 10 +# D 1.59 1.63 1.77 1.77 1.89 2.03 10 +# E 1.33 1.60 1.68 1.65 1.73 2.08 10 +# F 1.31 1.34 1.56 1.52 1.71 2.11 10 +# G 1.34 1.60 1.75 1.64 1.76 2.74 10 +# H 1.32 1.38 1.57 1.63 1.71 1.78 10

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

@@ -350,14 +336,14 @@ times = 100) print(run_it, unit = "ms", signif = 4) # Unit: milliseconds -# expr min lq mean median uq max neval -# en 15.91 16.98 21.87 17.54 18.34 168.50 100 -# de 18.98 20.14 26.30 20.74 22.64 66.68 100 -# nl 31.02 32.71 37.56 33.84 35.81 82.77 100 -# es 19.13 20.06 22.96 20.54 21.42 65.26 100 -# it 18.90 19.84 24.26 20.59 22.80 60.30 100 -# fr 18.89 19.92 23.46 20.49 21.72 62.85 100 -# pt 18.90 19.99 23.80 20.70 22.17 61.42 100
+# expr min lq mean median uq max neval +# en 15.73 16.35 20.85 16.74 17.71 56.56 100 +# de 18.96 19.62 22.32 19.86 20.46 59.58 100 +# nl 31.06 31.91 37.31 32.78 34.57 75.58 100 +# es 18.92 19.59 23.43 19.92 20.42 62.72 100 +# it 18.80 19.36 22.59 19.74 20.54 62.72 100 +# fr 18.88 19.53 23.89 19.85 20.91 61.56 100 +# pt 18.89 19.51 21.46 19.87 20.29 59.12 100

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

diff --git a/docs/articles/benchmarks_files/figure-html/unnamed-chunk-4-1.png b/docs/articles/benchmarks_files/figure-html/unnamed-chunk-4-1.png index e0037178..19a9dea9 100644 Binary files a/docs/articles/benchmarks_files/figure-html/unnamed-chunk-4-1.png and b/docs/articles/benchmarks_files/figure-html/unnamed-chunk-4-1.png differ diff --git a/docs/articles/datasets.html b/docs/articles/datasets.html index 6b0d3dac..a8e6ad88 100644 --- a/docs/articles/datasets.html +++ b/docs/articles/datasets.html @@ -12,7 +12,7 @@ - + @@ -39,7 +39,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/articles/index.html b/docs/articles/index.html index d9882af7..ac6f49d0 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -19,8 +19,8 @@ + - @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9045 + 1.4.0.9046 diff --git a/docs/articles/resistance_predict.html b/docs/articles/resistance_predict.html index 82c59521..79bf768c 100644 --- a/docs/articles/resistance_predict.html +++ b/docs/articles/resistance_predict.html @@ -12,7 +12,7 @@ - + @@ -39,7 +39,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/articles/welcome_to_AMR.html b/docs/articles/welcome_to_AMR.html index afd13571..7e649944 100644 --- a/docs/articles/welcome_to_AMR.html +++ b/docs/articles/welcome_to_AMR.html @@ -12,7 +12,7 @@ - + @@ -39,7 +39,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/authors.html b/docs/authors.html index d3d4c60a..5b87ff78 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -19,8 +19,8 @@ + - @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9045 + 1.4.0.9046 diff --git a/docs/countries.png b/docs/countries.png index 5b995680..587eec03 100644 Binary files a/docs/countries.png and b/docs/countries.png differ diff --git a/docs/countries_large.png b/docs/countries_large.png index 5b77adb7..b9ee0ea5 100644 Binary files a/docs/countries_large.png and b/docs/countries_large.png differ diff --git a/docs/index.html b/docs/index.html index f96c6373..9618e3b2 100644 --- a/docs/index.html +++ b/docs/index.html @@ -12,7 +12,7 @@ - + @@ -43,7 +43,7 @@ AMR (for R) - 1.4.0.9045 + 1.4.0.9046 @@ -210,7 +210,7 @@ Since you are one of our users, we would like to know how you use the package an

This package is fully independent of any other R package and works on Windows, macOS and Linux with all versions of R since R-3.0.0 (April 2013). It was designed to work in any setting, including those with very limited resources. It was created for both routine data analysis and academic research at the Faculty of Medical Sciences of the University of Groningen, in collaboration with non-profit organisations Certe Medical Diagnostics and Advice and University Medical Center Groningen. This R package is actively maintained and is free software (see Copyright).

- Used in 135 countries
Since its first public release in early 2018, this package has been downloaded from 135 countries. Click the map to enlarge and to see the country names. + Used in 138 countries
Since its first public release in early 2018, this package has been downloaded from 138 countries. Click the map to enlarge and to see the country names.

@@ -222,9 +222,9 @@ Since you are one of our users, we would like to know how you use the package an library(dplyr) example_isolates %>% - mutate(mo = mo_fullname(mo)) %>% - filter(mo_is_gram_negative(), mo_is_intrinsic_resistant(ab = "cefotax")) %>% - select(mo, aminoglycosides(), carbapenems()) + mutate(mo = mo_fullname(mo)) %>% + filter(mo_is_gram_negative(), mo_is_intrinsic_resistant(ab = "cefotax")) %>% + select(mo, aminoglycosides(), carbapenems()) #> NOTE: Using column 'mo' as input for mo_is_gram_negative() #> NOTE: Using column 'mo' as input for mo_is_intrinsic_resistant() #> Selecting aminoglycosides: 'AMK' (amikacin), 'GEN' (gentamicin), @@ -411,7 +411,7 @@ Since you are one of our users, we would like to know how you use the package an
  • It analyses the data with convenient functions that use well-known methods.

    diff --git a/docs/news/index.html b/docs/news/index.html index a26361bd..1c36c146 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -19,8 +19,8 @@ + - @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9045 + 1.4.0.9046
  • @@ -236,26 +236,26 @@ Source: NEWS.md -
    -

    -AMR 1.4.0.9045 Unreleased +
    +

    +AMR 1.4.0.9046 Unreleased

    -
    +

    -Last updated: 25 December 2020 +Last updated: 27 December 2020

    New

  • Functions mo_is_gram_negative() and mo_is_gram_positive() as wrappers around mo_gramstain(). They always return TRUE or FALSE (except when the input is NA or the MO code is UNKNOWN), thus always return FALSE for species outside the taxonomic kingdom of Bacteria.

  • Function mo_is_intrinsic_resistant() to test for intrinsic resistance, based on EUCAST Intrinsic Resistance and Unusual Phenotypes v3.2 from 2020.

  • @@ -279,15 +279,15 @@
  • -

    Some functions are now context-aware when used inside dplyr verbs, such as filter(), mutate() and summarise(). This means that then the data argument does not need to be set anymore. This is the case for the new functions mo_is_gram_negative(), mo_is_gram_positive(), mo_is_intrinsic_resistant() and for the existing functions first_isolate(), key_antibiotics(), mdro(), brmo(), mrgn(), mdr_tb(), mdr_cmi2012(), eucast_exceptional_phenotypes(). This was already the case for antibiotic selection functions (such as using penicillins() in dplyr::select()).

    +

    Some functions are now context-aware when used inside dplyr verbs, such as filter(), mutate() and summarise(). This means that then the data argument does not need to be set anymore. This is the case for the new functions mo_is_gram_negative(), mo_is_gram_positive(), mo_is_intrinsic_resistant() and for the existing functions first_isolate(), key_antibiotics(), mdro(), brmo(), mrgn(), mdr_tb(), mdr_cmi2012(), eucast_exceptional_phenotypes(). This was already the case for antibiotic selection functions (such as using penicillins() in dplyr::select()).

     
     # to select first isolates that are Gram-negative 
     # and view results of cephalosporins and aminoglycosides:
     library(dplyr)
     example_isolates %>%
    -  filter(first_isolate(), mo_is_gram_negative()) %>% 
    -  select(mo, cephalosporins(), aminoglycosides()) %>% 
    +  filter(first_isolate(), mo_is_gram_negative()) %>% 
    +  select(mo, cephalosporins(), aminoglycosides()) %>% 
       as_tibble()
  • For all function arguments in the code, it is now defined what the exact type of user input should be (inspired by the typed package). If the user input for a certain function does not meet the requirements for a specific argument (such as the class or length), an informative error will be thrown. This makes the package more robust and the use of it more reproducible and reliable. In total, more than 420 arguments were defined.

  • @@ -337,8 +337,8 @@ library(AMR) library(dplyr) intrinsic_resistant %>% - filter(antibiotic == "Vancomycin", microorganism %like% "Enterococcus") %>% - pull(microorganism) + filter(antibiotic == "Vancomycin", microorganism %like% "Enterococcus") %>% + pull(microorganism) #> [1] "Enterococcus casseliflavus" "Enterococcus gallinarum"
  • Support for veterinary ATC codes

  • @@ -354,16 +354,16 @@

    Improvements for as.rsi():

    • -

      Support for using dplyr’s across() to interpret MIC values or disk zone diameters, which also automatically determines the column with microorganism names or codes.

      +

      Support for using dplyr’s across() to interpret MIC values or disk zone diameters, which also automatically determines the column with microorganism names or codes.

       
       # until dplyr 1.0.0
      -your_data %>% mutate_if(is.mic, as.rsi)
      -your_data %>% mutate_if(is.disk, as.rsi)
      +your_data %>% mutate_if(is.mic, as.rsi)
      +your_data %>% mutate_if(is.disk, as.rsi)
       
       # since dplyr 1.0.0
      -your_data %>% mutate(across(where(is.mic), as.rsi))
      -your_data %>% mutate(across(where(is.disk), as.rsi))
      +your_data %>% mutate(across(where(is.mic), as.rsi)) +your_data %>% mutate(across(where(is.disk), as.rsi))
  • Cleaning columns in a data.frame now allows you to specify those columns with tidy selection, e.g. as.rsi(df, col1:col9)

  • Big speed improvement for interpreting MIC values and disk zone diameters. When interpreting 5,000 MIC values of two antibiotics (10,000 values in total), our benchmarks showed a total run time going from 80.7-85.1 seconds to 1.8-2.0 seconds.

  • @@ -433,14 +433,14 @@
    • Function ab_from_text() to retrieve antimicrobial drug names, doses and forms of administration from clinical texts in e.g. health care records, which also corrects for misspelling since it uses as.ab() internally

    • -

      Tidyverse selection helpers for antibiotic classes, that help to select the columns of antibiotics that are of a specific antibiotic class, without the need to define the columns or antibiotic abbreviations. They can be used in any function that allows selection helpers, like dplyr::select() and tidyr::pivot_longer():

      +

      Tidyverse selection helpers for antibiotic classes, that help to select the columns of antibiotics that are of a specific antibiotic class, without the need to define the columns or antibiotic abbreviations. They can be used in any function that allows selection helpers, like dplyr::select() and tidyr::pivot_longer():

       
       library(dplyr)
       
       # Columns 'IPM' and 'MEM' are in the example_isolates data set
       example_isolates %>% 
      -  select(carbapenems())
      +  select(carbapenems())
       #> Selecting carbapenems: `IPM` (imipenem), `MEM` (meropenem)
    • Added mo_domain() as an alias to mo_kingdom()

    • @@ -622,14 +622,14 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
      • Fixed important floating point error for some MIC comparisons in EUCAST 2020 guideline

      • -

        Interpretation from MIC values (and disk zones) to R/SI can now be used with mutate_at() of the dplyr package:

        +

        Interpretation from MIC values (and disk zones) to R/SI can now be used with mutate_at() of the dplyr package:

         
         yourdata %>% 
        -  mutate_at(vars(antibiotic1:antibiotic25), as.rsi, mo = "E. coli")
        +  mutate_at(vars(antibiotic1:antibiotic25), as.rsi, mo = "E. coli")
         
         yourdata %>% 
        -  mutate_at(vars(antibiotic1:antibiotic25), as.rsi, mo = .$mybacteria)
        + mutate_at(vars(antibiotic1:antibiotic25), as.rsi, mo = .$mybacteria)
  • Added antibiotic abbreviations for a laboratory manufacturer (GLIMS) for cefuroxime, cefotaxime, ceftazidime, cefepime, cefoxitin and trimethoprim/sulfamethoxazole

  • Added uti (as abbreviation of urinary tract infections) as argument to as.rsi(), so interpretation of MIC values and disk zones can be made dependent on isolates specifically from UTIs

  • @@ -750,10 +750,10 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ library(dplyr) example_isolates %>% - group_by(bug = mo_name(mo)) %>% - summarise(amoxicillin = resistance(AMX), + group_by(bug = mo_name(mo)) %>% + summarise(amoxicillin = resistance(AMX), amox_clav = resistance(AMC)) %>% - filter(!is.na(amoxicillin) | !is.na(amox_clav))

    + filter(!is.na(amoxicillin) | !is.na(amox_clav))
  • Support for a new MDRO guideline: Magiorakos AP, Srinivasan A et al. “Multidrug-resistant, extensively drug-resistant and pandrug-resistant bacteria: an international expert proposal for interim standard definitions for acquired resistance.” Clinical Microbiology and Infection (2012).

    @@ -922,7 +922,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ # (run this on your own console, as this page does not support colour printing) library(dplyr) example_isolates %>% - select(mo:AMC) %>% + select(mo:AMC) %>% as_tibble()
  • @@ -1003,7 +1003,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
     
     septic_patients %>%
    -  select(AMX, CIP) %>%
    +  select(AMX, CIP) %>%
       rsi_df()
     #      antibiotic  interpretation      value  isolates
     # 1   Amoxicillin              SI  0.4442636       546
    @@ -1139,7 +1139,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
       boxplot()
     # grouped boxplots:
     septic_patients %>% 
    -  group_by(hospital_id) %>% 
    +  group_by(hospital_id) %>% 
       freq(age) %>%
       boxplot()
    @@ -1288,9 +1288,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
     
     septic_patients %>%
    -  mutate(only_firsts = first_isolate(septic_patients, ...)) %>%
    -  filter(only_firsts == TRUE) %>%
    -  select(-only_firsts)
    + mutate(only_firsts = first_isolate(septic_patients, ...)) %>% + filter(only_firsts == TRUE) %>% + select(-only_firsts)
  • New function availability() to check the number of available (non-empty) results in a data.frame

  • New vignettes about how to conduct AMR analysis, predict antimicrobial resistance, use the G-test and more. These are also available (and even easier readable) on our website: https://msberends.gitlab.io/AMR.

  • @@ -1400,7 +1400,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ # Determine genus of microorganisms (mo) in `septic_patients` data set: # OLD WAY septic_patients %>% - mutate(genus = mo_genus(mo)) %>% + mutate(genus = mo_genus(mo)) %>% freq(genus) # NEW WAY septic_patients %>% @@ -1408,7 +1408,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ # Even supports grouping variables: septic_patients %>% - group_by(gender) %>% + group_by(gender) %>% freq(mo_genus(mo))
  • Header info is now available as a list, with the header function

  • @@ -1419,7 +1419,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
  • Fix for header text where all observations are NA

  • New argument droplevels to exclude empty factor levels when input is a factor

  • Factor levels will be in header when present in input data (maximum of 5)

  • -
  • Fix for using select() on frequency tables

  • +
  • Fix for using select() on frequency tables

  • Function scale_y_percent() now contains the limits argument
  • @@ -1499,7 +1499,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
     
     septic_patients %>% 
    -  group_by(hospital_id) %>% 
    +  group_by(hospital_id) %>% 
       freq(gender)
  • @@ -1508,7 +1508,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ septic_patients %>% freq(hospital_id) %>% - select(-count, -cum_count) # only get item, percent, cum_percent + select(-count, -cum_count) # only get item, percent, cum_percent
  • Check for hms::is.hms

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

  • @@ -1672,7 +1672,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/

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

     
    -septic_patients %>% select(amox, cipr) %>% count_IR()
    +septic_patients %>% select(amox, cipr) %>% count_IR()
     # which is the same as:
     septic_patients %>% count_IR(amox, cipr)
     
    @@ -1858,7 +1858,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
     
    • Full support for Windows, Linux and macOS
    • Full support for old R versions, only R-3.0.0 (April 2013) or later is needed (needed packages may have other dependencies)
    • -
    • Function n_rsi to count cases where antibiotic test results were available, to be used in conjunction with dplyr::summarise, see ?rsi
    • +
    • Function n_rsi to count cases where antibiotic test results were available, to be used in conjunction with dplyr::summarise, see ?rsi
    • Function guess_bactid to determine the ID of a microorganism based on genus/species or known abbreviations like MRSA
    • Function guess_atc to determine the ATC of an antibiotic based on name, trade name, or known abbreviations
    • Function freq to create frequency tables, with additional info in a header
    • diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index 7281d89d..75b73abf 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: 2020-12-24T23:05Z +last_built: 2020-12-26T23:05Z urls: reference: https://msberends.github.io/AMR//reference article: https://msberends.github.io/AMR//articles diff --git a/docs/reference/AMR-deprecated.html b/docs/reference/AMR-deprecated.html index b4538b60..b0a7f1ea 100644 --- a/docs/reference/AMR-deprecated.html +++ b/docs/reference/AMR-deprecated.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046
    diff --git a/docs/reference/AMR.html b/docs/reference/AMR.html index ebb6f032..c8496e0f 100644 --- a/docs/reference/AMR.html +++ b/docs/reference/AMR.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/WHOCC.html b/docs/reference/WHOCC.html index ded4fc41..74ba73e9 100644 --- a/docs/reference/WHOCC.html +++ b/docs/reference/WHOCC.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/WHONET.html b/docs/reference/WHONET.html index 1a8ce421..54233c88 100644 --- a/docs/reference/WHONET.html +++ b/docs/reference/WHONET.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/ab_from_text.html b/docs/reference/ab_from_text.html index 0472eeb4..3e66899a 100644 --- a/docs/reference/ab_from_text.html +++ b/docs/reference/ab_from_text.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/ab_property.html b/docs/reference/ab_property.html index 45a5413b..51c5c6d6 100644 --- a/docs/reference/ab_property.html +++ b/docs/reference/ab_property.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/age.html b/docs/reference/age.html index 4f34cdb0..6705c9ab 100644 --- a/docs/reference/age.html +++ b/docs/reference/age.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/age_groups.html b/docs/reference/age_groups.html index 78560a2d..1a277aeb 100644 --- a/docs/reference/age_groups.html +++ b/docs/reference/age_groups.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/antibiotic_class_selectors.html b/docs/reference/antibiotic_class_selectors.html index af560fe4..cff9656c 100644 --- a/docs/reference/antibiotic_class_selectors.html +++ b/docs/reference/antibiotic_class_selectors.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/antibiotics.html b/docs/reference/antibiotics.html index 89984a20..81f79ab4 100644 --- a/docs/reference/antibiotics.html +++ b/docs/reference/antibiotics.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/as.ab.html b/docs/reference/as.ab.html index 60cd57f6..2af88481 100644 --- a/docs/reference/as.ab.html +++ b/docs/reference/as.ab.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/as.disk.html b/docs/reference/as.disk.html index 615cf86d..cf0f59c6 100644 --- a/docs/reference/as.disk.html +++ b/docs/reference/as.disk.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/as.mic.html b/docs/reference/as.mic.html index e94aea08..d5260a2e 100644 --- a/docs/reference/as.mic.html +++ b/docs/reference/as.mic.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/as.mo.html b/docs/reference/as.mo.html index e6cd3110..becd1295 100644 --- a/docs/reference/as.mo.html +++ b/docs/reference/as.mo.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/as.rsi.html b/docs/reference/as.rsi.html index 383cfd56..55e2cc3f 100644 --- a/docs/reference/as.rsi.html +++ b/docs/reference/as.rsi.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/atc_online.html b/docs/reference/atc_online.html index 7cf363da..3281db16 100644 --- a/docs/reference/atc_online.html +++ b/docs/reference/atc_online.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/availability.html b/docs/reference/availability.html index 0fec9c5c..af2e53a7 100644 --- a/docs/reference/availability.html +++ b/docs/reference/availability.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/bug_drug_combinations.html b/docs/reference/bug_drug_combinations.html index 49aeb815..799d2f78 100644 --- a/docs/reference/bug_drug_combinations.html +++ b/docs/reference/bug_drug_combinations.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/catalogue_of_life.html b/docs/reference/catalogue_of_life.html index c16d361f..f3e3bc1c 100644 --- a/docs/reference/catalogue_of_life.html +++ b/docs/reference/catalogue_of_life.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/catalogue_of_life_version.html b/docs/reference/catalogue_of_life_version.html index 32098601..b35010b7 100644 --- a/docs/reference/catalogue_of_life_version.html +++ b/docs/reference/catalogue_of_life_version.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/count.html b/docs/reference/count.html index 463bdf32..564fe975 100644 --- a/docs/reference/count.html +++ b/docs/reference/count.html @@ -19,8 +19,8 @@ + - @@ -83,7 +83,7 @@ count_resistant() should be used to count resistant isolates, count_susceptible( AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/eucast_rules.html b/docs/reference/eucast_rules.html index fe376b6d..07386e56 100644 --- a/docs/reference/eucast_rules.html +++ b/docs/reference/eucast_rules.html @@ -19,8 +19,8 @@ + - @@ -83,7 +83,7 @@ To improve the interpretation of the antibiogram before EUCAST rules are applied AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/example_isolates.html b/docs/reference/example_isolates.html index 1cd40c8c..70b373bb 100644 --- a/docs/reference/example_isolates.html +++ b/docs/reference/example_isolates.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/example_isolates_unclean.html b/docs/reference/example_isolates_unclean.html index 4d71bf99..fb89c297 100644 --- a/docs/reference/example_isolates_unclean.html +++ b/docs/reference/example_isolates_unclean.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/filter_ab_class.html b/docs/reference/filter_ab_class.html index 23ff0f43..18e02a80 100644 --- a/docs/reference/filter_ab_class.html +++ b/docs/reference/filter_ab_class.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/first_isolate.html b/docs/reference/first_isolate.html index 6a2736ea..8e8e11b9 100644 --- a/docs/reference/first_isolate.html +++ b/docs/reference/first_isolate.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/g.test.html b/docs/reference/g.test.html index 75e0b929..ae075c6e 100644 --- a/docs/reference/g.test.html +++ b/docs/reference/g.test.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/get_episode.html b/docs/reference/get_episode.html new file mode 100644 index 00000000..9d14c8cd --- /dev/null +++ b/docs/reference/get_episode.html @@ -0,0 +1,378 @@ + + + + + + + + +Determine (new) episodes for patients — get_episode • AMR (for R) + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
    +
    + + + + +
    + +
    +
    + + +
    +

    These functions determine which items in a vector can be considered (the start of) a new episode, based on the argument episode_days. This can be used to determine clinical episodes for any epidemiological analysis. The get_episode() function returns the index number of the episode per group, while the is_new_episode() function returns values TRUE/FALSE to indicate whether an item in a vector is the start of a new episode.

    +
    + +
    get_episode(x, episode_days, ...)
    +
    +is_new_episode(x, episode_days, ...)
    + +

    Arguments

    + + + + + + + + + + + + + + +
    x

    vector of dates (class Date or POSIXt)

    episode_days

    length of the required episode in days, please see Details

    ...

    arguments passed on to as.Date()

    + +

    Value

    + + +
      +
    • get_episode(): a double vector

    • +
    • is_new_episode(): a logical vector

    • +
    + +

    Details

    + +

    Dates are first sorted from old to new. The oldest date will mark the start of the first episode. After this date, the next date will be marked that is at least episode_days days later than the start of the first episode. From that second marked date on, the next date will be marked that is at least episode_days days later than the start of the second episode which will be the start of the third episode, and so on. Before the vector is being returned, the original order will be restored.

    +

    The first_isolate() function is a wrapper around the is_new_episode() function, but is more efficient for data sets containing microorganism codes or names.

    +

    The dplyr package is not required for these functions to work, but these functions support variable grouping and work conveniently inside dplyr verbs such as filter(), mutate() and summarise().

    +

    Stable lifecycle

    + + + +


    +The lifecycle of this function is stable. In a stable function, major changes are unlikely. This means that the unlying code will generally evolve by adding new arguments; removing arguments or changing the meaning of existing arguments will be avoided.

    +

    If the unlying code needs breaking changes, they will occur gradually. For example, a argument will be deprecated and first continue to work, but will emit an message informing you of the change. Next, typically after at least one newly released version on CRAN, the message will be transformed to an error.

    +

    Read more on our website!

    + + + +

    On our website https://msberends.github.io/AMR/ you can find a comprehensive tutorial about how to conduct AMR analysis, the complete documentation of all functions and an example analysis using WHONET data. As we would like to better understand the backgrounds and needs of our users, please participate in our survey!

    +

    See also

    + + + +

    Examples

    +
    # `example_isolates` is a dataset available in the AMR package.
    +# See ?example_isolates.
    +
    +get_episode(example_isolates$date, episode_days = 60)
    +is_new_episode(example_isolates$date, episode_days = 60)
    +
    +# filter on results from the third 60-day episode using base R
    +example_isolates[which(get_episode(example_isolates$date, 60) == 3), ]
    +
    +# \donttest{
    +if (require("dplyr")) {
    +  # is_new_episode() can also be used in dplyr verbs to determine patient
    +  # episodes based on any (combination of) grouping variables:
    +  example_isolates %>%
    +    mutate(condition = sample(x = c("A", "B", "C"), 
    +                              size = 2000,
    +                              replace = TRUE)) %>% 
    +    group_by(condition) %>%
    +    mutate(new_episode = is_new_episode(date, 365))
    +    
    +  example_isolates %>%
    +    group_by(hospital_id, patient_id) %>%
    +    transmute(date, 
    +              patient_id,
    +              new_index = get_episode(date, 60),
    +              new_logical = is_new_episode(date, 60))
    +  
    +  
    +  example_isolates %>%
    +    group_by(hospital_id) %>% 
    +    summarise(patients = n_distinct(patient_id),
    +              n_episodes_365 = sum(is_new_episode(date, episode_days = 365)),
    +              n_episodes_60  = sum(is_new_episode(date, episode_days = 60)),
    +              n_episodes_30  = sum(is_new_episode(date, episode_days = 30)))
    +    
    +    
    +  # grouping on patients and microorganisms leads to the same results
    +  # as first_isolate():
    +  x <- example_isolates %>%
    +    filter(first_isolate(., include_unknown = TRUE))
    +    
    +  y <- example_isolates %>%
    +    group_by(patient_id, mo) %>%
    +    filter(is_new_episode(date, 365))
    +
    +  identical(x$patient_id, y$patient_id)
    +  
    +  # but is_new_episode() has a lot more flexibility than first_isolate(),
    +  # since you can now group on anything that seems relevant:
    +  example_isolates %>%
    +    group_by(patient_id, mo, hospital_id, ward_icu) %>%
    +    mutate(flag_episode = is_new_episode(date, 365))
    +}
    +# }
    +
    +
    + +
    + + + +
    + + + + + + + + diff --git a/docs/reference/ggplot_pca.html b/docs/reference/ggplot_pca.html index 63a705d3..0d086ee2 100644 --- a/docs/reference/ggplot_pca.html +++ b/docs/reference/ggplot_pca.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/ggplot_rsi.html b/docs/reference/ggplot_rsi.html index d4e12898..c30a6bd4 100644 --- a/docs/reference/ggplot_rsi.html +++ b/docs/reference/ggplot_rsi.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/guess_ab_col.html b/docs/reference/guess_ab_col.html index 0da9b562..b13893b7 100644 --- a/docs/reference/guess_ab_col.html +++ b/docs/reference/guess_ab_col.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/index.html b/docs/reference/index.html index dba1ca14..6a7a941f 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -19,8 +19,8 @@ + - @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9045 + 1.4.0.9046 @@ -455,7 +455,7 @@

    Analysing data: antimicrobial resistance

    -

    Use these function for the analysis part. You can use susceptibility() or resistance() on any antibiotic column. Be sure to first select the isolates that are appropiate for analysis, by using first_isolate() or is_new_episode(). You can also filter your data on certain resistance in certain antibiotic classes (filter_ab_class()), or determine multi-drug resistant microorganisms (MDRO, mdro()).

    +

    Use these function for the analysis part. You can use susceptibility() or resistance() on any antibiotic column. Be sure to first select the isolates that are appropiate for analysis, by using first_isolate() or is_new_episode(). You can also filter your data on certain resistance in certain antibiotic classes (filter_ab_class()), or determine multi-drug resistant microorganisms (MDRO, mdro()).

    @@ -478,7 +478,7 @@ -

    is_new_episode()

    +

    get_episode() is_new_episode()

    Determine (new) episodes for patients

    diff --git a/docs/reference/intrinsic_resistant.html b/docs/reference/intrinsic_resistant.html index 87769278..6b9b6723 100644 --- a/docs/reference/intrinsic_resistant.html +++ b/docs/reference/intrinsic_resistant.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/is_new_episode.html b/docs/reference/is_new_episode.html index 6a1f8a48..ea7ec263 100644 --- a/docs/reference/is_new_episode.html +++ b/docs/reference/is_new_episode.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/join.html b/docs/reference/join.html index dc358759..e70d453d 100644 --- a/docs/reference/join.html +++ b/docs/reference/join.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/key_antibiotics.html b/docs/reference/key_antibiotics.html index 0e63e308..93209875 100644 --- a/docs/reference/key_antibiotics.html +++ b/docs/reference/key_antibiotics.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/kurtosis.html b/docs/reference/kurtosis.html index 6758774a..f9dacfb5 100644 --- a/docs/reference/kurtosis.html +++ b/docs/reference/kurtosis.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/lifecycle.html b/docs/reference/lifecycle.html index 6e274f03..7b22cef1 100644 --- a/docs/reference/lifecycle.html +++ b/docs/reference/lifecycle.html @@ -19,8 +19,8 @@ + - @@ -84,7 +84,7 @@ This page contains a section for every lifecycle (with text borrowed from the af AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/like.html b/docs/reference/like.html index 81437461..31a8a7cf 100644 --- a/docs/reference/like.html +++ b/docs/reference/like.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/mdro.html b/docs/reference/mdro.html index 56e43601..c30c713a 100644 --- a/docs/reference/mdro.html +++ b/docs/reference/mdro.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/microorganisms.codes.html b/docs/reference/microorganisms.codes.html index 9d54a7c9..033c8fbd 100644 --- a/docs/reference/microorganisms.codes.html +++ b/docs/reference/microorganisms.codes.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/microorganisms.html b/docs/reference/microorganisms.html index 30d7a857..100f9da6 100644 --- a/docs/reference/microorganisms.html +++ b/docs/reference/microorganisms.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/microorganisms.old.html b/docs/reference/microorganisms.old.html index 4c51cc61..9b64ce45 100644 --- a/docs/reference/microorganisms.old.html +++ b/docs/reference/microorganisms.old.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/mo_matching_score.html b/docs/reference/mo_matching_score.html index 8b312240..6578ef4d 100644 --- a/docs/reference/mo_matching_score.html +++ b/docs/reference/mo_matching_score.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/mo_property.html b/docs/reference/mo_property.html index 67489484..79617975 100644 --- a/docs/reference/mo_property.html +++ b/docs/reference/mo_property.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/mo_source.html b/docs/reference/mo_source.html index f978e77a..ea585b5b 100644 --- a/docs/reference/mo_source.html +++ b/docs/reference/mo_source.html @@ -19,8 +19,8 @@ + - @@ -83,7 +83,7 @@ This is the fastest way to have your organisation (or analysis) specific codes p AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/pca.html b/docs/reference/pca.html index ce27622b..08f03885 100644 --- a/docs/reference/pca.html +++ b/docs/reference/pca.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/plot.html b/docs/reference/plot.html index 94e68755..65478bdd 100644 --- a/docs/reference/plot.html +++ b/docs/reference/plot.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/proportion.html b/docs/reference/proportion.html index 76be1e6d..da4aa2f9 100644 --- a/docs/reference/proportion.html +++ b/docs/reference/proportion.html @@ -19,8 +19,8 @@ + - @@ -83,7 +83,7 @@ resistance() should be used to calculate resistance, susceptibility() should be AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/random.html b/docs/reference/random.html index fd3565eb..8fe8fa3e 100644 --- a/docs/reference/random.html +++ b/docs/reference/random.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/resistance_predict.html b/docs/reference/resistance_predict.html index f3137959..31fdd23a 100644 --- a/docs/reference/resistance_predict.html +++ b/docs/reference/resistance_predict.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/rsi_translation.html b/docs/reference/rsi_translation.html index 594c9891..bcfe6e26 100644 --- a/docs/reference/rsi_translation.html +++ b/docs/reference/rsi_translation.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/skewness.html b/docs/reference/skewness.html index 96ed23d5..c4d5ab8a 100644 --- a/docs/reference/skewness.html +++ b/docs/reference/skewness.html @@ -19,8 +19,8 @@ + - @@ -83,7 +83,7 @@ When negative ('left-skewed'): the left tail is longer; the mass of the distribu AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/reference/translate.html b/docs/reference/translate.html index 0b4342a0..fcd33ebe 100644 --- a/docs/reference/translate.html +++ b/docs/reference/translate.html @@ -19,8 +19,8 @@ + - @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9044 + 1.4.0.9046 diff --git a/docs/sitemap.xml b/docs/sitemap.xml index 8071036d..30f3a701 100644 --- a/docs/sitemap.xml +++ b/docs/sitemap.xml @@ -84,6 +84,9 @@ https://msberends.github.io/AMR//reference/g.test.html + + https://msberends.github.io/AMR//reference/get_episode.html + https://msberends.github.io/AMR//reference/ggplot_pca.html @@ -96,9 +99,6 @@ https://msberends.github.io/AMR//reference/intrinsic_resistant.html - - https://msberends.github.io/AMR//reference/is_new_episode.html - https://msberends.github.io/AMR//reference/join.html diff --git a/docs/survey.html b/docs/survey.html index daddda6c..d99f5c5a 100644 --- a/docs/survey.html +++ b/docs/survey.html @@ -19,8 +19,8 @@ + - @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9045 + 1.4.0.9046 diff --git a/index.md b/index.md index 22902d66..05362cf6 100644 --- a/index.md +++ b/index.md @@ -18,8 +18,8 @@ This package is [fully independent of any other R package](https://en.wikipedia.

    - Used in 135 countries
    - Since its first public release in early 2018, this package has been downloaded from 135 countries. Click the map to enlarge and to see the country names.

    + Used in 138 countries
    + Since its first public release in early 2018, this package has been downloaded from 138 countries. Click the map to enlarge and to see the country names.

    ##### With `AMR` (for R), there's always a knowledgeable microbiologist by your side! diff --git a/man/is_new_episode.Rd b/man/get_episode.Rd similarity index 65% rename from man/is_new_episode.Rd rename to man/get_episode.Rd index 591e49c9..9e478c7d 100644 --- a/man/is_new_episode.Rd +++ b/man/get_episode.Rd @@ -1,30 +1,36 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/is_new_episode.R -\name{is_new_episode} +% Please edit documentation in R/episode.R +\name{get_episode} +\alias{get_episode} \alias{is_new_episode} \title{Determine (new) episodes for patients} \usage{ -is_new_episode(x, episode_days = 365, ...) +get_episode(x, episode_days, ...) + +is_new_episode(x, episode_days, ...) } \arguments{ \item{x}{vector of dates (class \code{Date} or \code{POSIXt})} -\item{episode_days}{length of the required episode in days, defaults to 365. Every element in the input will return \code{TRUE} after this number of days has passed since the last included date, independent of calendar years. Please see \emph{Details}.} +\item{episode_days}{length of the required episode in days, please see \emph{Details}} \item{...}{arguments passed on to \code{\link[=as.Date]{as.Date()}}} } \value{ -a \link{logical} vector +\itemize{ +\item \code{\link[=get_episode]{get_episode()}}: a \link{double} vector +\item \code{\link[=is_new_episode]{is_new_episode()}}: a \link{logical} vector +} } \description{ -This function determines which items in a vector can be considered (the start of) a new episode, based on the argument \code{episode_days}. This can be used to determine clinical episodes for any epidemiological analysis. +These functions determine which items in a vector can be considered (the start of) a new episode, based on the argument \code{episode_days}. This can be used to determine clinical episodes for any epidemiological analysis. The \code{\link[=get_episode]{get_episode()}} function returns the index number of the episode per group, while the \code{\link[=is_new_episode]{is_new_episode()}} function returns values \code{TRUE}/\code{FALSE} to indicate whether an item in a vector is the start of a new episode. } \details{ Dates are first sorted from old to new. The oldest date will mark the start of the first episode. After this date, the next date will be marked that is at least \code{episode_days} days later than the start of the first episode. From that second marked date on, the next date will be marked that is at least \code{episode_days} days later than the start of the second episode which will be the start of the third episode, and so on. Before the vector is being returned, the original order will be restored. -The \code{\link[=first_isolate]{first_isolate()}} function is a wrapper around the \code{\link[=is_new_episode]{is_new_episode()}} function, but more efficient for data sets containing microorganism codes or names. +The \code{\link[=first_isolate]{first_isolate()}} function is a wrapper around the \code{\link[=is_new_episode]{is_new_episode()}} function, but is more efficient for data sets containing microorganism codes or names. -The \code{dplyr} package is not required for this function to work, but this function works conveniently inside \code{dplyr} verbs such as \code{\link[dplyr:filter]{filter()}}, \code{\link[dplyr:mutate]{mutate()}} and \code{\link[dplyr:summarise]{summarise()}}. +The \code{dplyr} package is not required for these functions to work, but these functions support \link[dplyr:group_by]{variable grouping} and work conveniently inside \code{dplyr} verbs such as \code{\link[dplyr:filter]{filter()}}, \code{\link[dplyr:mutate]{mutate()}} and \code{\link[dplyr:summarise]{summarise()}}. } \section{Stable lifecycle}{ @@ -43,8 +49,12 @@ On our website \url{https://msberends.github.io/AMR/} you can find \href{https:/ # `example_isolates` is a dataset available in the AMR package. # See ?example_isolates. -is_new_episode(example_isolates$date) +get_episode(example_isolates$date, episode_days = 60) is_new_episode(example_isolates$date, episode_days = 60) + +# filter on results from the third 60-day episode using base R +example_isolates[which(get_episode(example_isolates$date, 60) == 3), ] + \donttest{ if (require("dplyr")) { # is_new_episode() can also be used in dplyr verbs to determine patient @@ -54,7 +64,15 @@ if (require("dplyr")) { size = 2000, replace = TRUE)) \%>\% group_by(condition) \%>\% - mutate(new_episode = is_new_episode(date)) + mutate(new_episode = is_new_episode(date, 365)) + + example_isolates \%>\% + group_by(hospital_id, patient_id) \%>\% + transmute(date, + patient_id, + new_index = get_episode(date, 60), + new_logical = is_new_episode(date, 60)) + example_isolates \%>\% group_by(hospital_id) \%>\% @@ -71,7 +89,7 @@ if (require("dplyr")) { y <- example_isolates \%>\% group_by(patient_id, mo) \%>\% - filter(is_new_episode(date)) + filter(is_new_episode(date, 365)) identical(x$patient_id, y$patient_id) @@ -79,7 +97,10 @@ if (require("dplyr")) { # since you can now group on anything that seems relevant: example_isolates \%>\% group_by(patient_id, mo, hospital_id, ward_icu) \%>\% - mutate(flag_episode = is_new_episode(date)) + mutate(flag_episode = is_new_episode(date, 365)) } } } +\seealso{ +\code{\link[=first_isolate]{first_isolate()}} +} diff --git a/pkgdown/logos/countries.png b/pkgdown/logos/countries.png index 5b995680..587eec03 100644 Binary files a/pkgdown/logos/countries.png and b/pkgdown/logos/countries.png differ diff --git a/pkgdown/logos/countries_large.png b/pkgdown/logos/countries_large.png index 5b77adb7..b9ee0ea5 100644 Binary files a/pkgdown/logos/countries_large.png and b/pkgdown/logos/countries_large.png differ diff --git a/tests/testthat/test-count.R b/tests/testthat/test-count.R index f42b8f52..2f63dadb 100644 --- a/tests/testthat/test-count.R +++ b/tests/testthat/test-count.R @@ -79,7 +79,9 @@ test_that("counts work", { ) # warning for speed loss + reset_all_thrown_messages() expect_warning(count_resistant(as.character(example_isolates$AMC))) + reset_all_thrown_messages() expect_warning(count_resistant(example_isolates$AMC, as.character(example_isolates$GEN))) diff --git a/tests/testthat/test-is_new_episode.R b/tests/testthat/test-episode.R similarity index 98% rename from tests/testthat/test-is_new_episode.R rename to tests/testthat/test-episode.R index 87f4d838..90f7606c 100644 --- a/tests/testthat/test-is_new_episode.R +++ b/tests/testthat/test-episode.R @@ -23,7 +23,7 @@ # how to conduct AMR analysis: https://msberends.github.io/AMR/ # # ==================================================================== # -context("is_new_episode.R") +context("episode.R") test_that("new episodes work", { skip_on_cran() diff --git a/tests/testthat/test-filter_ab_class.R b/tests/testthat/test-filter_ab_class.R index 6709c80d..c6d67f12 100644 --- a/tests/testthat/test-filter_ab_class.R +++ b/tests/testthat/test-filter_ab_class.R @@ -28,6 +28,7 @@ context("filter_ab_class.R") test_that("ATC-group filtering works", { skip_on_cran() + library(dplyr) expect_gt(example_isolates %>% filter_ab_class("carbapenem") %>% nrow(), 0) expect_gt(example_isolates %>% filter_aminoglycosides() %>% nrow(), 0) expect_gt(example_isolates %>% filter_carbapenems() %>% nrow(), 0) diff --git a/tests/testthat/test-proportion.R b/tests/testthat/test-proportion.R index 203e2342..438e0072 100755 --- a/tests/testthat/test-proportion.R +++ b/tests/testthat/test-proportion.R @@ -76,11 +76,15 @@ test_that("proportions works", { combination_n = n_rsi(CIP, GEN)) %>% pull(combination_n), c(305, 617, 241, 711)) - + + reset_all_thrown_messages() expect_warning(proportion_R(as.character(example_isolates$AMC))) + reset_all_thrown_messages() expect_warning(proportion_S(as.character(example_isolates$AMC))) + reset_all_thrown_messages() expect_warning(proportion_S(as.character(example_isolates$AMC, example_isolates$GEN))) + reset_all_thrown_messages() expect_warning(n_rsi(as.character(example_isolates$AMC, example_isolates$GEN))) expect_equal(suppressWarnings(n_rsi(as.character(example_isolates$AMC, @@ -105,8 +109,11 @@ test_that("proportions works", { NA_real_) # warning for speed loss + reset_all_thrown_messages() expect_warning(proportion_R(as.character(example_isolates$GEN))) + reset_all_thrown_messages() expect_warning(proportion_I(as.character(example_isolates$GEN))) + reset_all_thrown_messages() expect_warning(proportion_S(example_isolates$AMC, as.character(example_isolates$GEN))) # proportion_df