diff --git a/DESCRIPTION b/DESCRIPTION index 45d1100a..15007eb9 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 1.4.0.9024 -Date: 2020-11-17 +Version: 1.4.0.9025 +Date: 2020-11-23 Title: Antimicrobial Resistance Analysis Authors@R: c( person(role = c("aut", "cre"), diff --git a/NAMESPACE b/NAMESPACE index 1467837b..a4750927 100755 --- a/NAMESPACE +++ b/NAMESPACE @@ -65,8 +65,6 @@ S3method(unique,mo) S3method(unique,rsi) export("%like%") export("%like_case%") -export("%not_like%") -export("%not_like_case%") export(ab_atc) export(ab_atc_group1) export(ab_atc_group2) diff --git a/NEWS.md b/NEWS.md index 5b99ed0a..aeae4f47 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,14 +1,12 @@ -# AMR 1.4.0.9024 -## Last updated: 17 November 2020 +# AMR 1.4.0.9025 +## Last updated: 23 November 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()` and `summarise()` of the `dplyr` package: +* 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: ```r - example_isolates %>% - group_by(hospital_id) %>% - summarise(patients = n_distinct(patient_id), - n_episodes_365 = sum(is_new_episode(episode_days = 365)), - n_episodes_60 = sum(is_new_episode(episode_days = 60))) + example_isolates %>% + group_by(patient_id, hospital_id) %>% + filter(is_new_episode(date, episode_days = 60)) ``` * 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. If you have the `dplyr` package installed, they can even determine the column with microorganisms themselves when used inside `dplyr` verbs: ```r @@ -22,7 +20,6 @@ filter(mo_is_intrinsic_resistant(ab = "Vancomycin")) #> NOTE: Using column `mo` as input for mo_is_intrinsic_resistant() ``` -* Functions `%not_like%` and `%not_like_case%` as wrappers around `%like%` and `%like_case%`. The RStudio addin to insert the text " %like% " as provided in this package now iterates over all like variants. So if you have defined the keyboard shortcut Ctrl/Cmd + L to this addin, it will first insert ` %like% ` and by pressing it again it will be replaced with ` %not_like% `, etc. ### Changed * Reference data used for `as.rsi()` can now be set by the user, using the `reference_data` parameter. This allows for using own interpretation guidelines. @@ -32,6 +29,7 @@ * Updated coagulase-negative staphylococci determination with Becker *et al.* 2020 (PMID 32056452), meaning that the species *S. argensis*, *S. caeli*, *S. debuckii*, *S. edaphicus* and *S. pseudoxylosus* are now all considered CoNS * Fix for using parameter `reference_df` in `as.mo()` and `mo_*()` functions that contain old microbial codes (from previous package versions) * Fix for using `as.rsi()` on a data.frame in older R versions +* `as.rsi()` on a data.frame will not print a message anymore if the values are already clean R/SI values ### Other * All messages and warnings thrown by this package now break sentences on whole words diff --git a/R/aa_helper_functions.R b/R/aa_helper_functions.R index 2c70d9eb..9f685d35 100755 --- a/R/aa_helper_functions.R +++ b/R/aa_helper_functions.R @@ -71,41 +71,7 @@ addin_insert_in <- function() { # No export, no Rd addin_insert_like <- function() { - stop_ifnot_installed("rstudioapi") - # we want Ctrl/Cmd + L to iterate over %like%, %not_like% and %like_case%, so determine context first - - getSourceEditorContext <- import_fn("getSourceEditorContext", "rstudioapi") - insertText <- import_fn("insertText", "rstudioapi") - modifyRange <- import_fn("insertText", "rstudioapi") - document_range <- import_fn("document_range", "rstudioapi") - document_position <- import_fn("document_position", "rstudioapi") - - context <- getSourceEditorContext() - current_row <- context$selection[[1]]$range$end[1] - current_col <- context$selection[[1]]$range$end[2] - current_row_txt <- context$contents[current_row] - - pos_preceded_by <- function(txt) { - substr(current_row_txt, current_col - nchar(txt), current_col) %like% paste0("^", txt) - } - replace_pos <- function(old, with) { - modifyRange(document_range(document_position(current_row, current_col - nchar(old)), - document_position(current_row, current_col)), - text = with, - id = context$id) - } - - if (pos_preceded_by(" %like% ")) { - replace_pos(" %like% ", with = " %not_like% ") - } else if (pos_preceded_by(" %not_like% ")) { - replace_pos(" %not_like% ", with = " %like_case% ") - } else if (pos_preceded_by(" %like_case% ")) { - replace_pos(" %like_case% ", with = " %not_like_case% ") - } else if (pos_preceded_by(" %not_like_case% ")) { - replace_pos(" %not_like_case% ", with = " %like% ") - } else { - insertText(" %like% ") - } + import_fn("insertText", "rstudioapi")(" %like% ") } check_dataset_integrity <- function() { diff --git a/R/first_isolate.R b/R/first_isolate.R index 99557b25..7ed2c1f8 100755 --- a/R/first_isolate.R +++ b/R/first_isolate.R @@ -25,7 +25,7 @@ #' Determine first (weighted) isolates #' -#' Determine first (weighted) isolates of all microorganisms of every patient per episode and (if needed) per specimen type. To determine patient episodes not necessarily based on microorganisms, use [is_new_episode()] that also supports grouping with the `dplyr` package, see *Examples*. +#' Determine first (weighted) isolates of all microorganisms of every patient per episode and (if needed) per specimen type. To determine patient episodes not necessarily based on microorganisms, use [is_new_episode()] that also supports grouping with the `dplyr` package. #' @inheritSection lifecycle Stable lifecycle #' @param x,.data a [data.frame] containing isolates. #' @param col_date column name of the result date (or date that is was received on the lab), defaults to the first column with a date class @@ -45,7 +45,7 @@ #' @param info print progress #' @param include_unknown logical to determine whether 'unknown' microorganisms should be included too, i.e. microbial code `"UNKNOWN"`, which defaults to `FALSE`. For WHONET users, this means that all records with organism code `"con"` (*contamination*) will be excluded at default. Isolates with a microbial ID of `NA` will always be excluded as first isolate. #' @param ... parameters passed on to the [first_isolate()] function -#' @details The [is_new_episode()] function is a wrapper around the [first_isolate()] function and can be used for data sets without isolates to just determine patient episodes based on any combination of grouping variables (using `dplyr`), please see *Examples*. Since it runs [first_isolate()] for every group, it is quite slow. +#' @details The [first_isolate()] function is a wrapper around the [is_new_episode()] function, but more efficient for data sets containing microorganism codes or names. #' #' All isolates with a microbial ID of `NA` will be excluded as first isolate. #' @@ -130,42 +130,6 @@ #' # Gentamicin resistance in hospital D appears to be 3.7% higher than #' # when you (erroneously) would have used all isolates for analysis. #' } -#' -#' # filtering based on any other condition ----------------------------------- -#' -#' if (require("dplyr")) { -#' # is_new_episode() can 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()) -#' -#' example_isolates %>% -#' group_by(hospital_id) %>% -#' summarise(patients = n_distinct(patient_id), -#' n_episodes_365 = sum(is_new_episode(episode_days = 365)), -#' n_episodes_60 = sum(is_new_episode(episode_days = 60)), -#' n_episodes_30 = sum(is_new_episode(episode_days = 30))) -#' -#' -#' # grouping on microorganisms leads to the same results as first_isolate(): -#' x <- example_isolates %>% -#' filter_first_isolate(include_unknown = TRUE) -#' -#' y <- example_isolates %>% -#' group_by(mo) %>% -#' filter(is_new_episode()) -#' -#' identical(x$patient_id, y$patient_id) -#' -#' # but now you can group on isolates and many more: -#' example_isolates %>% -#' group_by(mo, hospital_id, ward_icu) %>% -#' mutate(flag_episode = is_new_episode()) -#' } #' } first_isolate <- function(x, col_date = NULL, @@ -375,28 +339,6 @@ first_isolate <- function(x, scope.size <- nrow(x[which(x$newvar_row_index_sorted %in% c(row.start + 1:row.end) & !is.na(x$newvar_mo)), , drop = FALSE]) - identify_new_year <- function(x, episode_days) { - # I asked on StackOverflow: - # https://stackoverflow.com/questions/42122245/filter-one-row-every-year - if (length(x) == 1) { - return(TRUE) - } - indices <- integer(0) - start <- x[1] - ind <- 1 - indices[ind] <- ind - for (i in 2:length(x)) { - if (isTRUE(as.numeric(x[i] - start) >= episode_days)) { - ind <- ind + 1 - indices[ind] <- i - start <- x[i] - } - } - result <- rep(FALSE, length(x)) - result[indices] <- TRUE - return(result) - } - # Analysis of first isolate ---- x$other_pat_or_mo <- ifelse(x$newvar_patient_id == pm_lag(x$newvar_patient_id) & x$newvar_genus_species == pm_lag(x$newvar_genus_species), @@ -407,8 +349,8 @@ first_isolate <- function(x, function(g, df = x, days = episode_days) { - identify_new_year(x = df[which(df$episode_group == g), "newvar_date", drop = TRUE], - episode_days = days) + is_new_episode(x = df[which(df$episode_group == g), ]$newvar_date, + episode_days = days) })) weighted.notice <- "" @@ -572,67 +514,5 @@ filter_first_weighted_isolate <- function(x, subset(x, first_isolate(x = y, col_date = col_date, - col_patient_id = col_patient_id, - ...)) -} - -#' @rdname first_isolate -#' @export -is_new_episode <- function(.data, - episode_days = 365, - col_date = NULL, - col_patient_id = NULL) { - if (missing(.data)) { - # look it up - this also supports grouping variables - cur_data <- import_fn("cur_data", "dplyr", error_on_fail = FALSE) - if (is.null(cur_data)) { - stop_("parameter '.data' not set.") - } - .data <- cur_data() - } - meet_criteria(.data, allow_class = "data.frame") # also checks dimensions to be >0 - meet_criteria(col_date, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) - meet_criteria(col_patient_id, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) - meet_criteria(episode_days, allow_class = c("numeric", "integer"), has_length = 1) - - # get i'th ID of group, so notices will only be thrown once - cur_group_id <- import_fn("cur_group_id", "dplyr", error_on_fail = FALSE) - first_group <- tryCatch(is.null(cur_group_id) || cur_group_id() == 1, - error = function(e) TRUE) - - # try to find columns based on type - # -- date - if (is.null(col_date)) { - col_date <- search_type_in_df(x = .data, - type = "date", - info = first_group) - stop_if(is.null(col_date), "`col_date` must be set") - } - - # -- patient id - if (is.null(col_patient_id)) { - if (all(c("First name", "Last name", "Sex") %in% colnames(.data))) { - # WHONET support - .data$patient_id <- paste(.data$`First name`, .data$`Last name`, .data$Sex) - col_patient_id <- "patient_id" - if (is.null(cur_group_id) || cur_group_id() == 1) { - message_("Using combined columns `", font_bold("First name"), "`, `", font_bold("Last name"), "` and `", font_bold("Sex"), "` as input for `col_patient_id`") - } - } else { - col_patient_id <- search_type_in_df(x = .data, - type = "patient_id", - info = first_group) - } - stop_if(is.null(col_patient_id), "`col_patient_id` must be set") - } - - # create any random mo, so first isolates can be calculated - .data$a94a8fe5 <- as.mo("Escherichia coli") - - first_isolate(.data, - col_date = col_date, - col_patient_id = col_patient_id, - episode_days = episode_days, - col_mo = "a94a8fe5", - info = FALSE) + col_patient_id = col_patient_id)) } diff --git a/R/is_new_episode.R b/R/is_new_episode.R new file mode 100644 index 00000000..13ec756e --- /dev/null +++ b/R/is_new_episode.R @@ -0,0 +1,129 @@ +# ==================================================================== # +# TITLE # +# Antimicrobial Resistance (AMR) Analysis for R # +# # +# SOURCE # +# https://github.com/msberends/AMR # +# # +# LICENCE # +# (c) 2018-2020 Berends MS, Luz CF et al. # +# Developed at the University of Groningen, the Netherlands, in # +# collaboration with non-profit organisations Certe Medical # +# Diagnostics & Advice, and University Medical Center Groningen. # +# # +# This R package is free software; you can freely use and distribute # +# it for both personal and commercial purposes under the terms of the # +# GNU General Public License version 2.0 (GNU GPL-2), as published by # +# the Free Software Foundation. # +# We created this package for both routine data analysis and academic # +# research and it was publicly released in the hope that it will be # +# useful, but it comes WITHOUT ANY WARRANTY OR LIABILITY. # +# # +# Visit our website for the full manual and a complete tutorial about # +# how to conduct AMR analysis: https://msberends.github.io/AMR/ # +# ==================================================================== # + +#' 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 parameter `episode_days`. This can be used to determine clinical episodes for any epidemiological analysis. +#' @inheritSection lifecycle Experimental 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 ... 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 `dplyr` package is not required for this function to work, but this function works conveniently inside `dplyr` verbs such as [filter()], [mutate()] and [summarise()]. +#' @return a [logical] vector +#' @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) +#' is_new_episode(example_isolates$date, episode_days = 60) +#' +#' 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)) +#' +#' 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)) +#' +#' 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)) +#' } +is_new_episode <- function(x, episode_days = 365, ...) { + meet_criteria(x, allow_class = c("Date", "POSIXt")) + meet_criteria(episode_days, allow_class = c("numeric", "double", "integer"), has_length = 1) + + x <- as.double(as.Date(x, ...)) # as.Date() for POSIX classes + if (length(x) == 1) { + return(TRUE) + } + if (length(x) == 2 && max(x) - min(x) >= episode_days) { + return(rep(TRUE, 2)) + } + + # I asked on StackOverflow: + # https://stackoverflow.com/questions/42122245/filter-one-row-every-year + exec <- function(x, episode_days) { + if (length(x) == 1) { + return(TRUE) + } else if (length(x) == 2) { + if (max(x) - min(x) >= episode_days) { + return(c(TRUE, TRUE)) + } else { + return(c(TRUE, FALSE)) + } + } + indices <- integer() + start <- x[1] + ind <- 1 + indices[1] <- 1 + for (i in 2:length(x)) { + if (isTRUE((x[i] - start) >= episode_days)) { + ind <- ind + 1 + indices[ind] <- i + start <- x[i] + } + } + result <- rep(FALSE, length(x)) + result[indices] <- TRUE + result + } + + df <- data.frame(x = x, + y = seq_len(length(x))) %pm>% + pm_arrange(x) + df$new <- exec(df$x, episode_days) + df %pm>% + pm_arrange(y) %pm>% + pm_pull(new) +} diff --git a/R/like.R b/R/like.R index 013e829c..02d7dfac 100755 --- a/R/like.R +++ b/R/like.R @@ -41,9 +41,7 @@ #' * Checks if `pattern` is a regular expression and sets `fixed = TRUE` if not, to greatly improve speed #' * Tries again with `perl = TRUE` if regex fails #' -#' Using RStudio? This function can also be inserted in your code from the Addins menu and can have its own Keyboard Shortcut like `Ctrl+Shift+L` or `Cmd+Shift+L` (see `Tools` > `Modify Keyboard Shortcuts...`). This addin iterates over all 'like' variants. So if you have defined the keyboard shortcut Ctrl/Cmd + L to this addin, it will first insert ` %like% ` and by pressing it again it will be replaced with ` %not_like% `, then ` %like_case% `, then ` %not_like_case% ` and then back to ` %like% `. -#' -#' The `"%not_like%"` and `"%not_like_case%"` functions are wrappers around `"%like%"` and `"%like_case%"`. +#' Using RStudio? The text `%like%` can also be directly inserted in your code from the Addins menu and can have its own Keyboard Shortcut like `Ctrl+Shift+L` or `Cmd+Shift+L` (see `Tools` > `Modify Keyboard Shortcuts...`). #' @source Idea from the [`like` function from the `data.table` package](https://github.com/Rdatatable/data.table/blob/master/R/like.R) #' @seealso [grep()] #' @inheritSection AMR Read more on our website! @@ -67,11 +65,6 @@ #' if (require("dplyr")) { #' example_isolates %>% #' filter(mo_name(mo) %like% "^ent") -#' -#' example_isolates %>% -#' mutate(group = case_when(hospital_id %like% "A|D" ~ "Group 1", -#' mo_name(mo) %not_like% "^Staph" ~ "Group 2a", -#' TRUE ~ "Group 2b")) #' } #' } like <- function(x, pattern, ignore.case = TRUE) { @@ -157,14 +150,6 @@ like <- function(x, pattern, ignore.case = TRUE) { like(x, pattern, ignore.case = TRUE) } -#' @rdname like -#' @export -"%not_like%" <- function(x, pattern) { - meet_criteria(x, allow_NA = TRUE) - meet_criteria(pattern, allow_NA = FALSE) - !like(x, pattern, ignore.case = TRUE) -} - #' @rdname like #' @export "%like_case%" <- function(x, pattern) { @@ -173,14 +158,6 @@ like <- function(x, pattern, ignore.case = TRUE) { like(x, pattern, ignore.case = FALSE) } -#' @rdname like -#' @export -"%not_like_case%" <- function(x, pattern) { - meet_criteria(x, allow_NA = TRUE) - meet_criteria(pattern, allow_NA = FALSE) - !like(x, pattern, ignore.case = FALSE) -} - "%like_perl%" <- function(x, pattern) { meet_criteria(x, allow_NA = TRUE) meet_criteria(pattern, allow_NA = FALSE) diff --git a/R/rsi.R b/R/rsi.R index 1fa79775..05a5afd9 100755 --- a/R/rsi.R +++ b/R/rsi.R @@ -614,13 +614,18 @@ as.rsi.data.frame <- function(x, } else if (types[i] == "rsi") { ab <- ab_cols[i] ab_coerced <- suppressWarnings(as.ab(ab)) - message_("=> Cleaning values in column `", font_bold(ab), "` (", - ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""), - ab_name(ab_coerced, tolower = TRUE), ")... ", - appendLF = FALSE, - as_note = FALSE) - x[, ab_cols[i]] <- as.rsi.default(x = x %pm>% pm_pull(ab_cols[i])) - message_(" OK.", add_fn = list(font_green, font_bold), as_note = FALSE) + if (!all(x[, ab_cols[i], drop = TRUE] %in% c("R", "S", "I"), na.rm = TRUE)) { + # only print message if values are not already clean + message_("=> Cleaning values in column `", font_bold(ab), "` (", + ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""), + ab_name(ab_coerced, tolower = TRUE), ")... ", + appendLF = FALSE, + as_note = FALSE) + } + x[, ab_cols[i]] <- as.rsi.default(x = as.character(x[, ab_cols[i], drop = TRUE])) + if (!all(x[, ab_cols[i], drop = TRUE] %in% c("R", "S", "I"), na.rm = TRUE)) { + message_(" OK.", add_fn = list(font_green, font_bold), as_note = FALSE) + } } } diff --git a/_pkgdown.yml b/_pkgdown.yml index d5a4a5fc..82cf48df 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -147,11 +147,12 @@ reference: - title: "Analysing data: antimicrobial resistance" desc: > 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()`. + 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()`). contents: - "`proportion`" - "`count`" + - "`is_new_episode`" - "`first_isolate`" - "`key_antibiotics`" - "`mdro`" @@ -181,20 +182,19 @@ reference: - title: "Other: statistical tests" desc: > - Some statistical tests or methods are not part of base R and are added to this package for convenience. + Some statistical tests or methods are not part of base R and were added to this package for convenience. contents: - "`g.test`" - "`kurtosis`" - "`skewness`" - - "`p_symbol`" - # - title: "Other: deprecated functions" - # desc: > - # These functions are deprecated, meaning that they will still - # work but show a warning with every use and will be removed - # in a future version. - # contents: - # - "`AMR-deprecated`" + - title: "Other: deprecated functions" + desc: > + These functions are deprecated, meaning that they will still + work but show a warning with every use and will be removed + in a future version. + contents: + - "`AMR-deprecated`" authors: Matthijs S. Berends: diff --git a/docs/404.html b/docs/404.html index edc34440..284968d7 100644 --- a/docs/404.html +++ b/docs/404.html @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9024 + 1.4.0.9025 diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index 8c61edb9..457bd022 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9024 + 1.4.0.9025 diff --git a/docs/articles/index.html b/docs/articles/index.html index 0e812de6..e61d52d7 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9024 + 1.4.0.9025 diff --git a/docs/authors.html b/docs/authors.html index cf09397b..cd1a905f 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9024 + 1.4.0.9025 diff --git a/docs/index.html b/docs/index.html index 60f4a7ff..8f28ce39 100644 --- a/docs/index.html +++ b/docs/index.html @@ -43,7 +43,7 @@ AMR (for R) - 1.4.0.9024 + 1.4.0.9025 diff --git a/docs/news/index.html b/docs/news/index.html index 13e22ebe..3a731784 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9024 + 1.4.0.9025 @@ -236,19 +236,19 @@ Source: NEWS.md -
-

-AMR 1.4.0.9024 Unreleased +
+

+AMR 1.4.0.9025 Unreleased

-
+

-Last updated: 17 November 2020 +Last updated: 23 November 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() and summarise() of the dplyr package: r example_isolates %>% group_by(hospital_id) %>% summarise(patients = n_distinct(patient_id), n_episodes_365 = sum(is_new_episode(episode_days = 365)), n_episodes_60 = sum(is_new_episode(episode_days = 60)))

  • +
  • 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: r example_isolates %>% group_by(patient_id, hospital_id) %>% filter(is_new_episode(date, episode_days = 60))

  • 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. If you have the dplyr package installed, they can even determine the column with microorganisms themselves when used inside dplyr verbs:

    @@ -263,7 +263,6 @@
       filter(mo_is_intrinsic_resistant(ab = "Vancomycin"))
     #> NOTE: Using column `mo` as input for mo_is_intrinsic_resistant()
  • -
  • Functions %not_like% and %not_like_case% as wrappers around %like% and %like_case%. The RStudio addin to insert the text " %like% " as provided in this package now iterates over all like variants. So if you have defined the keyboard shortcut Ctrl/Cmd + L to this addin, it will first insert %like% and by pressing it again it will be replaced with %not_like%, etc.

@@ -277,6 +276,8 @@
  • Updated coagulase-negative staphylococci determination with Becker et al. 2020 (PMID 32056452), meaning that the species S. argensis, S. caeli, S. debuckii, S. edaphicus and S. pseudoxylosus are now all considered CoNS
  • Fix for using parameter reference_df in as.mo() and mo_*() functions that contain old microbial codes (from previous package versions)
  • Fix for using as.rsi() on a data.frame in older R versions
  • +
  • +as.rsi() on a data.frame will not print a message anymore if the values are already clean R/SI values
  • diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index 4884f74a..9be9c25c 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-11-17T15:56Z +last_built: 2020-11-23T20:45Z urls: reference: https://msberends.github.io/AMR//reference article: https://msberends.github.io/AMR//articles diff --git a/docs/reference/first_isolate.html b/docs/reference/first_isolate.html index 1dcba621..38443340 100644 --- a/docs/reference/first_isolate.html +++ b/docs/reference/first_isolate.html @@ -49,7 +49,7 @@ - + @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9024 + 1.4.0.9025
    @@ -239,7 +239,7 @@
    -

    Determine first (weighted) isolates of all microorganisms of every patient per episode and (if needed) per specimen type. To determine patient episodes not necessarily based on microorganisms, use is_new_episode() that also supports grouping with the dplyr package, see Examples.

    +

    Determine first (weighted) isolates of all microorganisms of every patient per episode and (if needed) per specimen type. To determine patient episodes not necessarily based on microorganisms, use is_new_episode() that also supports grouping with the dplyr package.

    first_isolate(
    @@ -278,13 +278,6 @@
       col_mo = NULL,
       col_keyantibiotics = NULL,
       ...
    -)
    -
    -is_new_episode(
    -  .data,
    -  episode_days = 365,
    -  col_date = NULL,
    -  col_patient_id = NULL
     )

    Arguments

    @@ -373,7 +366,7 @@

    A logical vector

    Details

    -

    The is_new_episode() function is a wrapper around the first_isolate() function and can be used for data sets without isolates to just determine patient episodes based on any combination of grouping variables (using dplyr), please see Examples. Since it runs first_isolate() for every group, it is quite slow.

    +

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

    All isolates with a microbial ID of NA will be excluded as first isolate.

    Why this is so important

    @@ -462,42 +455,6 @@ The lifecycle of this function is stable# Gentamicin resistance in hospital D appears to be 3.7% higher than # when you (erroneously) would have used all isolates for analysis. } - -# filtering based on any other condition ----------------------------------- - -if (require("dplyr")) { - # is_new_episode() can 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()) - - example_isolates %>% - group_by(hospital_id) %>% - summarise(patients = n_distinct(patient_id), - n_episodes_365 = sum(is_new_episode(episode_days = 365)), - n_episodes_60 = sum(is_new_episode(episode_days = 60)), - n_episodes_30 = sum(is_new_episode(episode_days = 30))) - - - # grouping on microorganisms leads to the same results as first_isolate(): - x <- example_isolates %>% - filter_first_isolate(include_unknown = TRUE) - - y <- example_isolates %>% - group_by(mo) %>% - filter(is_new_episode()) - - identical(x$patient_id, y$patient_id) - - # but now you can group on isolates and many more: - example_isolates %>% - group_by(mo, hospital_id, ward_icu) %>% - mutate(flag_episode = is_new_episode()) -} # }
    diff --git a/docs/reference/index.html b/docs/reference/index.html index d6a81d37..fdce8d7c 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9024 + 1.4.0.9025
    @@ -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(). 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,13 @@ -

    first_isolate() filter_first_isolate() filter_first_weighted_isolate() is_new_episode()

    +

    is_new_episode()

    + +

    Determine (new) episodes for patients

    + + + +

    first_isolate() filter_first_isolate() filter_first_weighted_isolate()

    Determine first (weighted) isolates

    @@ -581,7 +587,7 @@ -

    like() `%like%` `%not_like%` `%like_case%` `%not_like_case%`

    +

    like() `%like%` `%like_case%`

    Pattern matching with keyboard shortcut

    @@ -601,7 +607,7 @@

    Other: statistical tests

    -

    Some statistical tests or methods are not part of base R and are added to this package for convenience.

    +

    Some statistical tests or methods are not part of base R and were added to this package for convenience.

    @@ -627,7 +633,20 @@

    skewness()

    Skewness of the sample

    - + + + + +

    Other: deprecated functions

    +

    These functions are deprecated, meaning that they will still work but show a warning with every use and will be removed in a future version.

    + + + + + + + +

    p_symbol()

    diff --git a/docs/reference/is_new_episode.html b/docs/reference/is_new_episode.html new file mode 100644 index 00000000..79494154 --- /dev/null +++ b/docs/reference/is_new_episode.html @@ -0,0 +1,348 @@ + + + + + + + + +Determine (new) episodes for patients — is_new_episode • AMR (for R) + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
    +
    + + + + +
    + +
    +
    + + +
    +

    This function determines which items in a vector can be considered (the start of) a new episode, based on the parameter episode_days. This can be used to determine clinical episodes for any epidemiological analysis.

    +
    + +
    is_new_episode(x, episode_days = 365, ...)
    + +

    Arguments

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

    vector of dates (class Date or POSIXt)

    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.

    ...

    arguments passed on to as.Date()

    + +

    Value

    + +

    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 dplyr package is not required for this function to work, but this function works conveniently inside dplyr verbs such as filter(), mutate() and summarise().

    +

    Experimental lifecycle

    + + + +


    +The lifecycle of this function is experimental. An experimental function is in early stages of development. The unlying code might be changing frequently. Experimental functions might be removed without deprecation, so you are generally best off waiting until a function is more mature before you use it in production code. Experimental functions are only available in development versions of this AMR package and will thus not be included in releases that are submitted to CRAN, since such functions have not yet matured enough.

    + +

    Examples

    +
    # `example_isolates` is a dataset available in the AMR package.
    +# See ?example_isolates.
    +
    +is_new_episode(example_isolates$date)
    +is_new_episode(example_isolates$date, episode_days = 60)
    +
    +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))
    +  
    +  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))
    +
    +  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))
    +}
    +
    +
    + +
    + + + +
    + + + + + + + + diff --git a/docs/reference/like.html b/docs/reference/like.html index cd2efa97..7c0403b2 100644 --- a/docs/reference/like.html +++ b/docs/reference/like.html @@ -82,7 +82,7 @@ AMR (for R) - 1.4.0.9019 + 1.4.0.9025

    @@ -246,11 +246,7 @@ x %like% pattern -x %not_like% pattern - -x %like_case% pattern - -x %not_like_case% pattern +x %like_case% pattern

    Arguments

    @@ -284,8 +280,7 @@
  • Tries again with perl = TRUE if regex fails

  • -

    Using RStudio? This function can also be inserted in your code from the Addins menu and can have its own Keyboard Shortcut like Ctrl+Shift+L or Cmd+Shift+L (see Tools > Modify Keyboard Shortcuts...). This addin iterates over all 'like' variants. So if you have defined the keyboard shortcut Ctrl/Cmd + L to this addin, it will first insert %like% and by pressing it again it will be replaced with %not_like%, then %like_case%, then %not_like_case% and then back to %like%.

    -

    The "%not_like%" and "%not_like_case%" functions are wrappers around "%like%" and "%like_case%".

    +

    Using RStudio? The text %like% can also be directly inserted in your code from the Addins menu and can have its own Keyboard Shortcut like Ctrl+Shift+L or Cmd+Shift+L (see Tools > Modify Keyboard Shortcuts...).

    Stable lifecycle

    @@ -322,11 +317,6 @@ The lifecycle of this function is stableif (require("dplyr")) { example_isolates %>% filter(mo_name(mo) %like% "^ent") - - example_isolates %>% - mutate(group = case_when(hospital_id %like% "A|D" ~ "Group 1", - mo_name(mo) %not_like% "^Staph" ~ "Group 2a", - TRUE ~ "Group 2b")) } # } diff --git a/docs/sitemap.xml b/docs/sitemap.xml index ec5ac538..aace7d9c 100644 --- a/docs/sitemap.xml +++ b/docs/sitemap.xml @@ -96,6 +96,9 @@ 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 2d50307e..ad3eb8ce 100644 --- a/docs/survey.html +++ b/docs/survey.html @@ -81,7 +81,7 @@ AMR (for R) - 1.4.0.9024 + 1.4.0.9025 diff --git a/inst/rstudio/addins.dcf b/inst/rstudio/addins.dcf index 738ce92b..d43c060a 100644 --- a/inst/rstudio/addins.dcf +++ b/inst/rstudio/addins.dcf @@ -2,6 +2,6 @@ Name: Insert %in% Binding: addin_insert_in Interactive: false -Name: Insert %like% / %not_like% +Name: Insert %like% Binding: addin_insert_like Interactive: false diff --git a/man/first_isolate.Rd b/man/first_isolate.Rd index 4e0f18f3..53eebcd6 100755 --- a/man/first_isolate.Rd +++ b/man/first_isolate.Rd @@ -4,7 +4,6 @@ \alias{first_isolate} \alias{filter_first_isolate} \alias{filter_first_weighted_isolate} -\alias{is_new_episode} \title{Determine first (weighted) isolates} \source{ Methodology of this function is strictly based on: @@ -49,13 +48,6 @@ filter_first_weighted_isolate( col_keyantibiotics = NULL, ... ) - -is_new_episode( - .data, - episode_days = 365, - col_date = NULL, - col_patient_id = NULL -) } \arguments{ \item{x, .data}{a \link{data.frame} containing isolates.} @@ -98,10 +90,10 @@ is_new_episode( A \code{\link{logical}} vector } \description{ -Determine first (weighted) isolates of all microorganisms of every patient per episode and (if needed) per specimen type. To determine patient episodes not necessarily based on microorganisms, use \code{\link[=is_new_episode]{is_new_episode()}} that also supports grouping with the \code{dplyr} package, see \emph{Examples}. +Determine first (weighted) isolates of all microorganisms of every patient per episode and (if needed) per specimen type. To determine patient episodes not necessarily based on microorganisms, use \code{\link[=is_new_episode]{is_new_episode()}} that also supports grouping with the \code{dplyr} package. } \details{ -The \code{\link[=is_new_episode]{is_new_episode()}} function is a wrapper around the \code{\link[=first_isolate]{first_isolate()}} function and can be used for data sets without isolates to just determine patient episodes based on any combination of grouping variables (using \code{dplyr}), please see \emph{Examples}. Since it runs \code{\link[=first_isolate]{first_isolate()}} for every group, it is quite slow. +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. All isolates with a microbial ID of \code{NA} will be excluded as first isolate. \subsection{Why this is so important}{ @@ -191,42 +183,6 @@ if (require("dplyr")) { # Gentamicin resistance in hospital D appears to be 3.7\% higher than # when you (erroneously) would have used all isolates for analysis. } - -# filtering based on any other condition ----------------------------------- - -if (require("dplyr")) { - # is_new_episode() can 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()) - - example_isolates \%>\% - group_by(hospital_id) \%>\% - summarise(patients = n_distinct(patient_id), - n_episodes_365 = sum(is_new_episode(episode_days = 365)), - n_episodes_60 = sum(is_new_episode(episode_days = 60)), - n_episodes_30 = sum(is_new_episode(episode_days = 30))) - - - # grouping on microorganisms leads to the same results as first_isolate(): - x <- example_isolates \%>\% - filter_first_isolate(include_unknown = TRUE) - - y <- example_isolates \%>\% - group_by(mo) \%>\% - filter(is_new_episode()) - - identical(x$patient_id, y$patient_id) - - # but now you can group on isolates and many more: - example_isolates \%>\% - group_by(mo, hospital_id, ward_icu) \%>\% - mutate(flag_episode = is_new_episode()) -} } } \seealso{ diff --git a/man/is_new_episode.Rd b/man/is_new_episode.Rd new file mode 100644 index 00000000..c0308105 --- /dev/null +++ b/man/is_new_episode.Rd @@ -0,0 +1,80 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/is_new_episode.R +\name{is_new_episode} +\alias{is_new_episode} +\title{Determine (new) episodes for patients} +\usage{ +is_new_episode(x, episode_days = 365, ...) +} +\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{...}{arguments passed on to \code{\link[=as.Date]{as.Date()}}} +} +\value{ +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 parameter \code{episode_days}. This can be used to determine clinical episodes for any epidemiological analysis. +} +\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{dplyr} package is not required for this function to work, but this function works conveniently inside \code{dplyr} verbs such as \code{\link[=filter]{filter()}}, \code{\link[=mutate]{mutate()}} and \code{\link[=summarise]{summarise()}}. +} +\section{Experimental lifecycle}{ + +\if{html}{\figure{lifecycle_experimental.svg}{options: style=margin-bottom:5px} \cr} +The \link[=lifecycle]{lifecycle} of this function is \strong{experimental}. An experimental function is in early stages of development. The unlying code might be changing frequently. Experimental functions might be removed without deprecation, so you are generally best off waiting until a function is more mature before you use it in production code. Experimental functions are only available in development versions of this \code{AMR} package and will thus not be included in releases that are submitted to CRAN, since such functions have not yet matured enough. +} + +\section{Read more on our website!}{ + +On our website \url{https://msberends.github.io/AMR/} you can find \href{https://msberends.github.io/AMR/articles/AMR.html}{a comprehensive tutorial} about how to conduct AMR analysis, the \href{https://msberends.github.io/AMR/reference/}{complete documentation of all functions} and \href{https://msberends.github.io/AMR/articles/WHONET.html}{an example analysis using WHONET data}. As we would like to better understand the backgrounds and needs of our users, please \href{https://msberends.github.io/AMR/survey.html}{participate in our survey}! +} + +\examples{ +# `example_isolates` is a dataset available in the AMR package. +# See ?example_isolates. + +is_new_episode(example_isolates$date) +is_new_episode(example_isolates$date, episode_days = 60) + +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)) + + 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)) + + 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)) +} +} diff --git a/man/like.Rd b/man/like.Rd index 073b8555..8c26f939 100755 --- a/man/like.Rd +++ b/man/like.Rd @@ -3,9 +3,7 @@ \name{like} \alias{like} \alias{\%like\%} -\alias{\%not_like\%} \alias{\%like_case\%} -\alias{\%not_like_case\%} \title{Pattern matching with keyboard shortcut} \source{ Idea from the \href{https://github.com/Rdatatable/data.table/blob/master/R/like.R}{\code{like} function from the \code{data.table} package} @@ -15,11 +13,7 @@ like(x, pattern, ignore.case = TRUE) x \%like\% pattern -x \%not_like\% pattern - x \%like_case\% pattern - -x \%not_like_case\% pattern } \arguments{ \item{x}{a character vector where matches are sought, or an object which can be coerced by \code{\link[=as.character]{as.character()}} to a character vector.} @@ -43,9 +37,7 @@ The \verb{\%like\%} function: \item Tries again with \code{perl = TRUE} if regex fails } -Using RStudio? This function can also be inserted in your code from the Addins menu and can have its own Keyboard Shortcut like \code{Ctrl+Shift+L} or \code{Cmd+Shift+L} (see \code{Tools} > \verb{Modify Keyboard Shortcuts...}). This addin iterates over all 'like' variants. So if you have defined the keyboard shortcut Ctrl/Cmd + L to this addin, it will first insert \verb{\%like\%} and by pressing it again it will be replaced with \verb{\%not_like\%}, then \verb{\%like_case\%}, then \verb{\%not_like_case\%} and then back to \verb{\%like\%}. - -The \code{"\%not_like\%"} and \code{"\%not_like_case\%"} functions are wrappers around \code{"\%like\%"} and \code{"\%like_case\%"}. +Using RStudio? The text \verb{\%like\%} can also be directly inserted in your code from the Addins menu and can have its own Keyboard Shortcut like \code{Ctrl+Shift+L} or \code{Cmd+Shift+L} (see \code{Tools} > \verb{Modify Keyboard Shortcuts...}). } \section{Stable lifecycle}{ @@ -80,11 +72,6 @@ a \%like\% b if (require("dplyr")) { example_isolates \%>\% filter(mo_name(mo) \%like\% "^ent") - - example_isolates \%>\% - mutate(group = case_when(hospital_id \%like\% "A|D" ~ "Group 1", - mo_name(mo) \%not_like\% "^Staph" ~ "Group 2a", - TRUE ~ "Group 2b")) } } } diff --git a/tests/testthat/test-first_isolate.R b/tests/testthat/test-first_isolate.R index 3245f93c..16ee89d0 100755 --- a/tests/testthat/test-first_isolate.R +++ b/tests/testthat/test-first_isolate.R @@ -204,11 +204,5 @@ test_that("first isolates work", { expect_true(all(example_isolates %pm>% pm_distinct(mo, .keep_all = TRUE) %pm>% first_isolate() == TRUE)) - - library(dplyr) - # is_new_episode - old <- example_isolates %>% mutate(out = first_isolate(., include_unknown = TRUE)) - new <- example_isolates %>% group_by(mo) %>% mutate(out = is_new_episode()) - expect_identical(which(old$out), which(new$out)) }) diff --git a/tests/testthat/test-is_new_episode.R b/tests/testthat/test-is_new_episode.R new file mode 100644 index 00000000..87f4d838 --- /dev/null +++ b/tests/testthat/test-is_new_episode.R @@ -0,0 +1,55 @@ +# ==================================================================== # +# TITLE # +# Antimicrobial Resistance (AMR) Analysis for R # +# # +# SOURCE # +# https://github.com/msberends/AMR # +# # +# LICENCE # +# (c) 2018-2020 Berends MS, Luz CF et al. # +# Developed at the University of Groningen, the Netherlands, in # +# collaboration with non-profit organisations Certe Medical # +# Diagnostics & Advice, and University Medical Center Groningen. # +# # +# This R package is free software; you can freely use and distribute # +# it for both personal and commercial purposes under the terms of the # +# GNU General Public License version 2.0 (GNU GPL-2), as published by # +# the Free Software Foundation. # +# We created this package for both routine data analysis and academic # +# research and it was publicly released in the hope that it will be # +# useful, but it comes WITHOUT ANY WARRANTY OR LIABILITY. # +# # +# Visit our website for the full manual and a complete tutorial about # +# how to conduct AMR analysis: https://msberends.github.io/AMR/ # +# ==================================================================== # + +context("is_new_episode.R") + +test_that("new episodes work", { + skip_on_cran() + + test_df <- rbind( + data.frame( + date = as.Date(c("2015-01-01", "2015-10-01", "2016-02-04", "2016-12-31", "2017-01-01", "2017-02-01", "2017-02-05", "2020-01-01")), + patient_id = "A" + ), + data.frame( + date = as.Date(c("2015-01-01", "2016-02-01", "2016-12-31", "2017-01-01", "2017-02-03")), + patient_id = "B" + )) + + library(dplyr) + expect_identical(test_df %>% group_by(patient_id) %>% mutate(f = is_new_episode(date)) %>% pull(f), + c(TRUE, FALSE, TRUE, FALSE, FALSE, FALSE, TRUE, TRUE, TRUE, TRUE, FALSE, FALSE, TRUE)) + + suppressMessages( + x <- example_isolates %>% + mutate(out = first_isolate(., include_unknown = TRUE, info = FALSE)) + ) + + y <- example_isolates %>% + group_by(patient_id, mo) %>% + mutate(out = is_new_episode(date)) + + expect_identical(which(x$out), which(y$out)) +}) diff --git a/tests/testthat/test-like.R b/tests/testthat/test-like.R index c941fda0..661b0dd8 100644 --- a/tests/testthat/test-like.R +++ b/tests/testthat/test-like.R @@ -31,10 +31,7 @@ test_that("`like` works", { expect_true("test" %like% "test") expect_false("test" %like_case% "TEST") - - expect_false("test" %not_like% "test") - expect_true("test" %not_like_case% "TEST") - + expect_true(as.factor("test") %like% "TEST") expect_identical(factor(c("Test case", "Something different", "Yet another thing")) %like% c("case", "diff", "yet"), c(TRUE, TRUE, TRUE))