diff --git a/DESCRIPTION b/DESCRIPTION index ce1e4601..63dd33c4 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 0.7.0.9007 -Date: 2019-06-12 +Version: 0.7.0.9008 +Date: 2019-06-13 Title: Antimicrobial Resistance Analysis Authors@R: c( person( diff --git a/NAMESPACE b/NAMESPACE index 7c16744d..043ce300 100755 --- a/NAMESPACE +++ b/NAMESPACE @@ -172,6 +172,7 @@ export(ratio) export(read.4D) export(resistance_predict) export(right_join_microorganisms) +export(rsi_df) export(rsi_predict) export(scale_rsi_colours) export(scale_type.ab) diff --git a/NEWS.md b/NEWS.md index f1dc00f0..901500c1 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,6 +1,17 @@ -# AMR 0.7.0.9007 +# AMR 0.7.0.9008 #### New +* Function `rsi_df()` to transform a `data.frame` to a data set containing only the microbial interpretation (S, I, R), the antibiotic, the percentage of S/I/R and the number of available isolates. This is a convenient combinations of existing functions `count_df()` and `portion_df()` to immediately show resistance percentages and number of available isolates: + ```r + septic_patients %>% + select(AMX, CIP) %>% + rsi_df() + # antibiotic interpretation value isolates + # 1 Amoxicillin SI 0.4442636 546 + # 2 Amoxicillin R 0.5557364 683 + # 3 Ciprofloxacin SI 0.8381831 1181 + # 4 Ciprofloxacin R 0.1618169 228 + ``` * Support for all scientifically published pathotypes of *E. coli* to date. Supported are: AIEC (Adherent-Invasive *E. coli*), ATEC (Atypical Entero-pathogenic *E. coli*), DAEC (Diffusely Adhering *E. coli*), EAEC (Entero-Aggresive *E. coli*), EHEC (Entero-Haemorrhagic *E. coli*), EIEC (Entero-Invasive *E. coli*), EPEC (Entero-Pathogenic *E. coli*), ETEC (Entero-Toxigenic *E. coli*), NMEC (Neonatal Meningitis‐causing *E. coli*), STEC (Shiga-toxin producing *E. coli*) and UPEC (Uropathogenic *E. coli*). All these lead to the microbial ID of *E. coli*: ```r as.mo("UPEC") @@ -11,6 +22,7 @@ * Function `mo_info()` as an analogy to `ab_info()`. The `mo_info()` prints a list with the full taxonomy, authors, and the URL to the online database of a microorganism #### Changed +* Column names of output `count_df()` and `portion_df()` are now lowercase * Fixed bug in translation of microorganism names * Fixed bug in determining taxonomic kingdoms * Algorithm improvements for `as.ab()` and `as.mo()` to understand even more severely misspelled input @@ -23,6 +35,7 @@ * Removed `latest_annual_release` from the `catalogue_of_life_version()` function * Removed antibiotic code `PVM1` from the `antibiotics` data set as this was a duplicate of `PME` * Fixed bug where not all old taxonomic named would not be printed when using a vector as input for `as.mo()` +* Manually added *Trichomonas vaginalis* from the kingdom of Protozoa, which is missing from the Catalogue of Life #### Other * Fixed a note thrown by CRAN tests diff --git a/R/ab.R b/R/ab.R index 1159d505..8a99c0be 100755 --- a/R/ab.R +++ b/R/ab.R @@ -203,7 +203,6 @@ as.ab <- function(x) { # try by removing all spaces if (x[i] %like% " ") { found <- suppressWarnings(as.ab(gsub(" +", "", x[i]))) - print(found) if (length(found) > 0 & !is.na(found)) { x_new[i] <- found[1L] next diff --git a/R/age.R b/R/age.R index 23f964a1..76144bb7 100755 --- a/R/age.R +++ b/R/age.R @@ -136,6 +136,9 @@ age <- function(x, reference = Sys.Date(), exact = FALSE) { #' select(age_group, CIP) %>% #' ggplot_rsi(x = "age_group") age_groups <- function(x, split_at = c(12, 25, 55, 75)) { + if (!is.numeric(x)) { + stop("`x` and must be numeric, not a ", paste0(class(x), collapse = "/"), ".") + } if (is.character(split_at)) { split_at <- split_at[1L] if (split_at %like% "^(child|kid|junior)") { @@ -148,11 +151,7 @@ age_groups <- function(x, split_at = c(12, 25, 55, 75)) { split_at <- 1:10 * 10 } } - split_at <- as.integer(split_at) - if (!is.numeric(x) | !is.numeric(split_at)) { - stop("`x` and `split_at` must both be numeric.") - } - split_at <- sort(unique(split_at)) + split_at <- sort(unique(as.integer(split_at))) if (!split_at[1] == 0) { # add base number 0 split_at <- c(0, split_at) diff --git a/R/count.R b/R/count.R index 492369bc..7c275b11 100755 --- a/R/count.R +++ b/R/count.R @@ -29,9 +29,11 @@ #' @inheritSection as.rsi Interpretation of S, I and R #' @details These functions are meant to count isolates. Use the \code{\link{portion}_*} functions to calculate microbial resistance. #' -#' \code{n_rsi} is an alias of \code{count_all}. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to \code{\link{n_distinct}}. Their function is equal to \code{count_S(...) + count_IR(...)}. +#' The function \code{n_rsi} is an alias of \code{count_all}. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to \code{\link{n_distinct}}. Their function is equal to \code{count_S(...) + count_IR(...)}. #' -#' \code{count_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and counts the amounts of R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}. +#' The function \code{count_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and counts the amounts of S, I and R. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}. +#' +#' The function \code{rsi_df} works exactly like \code{count_df}, but add the percentage of S, I and R. #' @source Wickham H. \strong{Tidy Data.} The Journal of Statistical Software, vol. 59, 2014. \url{http://vita.had.co.nz/papers/tidy-data.html} #' @seealso \code{\link{portion}_*} to calculate microbial resistance and susceptibility. #' @keywords resistance susceptibility rsi antibiotics isolate isolates diff --git a/R/data.R b/R/data.R index e02c24c3..fc6bd1f9 100755 --- a/R/data.R +++ b/R/data.R @@ -55,7 +55,7 @@ #' #' A data set containing the microbial taxonomy of six kingdoms from the Catalogue of Life. MO codes can be looked up using \code{\link{as.mo}}. #' @inheritSection catalogue_of_life Catalogue of Life -#' @format A \code{\link{data.frame}} with 67,903 observations and 16 variables: +#' @format A \code{\link{data.frame}} with 67,906 observations and 16 variables: #' \describe{ #' \item{\code{mo}}{ID of microorganism as used by this package} #' \item{\code{col_id}}{Catalogue of Life ID} @@ -69,9 +69,10 @@ #' } #' @details Manually added were: #' \itemize{ -#' \item{9 species of \emph{Streptococcus} (beta haemolytic groups A, B, C, D, F, G, H, K and unspecified)} -#' \item{2 species of \emph{Staphylococcus} (coagulase-negative [CoNS] and coagulase-positive [CoPS])} -#' \item{3 other undefined (unknown, unknown Gram negatives and unknown Gram positives)} +#' \item{9 entries of \emph{Streptococcus} (beta haemolytic groups A, B, C, D, F, G, H, K and unspecified)} +#' \item{2 entries of \emph{Staphylococcus} (coagulase-negative [CoNS] and coagulase-positive [CoPS])} +#' \item{3 entries of Trichomonas (Trichomonas vaginalis, and its family and genus)} +#' \item{3 other 'undefined' entries (unknown, unknown Gram negatives and unknown Gram positives)} #' \item{8,830 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) that are not in the Catalogue of Life} #' } #' @section About the records from DSMZ (see source): diff --git a/R/ggplot_rsi.R b/R/ggplot_rsi.R index d5158a43..d678cb2d 100755 --- a/R/ggplot_rsi.R +++ b/R/ggplot_rsi.R @@ -24,11 +24,11 @@ #' Use these functions to create bar plots for antimicrobial resistance analysis. All functions rely on internal \code{\link[ggplot2]{ggplot}2} functions. #' @param data a \code{data.frame} with column(s) of class \code{"rsi"} (see \code{\link{as.rsi}}) #' @param position position adjustment of bars, either \code{"fill"} (default when \code{fun} is \code{\link{count_df}}), \code{"stack"} (default when \code{fun} is \code{\link{portion_df}}) or \code{"dodge"} -#' @param x variable to show on x axis, either \code{"Antibiotic"} (default) or \code{"Interpretation"} or a grouping variable -#' @param fill variable to categorise using the plots legend, either \code{"Antibiotic"} (default) or \code{"Interpretation"} or a grouping variable +#' @param x variable to show on x axis, either \code{"antibiotic"} (default) or \code{"interpretation"} or a grouping variable +#' @param fill variable to categorise using the plots legend, either \code{"antibiotic"} (default) or \code{"interpretation"} or a grouping variable #' @param breaks numeric vector of positions #' @param limits numeric vector of length two providing limits of the scale, use \code{NA} to refer to the existing minimum or maximum -#' @param facet variable to split plots by, either \code{"Interpretation"} (default) or \code{"Antibiotic"} or a grouping variable +#' @param facet variable to split plots by, either \code{"interpretation"} (default) or \code{"antibiotic"} or a grouping variable #' @param fun function to transform \code{data}, either \code{\link{count_df}} (default) or \code{\link{portion_df}} #' @inheritParams portion #' @param nrow (when using \code{facet}) number of rows @@ -129,7 +129,7 @@ #' select(hospital_id, AMX, NIT, FOS, TMP, CIP) %>% #' group_by(hospital_id) %>% #' ggplot_rsi(x = "hospital_id", -#' facet = "Antibiotic", +#' facet = "antibiotic", #' nrow = 1, #' title = "AMR of Anti-UTI Drugs Per Hospital", #' x.title = "Hospital", @@ -150,7 +150,7 @@ #' # group by MO #' group_by(bug) %>% #' # plot the thing, putting MOs on the facet -#' ggplot_rsi(x = "Antibiotic", +#' ggplot_rsi(x = "antibiotic", #' facet = "bug", #' translate_ab = FALSE, #' nrow = 1, @@ -161,8 +161,8 @@ #' } ggplot_rsi <- function(data, position = NULL, - x = "Antibiotic", - fill = "Interpretation", + x = "antibiotic", + fill = "interpretation", # params = list(), facet = NULL, breaks = seq(0, 1, 0.1), @@ -226,7 +226,7 @@ ggplot_rsi <- function(data, fun = fun, combine_SI = combine_SI, combine_IR = combine_IR, ...) + theme_rsi() - if (fill == "Interpretation") { + if (fill == "interpretation") { # set RSI colours if (isFALSE(colours) & missing(datalabels.colour)) { # set datalabel colour to middle gray @@ -267,8 +267,8 @@ ggplot_rsi <- function(data, #' @rdname ggplot_rsi #' @export geom_rsi <- function(position = NULL, - x = c("Antibiotic", "Interpretation"), - fill = "Interpretation", + x = c("antibiotic", "interpretation"), + fill = "interpretation", translate_ab = "name", language = get_locale(), combine_SI = TRUE, @@ -286,7 +286,7 @@ geom_rsi <- function(position = NULL, if (!fun_name %in% c("portion_df", "count_df", "fun")) { stop("`fun` must be portion_df or count_df") } - y <- "Value" + y <- "value" if (identical(fun, count_df)) { if (missing(position) | is.null(position)) { position <- "fill" @@ -312,10 +312,10 @@ geom_rsi <- function(position = NULL, x <- substr(x, 2, nchar(x) - 1) } - if (tolower(x) %in% tolower(c('ab', 'antibiotic', 'abx', 'antibiotics'))) { - x <- "Antibiotic" - } else if (tolower(x) %in% tolower(c('SIR', 'RSI', 'interpretation', 'interpretations', 'result'))) { - x <- "Interpretation" + if (tolower(x) %in% tolower(c('ab', 'abx', 'antibiotics'))) { + x <- "antibiotic" + } else if (tolower(x) %in% tolower(c('SIR', 'RSI', 'interpretations', 'result'))) { + x <- "interpretation" } ggplot2::layer(geom = "bar", stat = "identity", position = position, @@ -332,7 +332,7 @@ geom_rsi <- function(position = NULL, #' @rdname ggplot_rsi #' @export -facet_rsi <- function(facet = c("Interpretation", "Antibiotic"), nrow = NULL) { +facet_rsi <- function(facet = c("interpretation", "antibiotic"), nrow = NULL) { stopifnot_installed_package("ggplot2") @@ -347,10 +347,10 @@ facet_rsi <- function(facet = c("Interpretation", "Antibiotic"), nrow = NULL) { facet <- substr(facet, 2, nchar(facet) - 1) } - if (tolower(facet) %in% tolower(c('SIR', 'RSI', 'interpretation', 'interpretations', 'result'))) { - facet <- "Interpretation" - } else if (tolower(facet) %in% tolower(c('ab', 'antibiotic', 'abx', 'antibiotics'))) { - facet <- "Antibiotic" + if (tolower(facet) %in% tolower(c('SIR', 'RSI', 'interpretations', 'result'))) { + facet <- "interpretation" + } else if (tolower(facet) %in% tolower(c('ab', 'abx', 'antibiotics'))) { + facet <- "antibiotic" } ggplot2::facet_wrap(facets = facet, scales = "free_x", nrow = nrow) @@ -408,7 +408,7 @@ theme_rsi <- function() { #' @importFrom dplyr mutate %>% group_by_at #' @export labels_rsi_count <- function(position = NULL, - x = "Antibiotic", + x = "antibiotic", translate_ab = "name", combine_SI = TRUE, combine_IR = FALSE, @@ -424,7 +424,7 @@ labels_rsi_count <- function(position = NULL, x_name <- x ggplot2::geom_text(mapping = ggplot2::aes_string(label = "lbl", x = x, - y = "Value"), + y = "value"), position = position, inherit.aes = FALSE, size = datalabels.size, @@ -438,7 +438,7 @@ labels_rsi_count <- function(position = NULL, combine_SI = combine_SI, combine_IR = combine_IR) %>% group_by_at(x_name) %>% - mutate(lbl = paste0(percent(Value / sum(Value, na.rm = TRUE), force_zero = TRUE), - "\n(n=", Value, ")")) + mutate(lbl = paste0(percent(value / sum(value, na.rm = TRUE), force_zero = TRUE), + "\n(n=", value, ")")) }) } diff --git a/R/portion.R b/R/portion.R index a11d3990..9bf11ab4 100755 --- a/R/portion.R +++ b/R/portion.R @@ -38,7 +38,9 @@ #' #' These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. \emph{Low counts can infuence the outcome - these \code{portion} functions may camouflage this, since they only return the portion albeit being dependent on the \code{minimum} parameter.} #' -#' \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}. +#' The function \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each group and each variable with class \code{"rsi"}. +#' +#' The function \code{rsi_df} works exactly like \code{portion_df}, but add the number of isolates. #' \if{html}{ # (created with https://www.latex4technics.com/) #' \cr\cr diff --git a/R/rsi_calc.R b/R/rsi_calc.R index cfe764e1..fd648eb9 100755 --- a/R/rsi_calc.R +++ b/R/rsi_calc.R @@ -151,6 +151,7 @@ rsi_calc <- function(..., } } +#' @importFrom dplyr %>% summarise_if mutate select everything bind_rows rsi_calc_df <- function(type, # "portion" or "count" data, translate_ab = "name", @@ -196,8 +197,8 @@ rsi_calc_df <- function(type, # "portion" or "count" .funs = int_fn) } summ %>% - mutate(Interpretation = int) %>% - select(Interpretation, everything()) + mutate(interpretation = int) %>% + select(interpretation, everything()) } resS <- get_summaryfunction("S") @@ -209,28 +210,29 @@ rsi_calc_df <- function(type, # "portion" or "count" if (isFALSE(combine_SI) & isFALSE(combine_IR)) { res <- bind_rows(resS, resI, resR) %>% - mutate(Interpretation = factor(Interpretation, + mutate(interpretation = factor(interpretation, levels = c("S", "I", "R"), ordered = TRUE)) } else if (isTRUE(combine_IR)) { res <- bind_rows(resS, resIR) %>% - mutate(Interpretation = factor(Interpretation, + mutate(interpretation = factor(interpretation, levels = c("S", "IR"), ordered = TRUE)) } else if (isTRUE(combine_SI)) { res <- bind_rows(resSI, resR) %>% - mutate(Interpretation = factor(Interpretation, + mutate(interpretation = factor(interpretation, levels = c("SI", "R"), ordered = TRUE)) } res <- res %>% - tidyr::gather(Antibiotic, Value, -Interpretation, -data.groups) + tidyr::gather(antibiotic, value, -interpretation, -data.groups) %>% + select(antibiotic, everything()) if (!translate_ab == FALSE) { - res <- res %>% mutate(Antibiotic = ab_property(Antibiotic, property = translate_ab, language = language)) + res <- res %>% mutate(antibiotic = ab_property(antibiotic, property = translate_ab, language = language)) } res diff --git a/R/rsi_df.R b/R/rsi_df.R new file mode 100644 index 00000000..84cc46ff --- /dev/null +++ b/R/rsi_df.R @@ -0,0 +1,58 @@ +# ==================================================================== # +# TITLE # +# Antimicrobial Resistance (AMR) Analysis # +# # +# SOURCE # +# https://gitlab.com/msberends/AMR # +# # +# LICENCE # +# (c) 2019 Berends MS (m.s.berends@umcg.nl), Luz CF (c.f.luz@umcg.nl) # +# # +# 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. # +# # +# This R package was created for academic research and was publicly # +# released in the hope that it will be useful, but it comes WITHOUT # +# ANY WARRANTY OR LIABILITY. # +# Visit our website for more info: https://msberends.gitlab.io/AMR. # +# ==================================================================== # + +#' @rdname portion +#' @rdname count +#' @importFrom dplyr %>% select_if bind_rows summarise_if mutate group_vars select everything +#' @export +rsi_df <- function(data, + translate_ab = "name", + language = get_locale(), + minimum = 30, + as_percent = FALSE, + combine_SI = TRUE, + combine_IR = FALSE) { + + portions <- rsi_calc_df(type = "portion", + data = data, + translate_ab = translate_ab, + language = language, + minimum = minimum, + as_percent = as_percent, + combine_SI = combine_SI, + combine_IR = combine_IR, + combine_SI_missing = missing(combine_SI)) + + counts <- rsi_calc_df(type = "count", + data = data, + translate_ab = FALSE, + language = "en", + minimum = minimum, + as_percent = as_percent, + combine_SI = combine_SI, + combine_IR = combine_IR, + combine_SI_missing = missing(combine_SI)) + + data.frame(portions, + isolates = counts$value, + stringsAsFactors = FALSE) + +} diff --git a/R/sysdata.rda b/R/sysdata.rda index ae5d9aeb..44b57253 100644 Binary files a/R/sysdata.rda and b/R/sysdata.rda differ diff --git a/data-raw/reproduction_of_microorganisms.R b/data-raw/reproduction_of_microorganisms.R index be15c580..4e187753 100644 --- a/data-raw/reproduction_of_microorganisms.R +++ b/data-raw/reproduction_of_microorganisms.R @@ -444,7 +444,43 @@ MOs <- MOs %>% fullname = "Beta-haemolytic Streptococcus", ref = NA_character_, species_id = "", - source = "manually added") + source = "manually added"), + # Trichomonas vaginalis is missing, same order as Dientamoeba + MOs %>% + filter(fullname == "Dientamoeba") %>% + mutate(mo = gsub("DNTMB", "THMNS", mo), + col_id = NA, + fullname = "Trichomonas", + family = "Trichomonadidae", + genus = "Trichomonas", + source = "manually added", + ref = "Donne, 1836", + species_id = ""), + MOs %>% + filter(fullname == "Dientamoeba fragilis") %>% + mutate(mo = gsub("DNTMB", "THMNS", mo), + mo = gsub("FRA", "VAG", mo), + col_id = NA, + fullname = "Trichomonas vaginalis", + family = "Trichomonadidae", + genus = "Trichomonas", + species = "vaginalis", + source = "manually added", + ref = "Donne, 1836", + species_id = ""), + MOs %>% # add family as such too + filter(fullname == "Monocercomonadidae") %>% + mutate(mo = gsub("MNCRCMND", "TRCHMNDD", mo), + col_id = NA, + fullname = "Trichomonadidae", + family = "Trichomonadidae", + rank = "family", + genus = "", + species = "", + source = "manually added", + ref = "", + species_id = ""), + ) @@ -485,8 +521,12 @@ MOs <- MOs %>% TRUE ~ 3 )) +# arrange +MOs <- MOs %>% arrange(fullname) +MOs.old <- MOs.old %>% arrange(fullname) + # save it -MOs <- as.data.frame(MOs %>% arrange(fullname), stringsAsFactors = FALSE) +MOs <- as.data.frame(MOs, stringsAsFactors = FALSE) MOs.old <- as.data.frame(MOs.old, stringsAsFactors = FALSE) class(MOs$mo) <- "mo" diff --git a/data-raw/translations.tsv b/data-raw/translations.tsv index d8dcaed4..4e83286e 100644 --- a/data-raw/translations.tsv +++ b/data-raw/translations.tsv @@ -154,6 +154,8 @@ pt vegetative vegetativo FALSE FALSE pt ([([ ]*?)group \\1grupo FALSE FALSE pt ([([ ]*?)Group \\1Grupo FALSE FALSE +de clavulanic acid Clavulansäure FALSE TRUE + nl 4-aminosalicylic acid 4-aminosalicylzuur nl Adefovir dipivoxil Adefovir nl Aldesulfone sodium Aldesulfon @@ -348,8 +350,10 @@ nl Thiamphenicol Thiamfenicol nl Thioacetazone/isoniazid Thioacetazon/isoniazide nl Ticarcillin Ticarcilline nl Ticarcillin/beta-lactamase inhibitor Ticarcilline/enzymremmer +nl Ticarcillin/clavulanic acid Ticarcilline/clavulaanzuur nl Tinidazole Tinidazol nl Tobramycin Tobramycine +nl Trimethoprim/sulfamethoxazole Trimethoprim/sulfamethoxazol nl Troleandomycin Troleandomycine nl Trovafloxacin Trovafloxacine nl Vancomycin Vancomycine diff --git a/data/microorganisms.codes.rda b/data/microorganisms.codes.rda index 8c886e7a..1193b223 100644 Binary files a/data/microorganisms.codes.rda and b/data/microorganisms.codes.rda differ diff --git a/data/microorganisms.rda b/data/microorganisms.rda index 29c91c41..c27938fa 100755 Binary files a/data/microorganisms.rda and b/data/microorganisms.rda differ diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index 57467e8d..204b3781 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.0.9007 + 0.7.0.9008 diff --git a/docs/articles/index.html b/docs/articles/index.html index 2858e420..0a1e751e 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.0.9007 + 0.7.0.9008 diff --git a/docs/authors.html b/docs/authors.html index 558d685f..e408fa05 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.0.9007 + 0.7.0.9008 diff --git a/docs/index.html b/docs/index.html index 588ad0c8..e01b6500 100644 --- a/docs/index.html +++ b/docs/index.html @@ -42,7 +42,7 @@ AMR (for R) - 0.7.0.9007 + 0.7.0.9008 diff --git a/docs/news/index.html b/docs/news/index.html index b375b22c..41d186ae 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.0.9007 + 0.7.0.9008 @@ -232,20 +232,31 @@ -
+

-AMR 0.7.0.9007 Unreleased +AMR 0.7.0.9008 Unreleased

New

@@ -254,6 +265,7 @@

Changed

    +
  • Column names of output count_df() and portion_df() are now lowercase
  • Fixed bug in translation of microorganism names
  • Fixed bug in determining taxonomic kingdoms
  • Algorithm improvements for as.ab() and as.mo() to understand even more severely misspelled input
  • @@ -270,6 +282,7 @@
  • Fixed bug where not all old taxonomic named would not be printed when using a vector as input for as.mo()
  • +
  • Manually added Trichomonas vaginalis from the kingdom of Protozoa, which is missing from the Catalogue of Life
+ @@ -430,32 +443,32 @@ This data is updated annually - check the included version with the new function
  • New filters for antimicrobial classes. Use these functions to filter isolates on results in one of more antibiotics from a specific class:

    - +

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

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

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

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

    - +

    is equal to:

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

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

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

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

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

    Contents

    @@ -166,13 +166,6 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_ Create frequency tables -
  • - - - - Use the G-test - -
  • @@ -311,8 +304,9 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_

    Details

    These functions are meant to count isolates. Use the portion_* functions to calculate microbial resistance.

    -

    n_rsi is an alias of count_all. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to n_distinct. Their function is equal to count_S(...) + count_IR(...).

    -

    count_df takes any variable from data that has an "rsi" class (created with as.rsi) and counts the amounts of R, I and S. The resulting tidy data (see Source) data.frame will have three rows (S/I/R) and a column for each variable with class "rsi".

    +

    The function n_rsi is an alias of count_all. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to n_distinct. Their function is equal to count_S(...) + count_IR(...).

    +

    The function count_df takes any variable from data that has an "rsi" class (created with as.rsi) and counts the amounts of S, I and R. The resulting tidy data (see Source) data.frame will have three rows (S/I/R) and a column for each variable with class "rsi".

    +

    The function rsi_df works exactly like count_df, but add the percentage of S, I and R.

    Interpretation of S, I and R

    diff --git a/docs/reference/ggplot_rsi.html b/docs/reference/ggplot_rsi.html index c91b6985..fbfff211 100644 --- a/docs/reference/ggplot_rsi.html +++ b/docs/reference/ggplot_rsi.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9000 + 0.7.0.9008 @@ -165,13 +165,6 @@ Create frequency tables
  • -
  • - - - - Use the G-test - -
  • @@ -248,8 +241,8 @@ -
    ggplot_rsi(data, position = NULL, x = "Antibiotic",
    -  fill = "Interpretation", facet = NULL, breaks = seq(0, 1, 0.1),
    +    
    ggplot_rsi(data, position = NULL, x = "antibiotic",
    +  fill = "interpretation", facet = NULL, breaks = seq(0, 1, 0.1),
       limits = NULL, translate_ab = "name", combine_SI = TRUE,
       combine_IR = FALSE, language = get_locale(), fun = count_df,
       nrow = NULL, colours = c(S = "#61a8ff", SI = "#61a8ff", I =
    @@ -258,12 +251,12 @@
       subtitle = NULL, caption = NULL, x.title = NULL, y.title = NULL,
       ...)
     
    -geom_rsi(position = NULL, x = c("Antibiotic", "Interpretation"),
    -  fill = "Interpretation", translate_ab = "name",
    +geom_rsi(position = NULL, x = c("antibiotic", "interpretation"),
    +  fill = "interpretation", translate_ab = "name",
       language = get_locale(), combine_SI = TRUE, combine_IR = FALSE,
       fun = count_df, ...)
     
    -facet_rsi(facet = c("Interpretation", "Antibiotic"), nrow = NULL)
    +facet_rsi(facet = c("interpretation", "antibiotic"), nrow = NULL)
     
     scale_y_percent(breaks = seq(0, 1, 0.1), limits = NULL)
     
    @@ -272,7 +265,7 @@
     
     theme_rsi()
     
    -labels_rsi_count(position = NULL, x = "Antibiotic",
    +labels_rsi_count(position = NULL, x = "antibiotic",
       translate_ab = "name", combine_SI = TRUE, combine_IR = FALSE,
       datalabels.size = 3, datalabels.colour = "gray15")
    @@ -289,15 +282,15 @@ x -

    variable to show on x axis, either "Antibiotic" (default) or "Interpretation" or a grouping variable

    +

    variable to show on x axis, either "antibiotic" (default) or "interpretation" or a grouping variable

    fill -

    variable to categorise using the plots legend, either "Antibiotic" (default) or "Interpretation" or a grouping variable

    +

    variable to categorise using the plots legend, either "antibiotic" (default) or "interpretation" or a grouping variable

    facet -

    variable to split plots by, either "Interpretation" (default) or "Antibiotic" or a grouping variable

    +

    variable to split plots by, either "interpretation" (default) or "antibiotic" or a grouping variable

    breaks @@ -458,7 +451,7 @@ select(hospital_id, AMX, NIT, FOS, TMP, CIP) %>% group_by(hospital_id) %>% ggplot_rsi(x = "hospital_id", - facet = "Antibiotic", + facet = "antibiotic", nrow = 1, title = "AMR of Anti-UTI Drugs Per Hospital", x.title = "Hospital", @@ -479,7 +472,7 @@ # group by MO group_by(bug) %>% # plot the thing, putting MOs on the facet - ggplot_rsi(x = "Antibiotic", + ggplot_rsi(x = "antibiotic", facet = "bug", translate_ab = FALSE, nrow = 1, diff --git a/docs/reference/index.html b/docs/reference/index.html index 653ff0c8..f2e25409 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.0.9007 + 0.7.0.9008 @@ -435,7 +435,7 @@ -

    portion_R() portion_IR() portion_I() portion_SI() portion_S() portion_df()

    +

    portion_R() portion_IR() portion_I() portion_SI() portion_S() portion_df() rsi_df()

    Calculate resistance of isolates

    diff --git a/docs/reference/microorganisms.html b/docs/reference/microorganisms.html index 7ee907a2..7c0f2a1e 100644 --- a/docs/reference/microorganisms.html +++ b/docs/reference/microorganisms.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9000 + 0.7.0.9008 @@ -165,13 +165,6 @@ Create frequency tables
  • -
  • - - - - Use the G-test - -
  • @@ -252,7 +245,7 @@

    Format

    -

    A data.frame with 67,903 observations and 16 variables:

    +

    A data.frame with 67,906 observations and 16 variables:

    mo

    ID of microorganism as used by this package

    col_id

    Catalogue of Life ID

    fullname

    Full name, like "Escherichia coli"

    @@ -272,9 +265,10 @@

    Details

    Manually added were:

      -
    • 9 species of Streptococcus (beta haemolytic groups A, B, C, D, F, G, H, K and unspecified)

    • -
    • 2 species of Staphylococcus (coagulase-negative [CoNS] and coagulase-positive [CoPS])

    • -
    • 3 other undefined (unknown, unknown Gram negatives and unknown Gram positives)

    • +
    • 9 entries of Streptococcus (beta haemolytic groups A, B, C, D, F, G, H, K and unspecified)

    • +
    • 2 entries of Staphylococcus (coagulase-negative [CoNS] and coagulase-positive [CoPS])

    • +
    • 3 entries of Trichomonas (Trichomonas vaginalis, and its family and genus)

    • +
    • 3 other 'undefined' entries (unknown, unknown Gram negatives and unknown Gram positives)

    • 8,830 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) that are not in the Catalogue of Life

    diff --git a/docs/reference/portion.html b/docs/reference/portion.html index 96016462..ff3984a5 100644 --- a/docs/reference/portion.html +++ b/docs/reference/portion.html @@ -81,7 +81,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port AMR (for R) - 0.7.0.9000 + 0.7.0.9008 @@ -166,13 +166,6 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port Create frequency tables
  • -
  • - - - - Use the G-test - -
  • @@ -266,6 +259,10 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port also_single_tested = FALSE) portion_df(data, translate_ab = "name", language = get_locale(), + minimum = 30, as_percent = FALSE, combine_SI = TRUE, + combine_IR = FALSE) + +rsi_df(data, translate_ab = "name", language = get_locale(), minimum = 30, as_percent = FALSE, combine_SI = TRUE, combine_IR = FALSE) @@ -323,7 +320,8 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port

    Remember that you should filter your table to let it contain only first isolates! Use first_isolate to determine them in your data set.

    These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the count functions to count isolates. Low counts can infuence the outcome - these portion functions may camouflage this, since they only return the portion albeit being dependent on the minimum parameter.

    -

    portion_df takes any variable from data that has an "rsi" class (created with as.rsi) and calculates the portions R, I and S. The resulting tidy data (see Source) data.frame will have three rows (S/I/R) and a column for each variable with class "rsi". +

    The function portion_df takes any variable from data that has an "rsi" class (created with as.rsi) and calculates the portions R, I and S. The resulting tidy data (see Source) data.frame will have three rows (S/I/R) and a column for each group and each variable with class "rsi".

    +

    The function rsi_df works exactly like portion_df, but add the number of isolates.

    To calculate the probability (p) of susceptibility of one antibiotic, we use this formula:

    diff --git a/man/count.Rd b/man/count.Rd index fb6af2bb..e38f7252 100644 --- a/man/count.Rd +++ b/man/count.Rd @@ -58,9 +58,11 @@ These functions can be used to count resistant/susceptible microbial isolates. A \details{ These functions are meant to count isolates. Use the \code{\link{portion}_*} functions to calculate microbial resistance. -\code{n_rsi} is an alias of \code{count_all}. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to \code{\link{n_distinct}}. Their function is equal to \code{count_S(...) + count_IR(...)}. +The function \code{n_rsi} is an alias of \code{count_all}. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to \code{\link{n_distinct}}. Their function is equal to \code{count_S(...) + count_IR(...)}. -\code{count_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and counts the amounts of R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}. +The function \code{count_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and counts the amounts of S, I and R. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}. + +The function \code{rsi_df} works exactly like \code{count_df}, but add the percentage of S, I and R. } \section{Interpretation of S, I and R}{ diff --git a/man/ggplot_rsi.Rd b/man/ggplot_rsi.Rd index efc9b2a3..d87e21b6 100644 --- a/man/ggplot_rsi.Rd +++ b/man/ggplot_rsi.Rd @@ -10,8 +10,8 @@ \alias{labels_rsi_count} \title{AMR plots with \code{ggplot2}} \usage{ -ggplot_rsi(data, position = NULL, x = "Antibiotic", - fill = "Interpretation", facet = NULL, breaks = seq(0, 1, 0.1), +ggplot_rsi(data, position = NULL, x = "antibiotic", + fill = "interpretation", facet = NULL, breaks = seq(0, 1, 0.1), limits = NULL, translate_ab = "name", combine_SI = TRUE, combine_IR = FALSE, language = get_locale(), fun = count_df, nrow = NULL, colours = c(S = "#61a8ff", SI = "#61a8ff", I = @@ -20,12 +20,12 @@ ggplot_rsi(data, position = NULL, x = "Antibiotic", subtitle = NULL, caption = NULL, x.title = NULL, y.title = NULL, ...) -geom_rsi(position = NULL, x = c("Antibiotic", "Interpretation"), - fill = "Interpretation", translate_ab = "name", +geom_rsi(position = NULL, x = c("antibiotic", "interpretation"), + fill = "interpretation", translate_ab = "name", language = get_locale(), combine_SI = TRUE, combine_IR = FALSE, fun = count_df, ...) -facet_rsi(facet = c("Interpretation", "Antibiotic"), nrow = NULL) +facet_rsi(facet = c("interpretation", "antibiotic"), nrow = NULL) scale_y_percent(breaks = seq(0, 1, 0.1), limits = NULL) @@ -34,7 +34,7 @@ scale_rsi_colours(colours = c(S = "#61a8ff", SI = "#61a8ff", I = theme_rsi() -labels_rsi_count(position = NULL, x = "Antibiotic", +labels_rsi_count(position = NULL, x = "antibiotic", translate_ab = "name", combine_SI = TRUE, combine_IR = FALSE, datalabels.size = 3, datalabels.colour = "gray15") } @@ -43,11 +43,11 @@ labels_rsi_count(position = NULL, x = "Antibiotic", \item{position}{position adjustment of bars, either \code{"fill"} (default when \code{fun} is \code{\link{count_df}}), \code{"stack"} (default when \code{fun} is \code{\link{portion_df}}) or \code{"dodge"}} -\item{x}{variable to show on x axis, either \code{"Antibiotic"} (default) or \code{"Interpretation"} or a grouping variable} +\item{x}{variable to show on x axis, either \code{"antibiotic"} (default) or \code{"interpretation"} or a grouping variable} -\item{fill}{variable to categorise using the plots legend, either \code{"Antibiotic"} (default) or \code{"Interpretation"} or a grouping variable} +\item{fill}{variable to categorise using the plots legend, either \code{"antibiotic"} (default) or \code{"interpretation"} or a grouping variable} -\item{facet}{variable to split plots by, either \code{"Interpretation"} (default) or \code{"Antibiotic"} or a grouping variable} +\item{facet}{variable to split plots by, either \code{"interpretation"} (default) or \code{"antibiotic"} or a grouping variable} \item{breaks}{numeric vector of positions} @@ -178,7 +178,7 @@ septic_patients \%>\% select(hospital_id, AMX, NIT, FOS, TMP, CIP) \%>\% group_by(hospital_id) \%>\% ggplot_rsi(x = "hospital_id", - facet = "Antibiotic", + facet = "antibiotic", nrow = 1, title = "AMR of Anti-UTI Drugs Per Hospital", x.title = "Hospital", @@ -199,7 +199,7 @@ septic_patients \%>\% # group by MO group_by(bug) \%>\% # plot the thing, putting MOs on the facet - ggplot_rsi(x = "Antibiotic", + ggplot_rsi(x = "antibiotic", facet = "bug", translate_ab = FALSE, nrow = 1, diff --git a/man/microorganisms.Rd b/man/microorganisms.Rd index ba502cb8..7df34f03 100755 --- a/man/microorganisms.Rd +++ b/man/microorganisms.Rd @@ -4,7 +4,7 @@ \name{microorganisms} \alias{microorganisms} \title{Data set with ~65,000 microorganisms} -\format{A \code{\link{data.frame}} with 67,903 observations and 16 variables: +\format{A \code{\link{data.frame}} with 67,906 observations and 16 variables: \describe{ \item{\code{mo}}{ID of microorganism as used by this package} \item{\code{col_id}}{Catalogue of Life ID} @@ -30,9 +30,10 @@ A data set containing the microbial taxonomy of six kingdoms from the Catalogue \details{ Manually added were: \itemize{ - \item{9 species of \emph{Streptococcus} (beta haemolytic groups A, B, C, D, F, G, H, K and unspecified)} - \item{2 species of \emph{Staphylococcus} (coagulase-negative [CoNS] and coagulase-positive [CoPS])} - \item{3 other undefined (unknown, unknown Gram negatives and unknown Gram positives)} + \item{9 entries of \emph{Streptococcus} (beta haemolytic groups A, B, C, D, F, G, H, K and unspecified)} + \item{2 entries of \emph{Staphylococcus} (coagulase-negative [CoNS] and coagulase-positive [CoPS])} + \item{3 entries of Trichomonas (Trichomonas vaginalis, and its family and genus)} + \item{3 other 'undefined' entries (unknown, unknown Gram negatives and unknown Gram positives)} \item{8,830 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) that are not in the Catalogue of Life} } } diff --git a/man/portion.Rd b/man/portion.Rd index f4a0965f..eefc4028 100644 --- a/man/portion.Rd +++ b/man/portion.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/portion.R +% Please edit documentation in R/portion.R, R/rsi_df.R \name{portion} \alias{portion} \alias{portion_R} @@ -8,6 +8,7 @@ \alias{portion_SI} \alias{portion_S} \alias{portion_df} +\alias{rsi_df} \title{Calculate resistance of isolates} \source{ \strong{M39 Analysis and Presentation of Cumulative Antimicrobial Susceptibility Test Data, 4th Edition}, 2014, \emph{Clinical and Laboratory Standards Institute (CLSI)}. \url{https://clsi.org/standards/products/microbiology/documents/m39/}. @@ -33,6 +34,10 @@ portion_S(..., minimum = 30, as_percent = FALSE, portion_df(data, translate_ab = "name", language = get_locale(), minimum = 30, as_percent = FALSE, combine_SI = TRUE, combine_IR = FALSE) + +rsi_df(data, translate_ab = "name", language = get_locale(), + minimum = 30, as_percent = FALSE, combine_SI = TRUE, + combine_IR = FALSE) } \arguments{ \item{...}{one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with \code{\link{as.rsi}} if needed. Use multiple columns to calculate (the lack of) co-resistance: the probability where one of two drugs have a resistant or susceptible result. See Examples.} @@ -66,7 +71,9 @@ These functions can be used to calculate the (co-)resistance of microbial isolat These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. \emph{Low counts can infuence the outcome - these \code{portion} functions may camouflage this, since they only return the portion albeit being dependent on the \code{minimum} parameter.} -\code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}. +The function \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each group and each variable with class \code{"rsi"}. + +The function \code{rsi_df} works exactly like \code{portion_df}, but add the number of isolates. \if{html}{ \cr\cr To calculate the probability (\emph{p}) of susceptibility of one antibiotic, we use this formula: diff --git a/tests/testthat/test-count.R b/tests/testthat/test-count.R index 0d3b0840..4f4f4c3e 100644 --- a/tests/testthat/test-count.R +++ b/tests/testthat/test-count.R @@ -50,17 +50,17 @@ test_that("counts work", { # count_df expect_equal( - septic_patients %>% select(AMX) %>% count_df() %>% pull(Value), + septic_patients %>% select(AMX) %>% count_df() %>% pull(value), c(septic_patients$AMX %>% count_SI(), septic_patients$AMX %>% count_R()) ) expect_equal( - septic_patients %>% select(AMX) %>% count_df(combine_IR = TRUE) %>% pull(Value), + septic_patients %>% select(AMX) %>% count_df(combine_IR = TRUE) %>% pull(value), c(septic_patients$AMX %>% count_S(), septic_patients$AMX %>% count_IR()) ) expect_equal( - septic_patients %>% select(AMX) %>% count_df(combine_SI = FALSE) %>% pull(Value), + septic_patients %>% select(AMX) %>% count_df(combine_SI = FALSE) %>% pull(value), c(septic_patients$AMX %>% count_S(), septic_patients$AMX %>% count_I(), septic_patients$AMX %>% count_R()) diff --git a/tests/testthat/test-portion.R b/tests/testthat/test-portion.R index 2135bf5d..84599859 100755 --- a/tests/testthat/test-portion.R +++ b/tests/testthat/test-portion.R @@ -100,17 +100,17 @@ test_that("portions works", { # portion_df expect_equal( - septic_patients %>% select(AMX) %>% portion_df() %>% pull(Value), + septic_patients %>% select(AMX) %>% portion_df() %>% pull(value), c(septic_patients$AMX %>% portion_SI(), septic_patients$AMX %>% portion_R()) ) expect_equal( - septic_patients %>% select(AMX) %>% portion_df(combine_IR = TRUE) %>% pull(Value), + septic_patients %>% select(AMX) %>% portion_df(combine_IR = TRUE) %>% pull(value), c(septic_patients$AMX %>% portion_S(), septic_patients$AMX %>% portion_IR()) ) expect_equal( - septic_patients %>% select(AMX) %>% portion_df(combine_SI = FALSE) %>% pull(Value), + septic_patients %>% select(AMX) %>% portion_df(combine_SI = FALSE) %>% pull(value), c(septic_patients$AMX %>% portion_S(), septic_patients$AMX %>% portion_I(), septic_patients$AMX %>% portion_R())