diff --git a/DESCRIPTION b/DESCRIPTION index 255d5700..53a4494b 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 0.7.1.9062 -Date: 2019-08-26 +Version: 0.7.1.9063 +Date: 2019-08-27 Title: Antimicrobial Resistance Analysis Authors@R: c( person(role = c("aut", "cre"), diff --git a/NEWS.md b/NEWS.md index c0e20796..a310a5a4 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# AMR 0.7.1.9062 +# AMR 0.7.1.9063 ### Breaking * Determination of first isolates now **excludes** all 'unknown' microorganisms at default, i.e. microbial code `"UNKNOWN"`. They can be included with the new parameter `include_unknown`: @@ -37,7 +37,7 @@ ``` You can format this to a printable format, ready for reporting or exporting to e.g. Excel with the base R `format()` function: ```r - format(x) + format(x, combine_SI = TRUE) ``` * Additional way to calculate co-resistance, i.e. when using multiple antimicrobials as input for `portion_*` functions or `count_*` functions. This can be used to determine the empiric susceptibily of a combination therapy. A new parameter `only_all_tested` (**which defaults to `FALSE`**) replaces the old `also_single_tested` and can be used to select one of the two methods to count isolates and calculate portions. The difference can be seen in this example table (which is also on the `portion` and `count` help pages), where the %SI is being determined: @@ -71,7 +71,8 @@ ``` ### Changed -* Function: `eucast_rules()` +* Renamed data set `septic_patients` to `example_isolates` +* Function `eucast_rules()`: * Fixed a bug for *Yersinia pseudotuberculosis* * Added more informative errors and warnings * Printed info now distinguishes between added and changes values diff --git a/R/age.R b/R/age.R index 76144bb7..b11ea31d 100755 --- a/R/age.R +++ b/R/age.R @@ -129,7 +129,7 @@ age <- function(x, reference = Sys.Date(), exact = FALSE) { #' #' # resistance of ciprofloxacine per age group #' library(dplyr) -#' septic_patients %>% +#' example_isolates %>% #' filter_first_isolate() %>% #' filter(mo == as.mo("E. coli")) %>% #' group_by(age_group = age_groups(age)) %>% diff --git a/R/availability.R b/R/availability.R index e6e1bf43..2163b5e1 100644 --- a/R/availability.R +++ b/R/availability.R @@ -29,16 +29,16 @@ #' @inheritSection AMR Read more on our website! #' @export #' @examples -#' availability(septic_patients) +#' availability(example_isolates) #' #' library(dplyr) -#' septic_patients %>% availability() +#' example_isolates %>% availability() #' -#' septic_patients %>% +#' example_isolates %>% #' select_if(is.rsi) %>% #' availability() #' -#' septic_patients %>% +#' example_isolates %>% #' filter(mo == as.mo("E. coli")) %>% #' select_if(is.rsi) %>% #' availability() diff --git a/R/bug_drug_combinations.R b/R/bug_drug_combinations.R index ef32b5b4..f928df72 100644 --- a/R/bug_drug_combinations.R +++ b/R/bug_drug_combinations.R @@ -23,16 +23,18 @@ #' #' Determine antimicrobial resistance (AMR) of all bug-drug combinations in your data set where at least 30 (default) isolates are available per species. Use \code{format} on the result to prettify it to a printable format, see Examples. #' @inheritParams eucast_rules +#' @param combine_RI logical to indicate whether values R and I should be summed #' @inheritParams rsi_df #' @importFrom dplyr rename #' @importFrom tidyr spread #' @importFrom clean freq +#' @details The function \code{format} calculated the resistance per bug-drug combination. Use \code{combine_RI = FALSE} (default) to test R vs. S+I and \code{combine_RI = TRUE} to test R+I vs. S. #' @export #' @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/}. #' @inheritSection AMR Read more on our website! #' @examples #' \donttest{ -#' x <- bug_drug_combinations(septic_patients) +#' x <- bug_drug_combinations(example_isolates) #' x #' format(x) #' } @@ -70,8 +72,8 @@ bug_drug_combinations <- function(x, col_mo = NULL, minimum = 30) { #' @importFrom tidyr spread #' @exportMethod format.bugdrug #' @export -format.bugdrug <- function(x, combine_SI = TRUE, add_ab_group = TRUE, ...) { - if (combine_SI == TRUE) { +format.bugdrug <- function(x, combine_RI = FALSE, add_ab_group = TRUE, ...) { + if (combine_RI == FALSE) { x$isolates <- x$R } else { x$isolates <- x$R + x$I diff --git a/R/count.R b/R/count.R index 0a03d22e..7bcbf626 100755 --- a/R/count.R +++ b/R/count.R @@ -44,29 +44,29 @@ #' @export #' @inheritSection AMR Read more on our website! #' @examples -#' # septic_patients is a data set available in the AMR package. It is true, genuine data. -#' ?septic_patients +#' # example_isolates is a data set available in the AMR package. +#' ?example_isolates #' #' # Count resistant isolates -#' count_R(septic_patients$AMX) -#' count_IR(septic_patients$AMX) +#' count_R(example_isolates$AMX) +#' count_IR(example_isolates$AMX) #' #' # Or susceptible isolates -#' count_S(septic_patients$AMX) -#' count_SI(septic_patients$AMX) +#' count_S(example_isolates$AMX) +#' count_SI(example_isolates$AMX) #' #' # Count all available isolates -#' count_all(septic_patients$AMX) -#' n_rsi(septic_patients$AMX) +#' count_all(example_isolates$AMX) +#' n_rsi(example_isolates$AMX) #' #' # Since n_rsi counts available isolates, you can #' # calculate back to count e.g. non-susceptible isolates. #' # This results in the same: -#' count_SI(septic_patients$AMX) -#' portion_SI(septic_patients$AMX) * n_rsi(septic_patients$AMX) +#' count_SI(example_isolates$AMX) +#' portion_SI(example_isolates$AMX) * n_rsi(example_isolates$AMX) #' #' library(dplyr) -#' septic_patients %>% +#' example_isolates %>% #' group_by(hospital_id) %>% #' summarise(R = count_R(CIP), #' I = count_I(CIP), @@ -78,24 +78,24 @@ #' # Count co-resistance between amoxicillin/clav acid and gentamicin, #' # so we can see that combination therapy does a lot more than mono therapy. #' # Please mind that `portion_SI` calculates percentages right away instead. -#' count_SI(septic_patients$AMC) # 1433 -#' count_all(septic_patients$AMC) # 1879 +#' count_SI(example_isolates$AMC) # 1433 +#' count_all(example_isolates$AMC) # 1879 #' -#' count_SI(septic_patients$GEN) # 1399 -#' count_all(septic_patients$GEN) # 1855 +#' count_SI(example_isolates$GEN) # 1399 +#' count_all(example_isolates$GEN) # 1855 #' -#' with(septic_patients, +#' with(example_isolates, #' count_SI(AMC, GEN)) # 1764 -#' with(septic_patients, +#' with(example_isolates, #' n_rsi(AMC, GEN)) # 1936 #' #' # Get portions S/I/R immediately of all rsi columns -#' septic_patients %>% +#' example_isolates %>% #' select(AMX, CIP) %>% #' count_df(translate = FALSE) #' #' # It also supports grouping variables -#' septic_patients %>% +#' example_isolates %>% #' select(hospital_id, AMX, CIP) %>% #' group_by(hospital_id) %>% #' count_df(translate = FALSE) diff --git a/R/data.R b/R/data.R index 0a506dd6..9fe927f6 100755 --- a/R/data.R +++ b/R/data.R @@ -125,7 +125,7 @@ catalogue_of_life <- list( #' Data set with 2,000 blood culture isolates from septic patients #' -#' An anonymised data set containing 2,000 microbial blood culture isolates with their full antibiograms found in septic patients in 4 different hospitals in the Netherlands, between 2001 and 2017. It is true, genuine data. This \code{data.frame} can be used to practice AMR analysis. For examples, please read \href{https://msberends.gitlab.io/AMR/articles/AMR.html}{the tutorial on our website}. +#' An anonymised data set containing 2,000 microbial blood culture isolates with their full antibiograms found in septic patients in 4 different hospitals in the Netherlands, between 2001 and 2017. This \code{data.frame} can be used to practice AMR analysis. For examples, please read \href{https://msberends.gitlab.io/AMR/articles/AMR.html}{the tutorial on our website}. #' @format A \code{\link{data.frame}} with 2,000 observations and 49 variables: #' \describe{ #' \item{\code{date}}{date of receipt at the laboratory} @@ -140,11 +140,11 @@ catalogue_of_life <- list( #' \item{\code{peni:rifa}}{40 different antibiotics with class \code{rsi} (see \code{\link{as.rsi}}); these column names occur in \code{\link{antibiotics}} data set and can be translated with \code{\link{ab_name}}} #' } #' @inheritSection AMR Read more on our website! -"septic_patients" +"example_isolates" #' Data set with 500 isolates - WHONET example #' -#' This example data set has the exact same structure as an export file from WHONET. Such files can be used with this package, as this example data set shows. The data itself was based on our \code{\link{septic_patients}} data set. +#' This example data set has the exact same structure as an export file from WHONET. Such files can be used with this package, as this example data set shows. The data itself was based on our \code{\link{example_isolates}} data set. #' @format A \code{\link{data.frame}} with 500 observations and 53 variables: #' \describe{ #' \item{\code{Identification number}}{ID of the sample} diff --git a/R/filter_ab_class.R b/R/filter_ab_class.R index 1f5ea37d..634aa8d2 100644 --- a/R/filter_ab_class.R +++ b/R/filter_ab_class.R @@ -37,29 +37,29 @@ #' library(dplyr) #' #' # filter on isolates that have any result for any aminoglycoside -#' septic_patients %>% filter_aminoglycosides() +#' example_isolates %>% filter_aminoglycosides() #' #' # this is essentially the same as (but without determination of column names): -#' septic_patients %>% +#' example_isolates %>% #' filter_at(.vars = vars(c("GEN", "TOB", "AMK", "KAN")), #' .vars_predicate = any_vars(. %in% c("S", "I", "R"))) #' #' #' # filter on isolates that show resistance to ANY aminoglycoside -#' septic_patients %>% filter_aminoglycosides("R") +#' example_isolates %>% filter_aminoglycosides("R") #' #' # filter on isolates that show resistance to ALL aminoglycosides -#' septic_patients %>% filter_aminoglycosides("R", "all") +#' example_isolates %>% filter_aminoglycosides("R", "all") #' #' # filter on isolates that show resistance to #' # any aminoglycoside and any fluoroquinolone -#' septic_patients %>% +#' example_isolates %>% #' filter_aminoglycosides("R") %>% #' filter_fluoroquinolones("R") #' #' # filter on isolates that show resistance to #' # all aminoglycosides and all fluoroquinolones -#' septic_patients %>% +#' example_isolates %>% #' filter_aminoglycosides("R", "all") %>% #' filter_fluoroquinolones("R", "all") filter_ab_class <- function(x, diff --git a/R/first_isolate.R b/R/first_isolate.R index 50baae75..821d9f72 100755 --- a/R/first_isolate.R +++ b/R/first_isolate.R @@ -79,12 +79,12 @@ #' @source Methodology of this function is based on: \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/}. #' @inheritSection AMR Read more on our website! #' @examples -#' # `septic_patients` is a dataset available in the AMR package. It is true, genuine data. -#' # See ?septic_patients. +#' # `example_isolates` is a dataset available in the AMR package. +#' # See ?example_isolates. #' #' library(dplyr) #' # Filter on first isolates: -#' septic_patients %>% +#' example_isolates %>% #' mutate(first_isolate = first_isolate(., #' col_date = "date", #' col_patient_id = "patient_id", @@ -92,19 +92,19 @@ #' filter(first_isolate == TRUE) #' #' # Which can be shortened to: -#' septic_patients %>% +#' example_isolates %>% #' filter_first_isolate() #' # or for first weighted isolates: -#' septic_patients %>% +#' example_isolates %>% #' filter_first_weighted_isolate() #' #' # Now let's see if first isolates matter: -#' A <- septic_patients %>% +#' A <- example_isolates %>% #' group_by(hospital_id) %>% #' summarise(count = n_rsi(GEN), # gentamicin availability #' resistance = portion_IR(GEN)) # gentamicin resistance #' -#' B <- septic_patients %>% +#' B <- example_isolates %>% #' filter_first_weighted_isolate() %>% # the 1st isolate filter #' group_by(hospital_id) %>% #' summarise(count = n_rsi(GEN), # gentamicin availability diff --git a/R/ggplot_rsi.R b/R/ggplot_rsi.R index c54050e3..4a4df5fd 100755 --- a/R/ggplot_rsi.R +++ b/R/ggplot_rsi.R @@ -66,11 +66,11 @@ #' library(ggplot2) #' #' # get antimicrobial results for drugs against a UTI: -#' ggplot(septic_patients %>% select(AMX, NIT, FOS, TMP, CIP)) + +#' ggplot(example_isolates %>% select(AMX, NIT, FOS, TMP, CIP)) + #' geom_rsi() #' #' # prettify the plot using some additional functions: -#' df <- septic_patients %>% select(AMX, NIT, FOS, TMP, CIP) +#' df <- example_isolates %>% select(AMX, NIT, FOS, TMP, CIP) #' ggplot(df) + #' geom_rsi() + #' scale_y_percent() + @@ -79,17 +79,17 @@ #' theme_rsi() #' #' # or better yet, simplify this using the wrapper function - a single command: -#' septic_patients %>% +#' example_isolates %>% #' select(AMX, NIT, FOS, TMP, CIP) %>% #' ggplot_rsi() #' #' # get only portions and no counts: -#' septic_patients %>% +#' example_isolates %>% #' select(AMX, NIT, FOS, TMP, CIP) %>% #' ggplot_rsi(datalabels = FALSE) #' #' # add other ggplot2 parameters as you like: -#' septic_patients %>% +#' example_isolates %>% #' select(AMX, NIT, FOS, TMP, CIP) %>% #' ggplot_rsi(width = 0.5, #' colour = "black", @@ -97,12 +97,12 @@ #' linetype = 2, #' alpha = 0.25) #' -#' septic_patients %>% +#' example_isolates %>% #' select(AMX) %>% #' ggplot_rsi(colours = c(SI = "yellow")) #' #' # resistance of ciprofloxacine per age group -#' septic_patients %>% +#' example_isolates %>% #' mutate(first_isolate = first_isolate(.)) %>% #' filter(first_isolate == TRUE, #' mo == as.mo("E. coli")) %>% @@ -114,17 +114,17 @@ #' \donttest{ #' #' # for colourblind mode, use divergent colours from the viridis package: -#' septic_patients %>% +#' example_isolates %>% #' select(AMX, NIT, FOS, TMP, CIP) %>% #' ggplot_rsi() + scale_fill_viridis_d() #' # a shorter version which also adjusts data label colours: -#' septic_patients %>% +#' example_isolates %>% #' select(AMX, NIT, FOS, TMP, CIP) %>% #' ggplot_rsi(colours = FALSE) #' #' #' # it also supports groups (don't forget to use the group var on `x` or `facet`): -#' septic_patients %>% +#' example_isolates %>% #' select(hospital_id, AMX, NIT, FOS, TMP, CIP) %>% #' group_by(hospital_id) %>% #' ggplot_rsi(x = "hospital_id", @@ -135,7 +135,7 @@ #' datalabels = FALSE) #' #' # genuine analysis: check 3 most prevalent microorganisms -#' septic_patients %>% +#' example_isolates %>% #' # create new bacterial ID's, with all CoNS under the same group (Becker et al.) #' mutate(mo = as.mo(mo, Becker = TRUE)) %>% #' # filter on top three bacterial ID's diff --git a/R/guess_ab_col.R b/R/guess_ab_col.R index a642da8b..ce7a9161 100755 --- a/R/guess_ab_col.R +++ b/R/guess_ab_col.R @@ -129,7 +129,7 @@ get_column_abx <- function(x, names(x) <- df_trans$abcode # add from self-defined dots (...): - # get_column_abx(septic_patients %>% rename(thisone = AMX), amox = "thisone") + # get_column_abx(example_isolates %>% rename(thisone = AMX), amox = "thisone") dots <- list(...) if (length(dots) > 0) { newnames <- suppressWarnings(as.ab(names(dots))) diff --git a/R/join_microorganisms.R b/R/join_microorganisms.R index 7121f613..fb5a6001 100755 --- a/R/join_microorganisms.R +++ b/R/join_microorganisms.R @@ -37,7 +37,7 @@ #' left_join_microorganisms("B_KLBSL_PNE") #' #' library(dplyr) -#' septic_patients %>% left_join_microorganisms() +#' example_isolates %>% left_join_microorganisms() #' #' df <- data.frame(date = seq(from = as.Date("2018-01-01"), #' to = as.Date("2018-01-07"), diff --git a/R/key_antibiotics.R b/R/key_antibiotics.R index f802492f..71ebb29c 100755 --- a/R/key_antibiotics.R +++ b/R/key_antibiotics.R @@ -48,12 +48,12 @@ #' @seealso \code{\link{first_isolate}} #' @inheritSection AMR Read more on our website! #' @examples -#' # `septic_patients` is a dataset available in the AMR package. It is true, genuine data. -#' # See ?septic_patients. +#' # `example_isolates` is a dataset available in the AMR package. +#' # See ?example_isolates. #' #' library(dplyr) #' # set key antibiotics to a new variable -#' my_patients <- septic_patients %>% +#' my_patients <- example_isolates %>% #' mutate(keyab = key_antibiotics(.)) %>% #' mutate( #' # now calculate first isolates diff --git a/R/like.R b/R/like.R index 2ab07bdc..f69d5fe8 100755 --- a/R/like.R +++ b/R/like.R @@ -49,7 +49,7 @@ #' # get frequencies of bacteria whose name start with 'Ent' or 'ent' #' library(dplyr) #' library(clean) -#' septic_patients %>% +#' example_isolates %>% #' left_join_microorganisms() %>% #' filter(genus %like% '^ent') %>% #' freq(genus, species) diff --git a/R/mdro.R b/R/mdro.R index 8ce9d928..ea61aed2 100755 --- a/R/mdro.R +++ b/R/mdro.R @@ -54,7 +54,7 @@ #' @examples #' library(dplyr) #' -#' septic_patients %>% +#' example_isolates %>% #' mutate(EUCAST = mdro(.), #' BRMO = brmo(.)) mdro <- function(x, diff --git a/R/portion.R b/R/portion.R index 9e6c9cf4..7357eb32 100755 --- a/R/portion.R +++ b/R/portion.R @@ -86,31 +86,31 @@ #' @export #' @inheritSection AMR Read more on our website! #' @examples -#' # septic_patients is a data set available in the AMR package. It is true, genuine data. -#' ?septic_patients +#' # example_isolates is a data set available in the AMR package. +#' ?example_isolates #' #' # Calculate resistance -#' portion_R(septic_patients$AMX) -#' portion_IR(septic_patients$AMX) +#' portion_R(example_isolates$AMX) +#' portion_IR(example_isolates$AMX) #' #' # Or susceptibility -#' portion_S(septic_patients$AMX) -#' portion_SI(septic_patients$AMX) +#' portion_S(example_isolates$AMX) +#' portion_SI(example_isolates$AMX) #' #' # Do the above with pipes: #' library(dplyr) -#' septic_patients %>% portion_R(AMX) -#' septic_patients %>% portion_IR(AMX) -#' septic_patients %>% portion_S(AMX) -#' septic_patients %>% portion_SI(AMX) +#' example_isolates %>% portion_R(AMX) +#' example_isolates %>% portion_IR(AMX) +#' example_isolates %>% portion_S(AMX) +#' example_isolates %>% portion_SI(AMX) #' -#' septic_patients %>% +#' example_isolates %>% #' group_by(hospital_id) %>% #' summarise(p = portion_SI(CIP), #' n = n_rsi(CIP)) # n_rsi works like n_distinct in dplyr #' -#' septic_patients %>% +#' example_isolates %>% #' group_by(hospital_id) %>% #' summarise(R = portion_R(CIP, as_percent = TRUE), #' I = portion_I(CIP, as_percent = TRUE), @@ -121,24 +121,24 @@ #' #' # Calculate co-resistance between amoxicillin/clav acid and gentamicin, #' # so we can see that combination therapy does a lot more than mono therapy: -#' septic_patients %>% portion_SI(AMC) # %SI = 76.3% -#' septic_patients %>% count_all(AMC) # n = 1879 +#' example_isolates %>% portion_SI(AMC) # %SI = 76.3% +#' example_isolates %>% count_all(AMC) # n = 1879 #' -#' septic_patients %>% portion_SI(GEN) # %SI = 75.4% -#' septic_patients %>% count_all(GEN) # n = 1855 +#' example_isolates %>% portion_SI(GEN) # %SI = 75.4% +#' example_isolates %>% count_all(GEN) # n = 1855 #' -#' septic_patients %>% portion_SI(AMC, GEN) # %SI = 94.1% -#' septic_patients %>% count_all(AMC, GEN) # n = 1939 +#' example_isolates %>% portion_SI(AMC, GEN) # %SI = 94.1% +#' example_isolates %>% count_all(AMC, GEN) # n = 1939 #' #' #' # See Details on how `only_all_tested` works. Example: -#' septic_patients %>% +#' example_isolates %>% #' summarise(numerator = count_SI(AMC, GEN), #' denominator = count_all(AMC, GEN), #' portion = portion_SI(AMC, GEN)) #' # numerator denominator portion #' # 1764 1936 0.9408 -#' septic_patients %>% +#' example_isolates %>% #' summarise(numerator = count_SI(AMC, GEN, only_all_tested = TRUE), #' denominator = count_all(AMC, GEN, only_all_tested = TRUE), #' portion = portion_SI(AMC, GEN, only_all_tested = TRUE)) @@ -146,7 +146,7 @@ #' # 1687 1798 0.9383 #' #' -#' septic_patients %>% +#' example_isolates %>% #' group_by(hospital_id) %>% #' summarise(cipro_p = portion_SI(CIP, as_percent = TRUE), #' cipro_n = count_all(CIP), @@ -156,12 +156,12 @@ #' combination_n = count_all(CIP, GEN)) #' #' # Get portions S/I/R immediately of all rsi columns -#' septic_patients %>% +#' example_isolates %>% #' select(AMX, CIP) %>% #' portion_df(translate = FALSE) #' #' # It also supports grouping variables -#' septic_patients %>% +#' example_isolates %>% #' select(hospital_id, AMX, CIP) %>% #' group_by(hospital_id) %>% #' portion_df(translate = FALSE) diff --git a/R/resistance_predict.R b/R/resistance_predict.R index 33fb7f83..d769a26e 100755 --- a/R/resistance_predict.R +++ b/R/resistance_predict.R @@ -61,13 +61,13 @@ #' @importFrom dplyr %>% pull mutate mutate_at n group_by_at summarise filter filter_at all_vars n_distinct arrange case_when n_groups transmute ungroup #' @inheritSection AMR Read more on our website! #' @examples -#' x <- resistance_predict(septic_patients, col_ab = "AMX", year_min = 2010, model = "binomial") +#' x <- resistance_predict(example_isolates, col_ab = "AMX", year_min = 2010, model = "binomial") #' plot(x) #' ggplot_rsi_predict(x) #' #' # use dplyr so you can actually read it: #' library(dplyr) -#' x <- septic_patients %>% +#' x <- example_isolates %>% #' filter_first_isolate() %>% #' filter(mo_genus(mo) == "Staphylococcus") %>% #' resistance_predict("PEN", model = "binomial") @@ -82,7 +82,7 @@ #' # create nice plots with ggplot2 yourself #' if (!require(ggplot2)) { #' -#' data <- septic_patients %>% +#' data <- example_isolates %>% #' filter(mo == as.mo("E. coli")) %>% #' resistance_predict(col_ab = "AMX", #' col_date = "date", diff --git a/R/rsi.R b/R/rsi.R index d8938c45..8c5c50d1 100755 --- a/R/rsi.R +++ b/R/rsi.R @@ -79,12 +79,12 @@ #' #' # using dplyr's mutate #' library(dplyr) -#' septic_patients %>% +#' example_isolates %>% #' mutate_at(vars(PEN:RIF), as.rsi) #' #' #' # fastest way to transform all columns with already valid AB results to class `rsi`: -#' septic_patients %>% +#' example_isolates %>% #' mutate_if(is.rsi.eligible, #' as.rsi) #' diff --git a/R/rsi_calc.R b/R/rsi_calc.R index fdc08965..e80fb2c1 100755 --- a/R/rsi_calc.R +++ b/R/rsi_calc.R @@ -67,11 +67,11 @@ rsi_calc <- function(..., if ("data.frame" %in% class(dots_df)) { # data.frame passed with other columns, like: - # septic_patients %>% portion_S(amcl, gent) + # example_isolates %>% portion_S(amcl, gent) dots <- as.character(dots) dots <- dots[dots != "."] if (length(dots) == 0 | all(dots == "df")) { - # for complete data.frames, like septic_patients %>% select(amcl, gent) %>% portion_S() + # for complete data.frames, like example_isolates %>% select(amcl, gent) %>% portion_S() # and the old rsi function, that has "df" as name of the first parameter x <- dots_df } else { @@ -79,16 +79,16 @@ rsi_calc <- function(..., } } else if (ndots == 1) { # only 1 variable passed (can also be data.frame), like: - # portion_S(septic_patients$amcl) - # septic_patients$amcl %>% portion_S() + # portion_S(example_isolates$amcl) + # example_isolates$amcl %>% portion_S() x <- dots_df } else { # multiple variables passed without pipe, like: - # portion_S(septic_patients$amcl, septic_patients$gent) + # portion_S(example_isolates$amcl, example_isolates$gent) x <- NULL try(x <- as.data.frame(dots), silent = TRUE) if (is.null(x)) { - # support for: with(septic_patients, portion_S(amcl, gent)) + # support for: with(example_isolates, portion_S(amcl, gent)) x <- as.data.frame(rlang::list2(...)) } } diff --git a/_pkgdown.yml b/_pkgdown.yml index 8a8c5027..a4d8ac2f 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -143,7 +143,7 @@ reference: contents: - "`antibiotics`" - "`microorganisms`" - - "`septic_patients`" + - "`example_isolates`" - "`WHONET`" - "`microorganisms.codes`" - "`microorganisms.old`" diff --git a/data/example_isolates.rda b/data/example_isolates.rda new file mode 100644 index 00000000..2a00a286 Binary files /dev/null and b/data/example_isolates.rda differ diff --git a/data/septic_patients.rda b/data/septic_patients.rda deleted file mode 100755 index 3dab7fcd..00000000 Binary files a/data/septic_patients.rda and /dev/null differ diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index 8922f06f..b97e60ba 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.1.9062 + 0.7.1.9063 diff --git a/docs/articles/AMR.html b/docs/articles/AMR.html index e9624040..14fbcb40 100644 --- a/docs/articles/AMR.html +++ b/docs/articles/AMR.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.1.9055 + 0.7.1.9063 @@ -185,7 +185,7 @@

How to conduct AMR analysis

Matthijs S. Berends

-

13 August 2019

+

27 August 2019

@@ -194,7 +194,7 @@ -

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

+

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

Introduction

@@ -210,21 +210,21 @@ -2019-08-13 +2019-08-27 abcd Escherichia coli S S -2019-08-13 +2019-08-27 abcd Escherichia coli S R -2019-08-13 +2019-08-27 efgh Escherichia coli R @@ -320,10 +320,54 @@ -2012-12-02 -V1 +2014-06-23 +O4 +Hospital A +Escherichia coli +S +S +S +S +F + + +2016-10-05 +W5 +Hospital A +Escherichia coli +R +S +S +S +F + + +2017-12-26 +S8 +Hospital A +Escherichia coli +S +R +R +R +F + + +2011-11-26 +Z1 +Hospital A +Streptococcus pneumoniae +S +S +S +S +F + + +2014-04-03 +Y7 Hospital B -Staphylococcus aureus +Escherichia coli S I S @@ -331,59 +375,15 @@ F -2014-02-14 -E4 -Hospital D -Staphylococcus aureus -S -S -R -R -M - - -2011-11-09 -E3 -Hospital A -Escherichia coli -S -S -S -S -M - - -2011-11-19 -S8 +2012-06-06 +F9 Hospital B Escherichia coli S S S S -F - - -2016-07-28 -X9 -Hospital D -Streptococcus pneumoniae -S -S -R -S -F - - -2010-03-04 -T4 -Hospital A -Streptococcus pneumoniae -S -S -S -S -F +M @@ -406,8 +406,8 @@ # # Item Count Percent Cum. Count Cum. Percent # --- ----- ------- -------- ----------- ------------- -# 1 M 10,486 52.4% 10,486 52.4% -# 2 F 9,514 47.6% 20,000 100.0% +# 1 M 10,514 52.6% 10,514 52.6% +# 2 F 9,486 47.4% 20,000 100.0%

So, we can draw at least two conclusions immediately. From a data scientists perspective, the data looks clean: only values M and F. From a researchers perspective: there are slightly more men. Nothing we didn’t already know.

The data is already quite clean, but we still need to transform some variables. The bacteria column now consists of text, and we want to add more variables based on microbial IDs later on. So, we will transform this column to valid IDs. The mutate() function of the dplyr package makes this really easy:

data <- data %>%
@@ -437,14 +437,14 @@
 # Pasteurella multocida (no changes)
 # Staphylococcus (no changes)
 # Streptococcus groups A, B, C, G (no changes)
-# Streptococcus pneumoniae (1,452 values changed)
+# Streptococcus pneumoniae (1,504 values changed)
 # Viridans group streptococci (no changes)
 # 
 # EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)
-# Table 01: Intrinsic resistance in Enterobacteriaceae (1,313 values changed)
+# Table 01: Intrinsic resistance in Enterobacteriaceae (1,298 values changed)
 # Table 02: Intrinsic resistance in non-fermentative Gram-negative bacteria (no changes)
 # Table 03: Intrinsic resistance in other Gram-negative bacteria (no changes)
-# Table 04: Intrinsic resistance in Gram-positive bacteria (2,715 values changed)
+# Table 04: Intrinsic resistance in Gram-positive bacteria (2,705 values changed)
 # Table 08: Interpretive rules for B-lactam agents and Gram-positive cocci (no changes)
 # Table 09: Interpretive rules for B-lactam agents and Gram-negative rods (no changes)
 # Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins (no changes)
@@ -452,24 +452,24 @@
 # Table 13: Interpretive rules for quinolones (no changes)
 # 
 # Other rules
-# Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (2,240 values changed)
-# Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (123 values changed)
+# Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (2,323 values changed)
+# Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (118 values changed)
 # Non-EUCAST: piperacillin = R where piperacillin/tazobactam = R (no changes)
 # Non-EUCAST: piperacillin/tazobactam = S where piperacillin = S (no changes)
 # Non-EUCAST: trimethoprim = R where trimethoprim/sulfa = R (no changes)
 # Non-EUCAST: trimethoprim/sulfa = S where trimethoprim = S (no changes)
 # 
 # --------------------------------------------------------------------------
-# EUCAST rules affected 6,513 out of 20,000 rows, making a total of 7,843 edits
+# EUCAST rules affected 6,559 out of 20,000 rows, making a total of 7,948 edits
 # => added 0 test results
 # 
-# => changed 7,843 test results
-#    - 111 test results changed from S to I
-#    - 4,735 test results changed from S to R
-#    - 1,034 test results changed from I to S
-#    - 316 test results changed from I to R
-#    - 1,612 test results changed from R to S
-#    - 35 test results changed from R to I
+# => changed 7,948 test results
+#    - 115 test results changed from S to I
+#    - 4,723 test results changed from S to R
+#    - 1,098 test results changed from I to S
+#    - 338 test results changed from I to R
+#    - 1,648 test results changed from R to S
+#    - 26 test results changed from R to I
 # --------------------------------------------------------------------------
 # 
 # Use eucast_rules(..., verbose = TRUE) (on your original data) to get a data.frame with all specified edits instead.
@@ -497,7 +497,7 @@ # NOTE: Using column `bacteria` as input for `col_mo`. # NOTE: Using column `date` as input for `col_date`. # NOTE: Using column `patient_id` as input for `col_patient_id`. -# => Found 5,643 first isolates (28.2% of total)
+# => Found 5,672 first isolates (28.4% of total)

So only is suitable for resistance analysis! We can now filter on it with the filter() function, also from the dplyr package:

data_1st <- data %>% 
   filter(first == TRUE)
@@ -508,7 +508,7 @@

First weighted isolates

-

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

+

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

@@ -524,32 +524,32 @@ - - + + - - + + - - + + - + - - + + - + @@ -557,21 +557,21 @@ - - + + - + - - + + - + @@ -579,8 +579,8 @@ - - + + @@ -590,8 +590,8 @@ - - + + @@ -601,32 +601,32 @@ - - + + - - + + - - + + - + - + - - + + - + @@ -634,7 +634,7 @@
isolate
12010-01-12Q102010-02-15K7 B_ESCHR_COLRRSS S S TRUE
22010-01-16Q102010-03-24K7 B_ESCHR_COL RSR R S FALSE
32010-03-09Q102010-06-05K7 B_ESCHR_COLSR S R S
42010-03-31Q102010-07-16K7 B_ESCHR_COL I SRS S FALSE
52010-04-06Q102010-09-22K7 B_ESCHR_COLSR S S S
62010-05-24Q102011-01-18K7 B_ESCHR_COL S S
72010-05-25Q102011-01-26K7 B_ESCHR_COL S S
82010-07-08Q102011-02-11K7 B_ESCHR_COLSS R SSS FALSE
92010-10-22Q102011-02-17K7 B_ESCHR_COLRI S S SFALSETRUE
102010-11-30Q102011-04-01K7 B_ESCHR_COLRS S S S
-

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

+

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

If a column exists with a name like ‘key(…)ab’ the first_isolate() function will automatically use it and determine the first weighted isolates. Mind the NOTEs in below output:

data <- data %>% 
   mutate(keyab = key_antibiotics(.)) %>% 
@@ -645,7 +645,7 @@
 # NOTE: Using column `patient_id` as input for `col_patient_id`.
 # NOTE: Using column `keyab` as input for `col_keyantibiotics`. Use col_keyantibiotics = FALSE to prevent this.
 # [Criterion] Inclusion based on key antibiotics, ignoring I.
-# => Found 15,004 first weighted isolates (75.0% of total)
+# => Found 15,107 first weighted isolates (75.5% of total)
@@ -662,11 +662,11 @@ - - + + - - + + @@ -674,11 +674,11 @@ - - + + - + @@ -686,10 +686,10 @@ - - + + - + @@ -698,20 +698,32 @@ - - + + + + + + + + + + + + + + - - - - + + + + @@ -720,22 +732,10 @@ - - - - - - - - - - - - - - + + @@ -746,34 +746,34 @@ - - + + - - + + - - + + - + - + - - + + - + @@ -782,11 +782,11 @@
isolate
12010-01-12Q102010-02-15K7 B_ESCHR_COLRRSS S S TRUE
22010-01-16Q102010-03-24K7 B_ESCHR_COL RSR R S FALSE
32010-03-09Q102010-06-05K7 B_ESCHR_COLSR S R S
42010-03-31Q102010-07-16K7 B_ESCHR_COL I SSSFALSETRUE
52010-09-22K7B_ESCHR_COL R SSS FALSE FALSE
52010-04-06Q10
62011-01-18K7 B_ESCHR_COL S SFALSE TRUE
62010-05-24Q10B_ESCHR_COLSSSSFALSEFALSE
72010-05-25Q102011-01-26K7 B_ESCHR_COL S S
82010-07-08Q102011-02-11K7 B_ESCHR_COLSS R SSS FALSE TRUE
92010-10-22Q102011-02-17K7 B_ESCHR_COLRI S S SFALSETRUE TRUE
102010-11-30Q102011-04-01K7 B_ESCHR_COLRS S S S
-

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

+

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

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

data_1st <- data %>% 
   filter_first_weighted_isolate()
-

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

+

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

We can remove unneeded columns:

data_1st <- data_1st %>% 
   select(-c(first, keyab))
@@ -811,26 +811,10 @@ -2 -2014-02-14 -E4 -Hospital D -B_STPHY_AUR -S -S -R -R -M -Gram-positive -Staphylococcus -aureus -TRUE - - -4 -2011-11-19 -S8 -Hospital B +1 +2014-06-23 +O4 +Hospital A B_ESCHR_COL S S @@ -842,68 +826,84 @@ coli TRUE + +2 +2016-10-05 +W5 +Hospital A +B_ESCHR_COL +R +S +S +S +F +Gram-negative +Escherichia +coli +TRUE + -5 -2016-07-28 -X9 -Hospital D -B_STRPT_PNE +3 +2017-12-26 +S8 +Hospital A +B_ESCHR_COL S S R R F -Gram-positive -Streptococcus -pneumoniae +Gram-negative +Escherichia +coli TRUE -6 -2010-03-04 -T4 -Hospital A -B_STRPT_PNE +5 +2014-04-03 +Y7 +Hospital B +B_ESCHR_COL +S S S S -R F -Gram-positive -Streptococcus -pneumoniae +Gram-negative +Escherichia +coli TRUE 7 -2012-10-22 -Q6 -Hospital A -B_ESCHR_COL +2011-05-16 +I8 +Hospital D +B_KLBSL_PNE +R +S +S +S +M +Gram-negative +Klebsiella +pneumoniae +TRUE + + +8 +2014-12-28 +Z2 +Hospital B +B_STPHY_AUR S S S S F -Gram-negative -Escherichia -coli -TRUE - - -8 -2016-12-06 -B2 -Hospital B -B_STRPT_PNE -S -S -S -R -M Gram-positive -Streptococcus -pneumoniae +Staphylococcus +aureus TRUE @@ -925,7 +925,7 @@
data_1st %>% freq(genus, species)

Frequency table

Class: character
-Length: 15,004 (of which NA: 0 = 0.00%)
+Length: 15,107 (of which NA: 0 = 0.00%)
Unique: 4

Shortest: 16
Longest: 24

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

1 Escherichia coli -7,359 -49.0% -7,359 -49.0% +7,471 +49.5% +7,471 +49.5% 2 Staphylococcus aureus -3,800 -25.3% -11,159 -74.4% +3,789 +25.1% +11,260 +74.5% 3 Streptococcus pneumoniae -2,272 -15.1% -13,431 -89.5% +2,296 +15.2% +13,556 +89.7% 4 Klebsiella pneumoniae -1,573 -10.5% -15,004 +1,551 +10.3% +15,107 100.0% @@ -979,7 +979,7 @@ Longest: 24

Resistance percentages

The functions portion_S(), portion_SI(), portion_I(), portion_IR() and portion_R() can be used to determine the portion of a specific antimicrobial outcome. As per the EUCAST guideline of 2019, we calculate resistance as the portion of R (portion_R()) and susceptibility as the portion of S and I (portion_SI()). These functions can be used on their own:

data_1st %>% portion_R(AMX)
-# [1] 0.4674753
+# [1] 0.4685245

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

data_1st %>% 
   group_by(hospital) %>% 
@@ -992,19 +992,19 @@ Longest: 24

Hospital A -0.4635820 +0.4686054 Hospital B -0.4720092 +0.4644004 Hospital C -0.4717477 +0.4821269 Hospital D -0.4621821 +0.4655684 @@ -1022,23 +1022,23 @@ Longest: 24

Hospital A -0.4635820 -4517 +0.4686054 +4539 Hospital B -0.4720092 -5216 +0.4644004 +5295 Hospital C -0.4717477 -2283 +0.4821269 +2238 Hospital D -0.4621821 -2988 +0.4655684 +3035 @@ -1058,27 +1058,27 @@ Longest: 24

Escherichia -0.9244463 -0.8884359 -0.9930697 +0.9243742 +0.8933208 +0.9950475 Klebsiella -0.8207247 -0.9052765 -0.9860140 +0.8149581 +0.8884591 +0.9787234 Staphylococcus -0.9189474 -0.9250000 -0.9934211 +0.9192399 +0.9160728 +0.9912906 Streptococcus -0.6126761 +0.5997387 0.0000000 -0.6126761 +0.5997387 @@ -1151,9 +1151,9 @@ Longest: 24

Independence test

-

The next example uses the included septic_patients, which is an anonymised data set containing 2,000 microbial blood culture isolates with their full antibiograms found in septic patients in 4 different hospitals in the Netherlands, between 2001 and 2017. It is true, genuine data. This data.frame can be used to practice AMR analysis.

+

The next example uses the included example_isolates, which is an anonymised data set containing 2,000 microbial blood culture isolates with their full antibiograms found in septic patients in 4 different hospitals in the Netherlands, between 2001 and 2017. This data.frame can be used to practice AMR analysis.

We will compare the resistance to fosfomycin (column FOS) in hospital A and D. The input for the fisher.test() can be retrieved with a transformation like this:

-
check_FOS <- septic_patients %>%
+
check_FOS <- example_isolates %>%
   filter(hospital_id %in% c("A", "D")) %>% # filter on only hospitals A and D
   select(hospital_id, FOS) %>%             # select the hospitals and fosfomycin
   group_by(hospital_id) %>%                # group on the hospitals
@@ -1226,7 +1226,7 @@ Longest: 24

+# as.mo("sau") 8.1 8.1 8.3 8.3 8.4 8.6 10 +# as.mo("stau") 31.0 31.0 48.0 40.0 48.0 130.0 10 +# as.mo("staaur") 8.1 8.3 10.0 8.4 8.6 24.0 10 +# as.mo("STAAUR") 8.1 8.1 12.0 8.4 9.2 28.0 10 +# as.mo("S. aureus") 22.0 23.0 26.0 23.0 24.0 40.0 10 +# as.mo("S. aureus") 22.0 23.0 23.0 23.0 23.0 24.0 10 +# as.mo("Staphylococcus aureus") 3.6 3.8 4.0 3.9 4.0 5.2 10

In the table above, all measurements are shown in milliseconds (thousands of seconds). A value of 5 milliseconds means it can determine 200 input values per second. It case of 100 milliseconds, this is only 10 input values per second. The second input is the only one that has to be looked up thoroughly. All the others are known codes (the first one is a WHONET code) or common laboratory codes, or common full organism names like the last one. Full organism names are always preferred.

To achieve this speed, the as.mo function also takes into account the prevalence of human pathogenic microorganisms. The downside is of course that less prevalent microorganisms will be determined less fast. See this example for the ID of Thermus islandicus (B_THERMS_ISL), a bug probably never found before in humans:

-

That takes 9.8 times as much time on average. A value of 100 milliseconds means it can only determine ~10 different input values per second. We can conclude that looking up arbitrary codes of less prevalent microorganisms is the worst way to go, in terms of calculation performance. Full names (like Thermus islandicus) are almost fast - these are the most probable input from most data sets.

+# as.mo("theisl") 260 270 280 280 290 300 10 +# as.mo("THEISL") 260 280 300 290 300 370 10 +# as.mo("T. islandicus") 130 140 140 140 150 150 10 +# as.mo("T. islandicus") 130 130 130 130 140 150 10 +# as.mo("Thermus islandicus") 47 48 53 50 52 71 10
+

That takes 9.6 times as much time on average. A value of 100 milliseconds means it can only determine ~10 different input values per second. We can conclude that looking up arbitrary codes of less prevalent microorganisms is the worst way to go, in terms of calculation performance. Full names (like Thermus islandicus) are almost fast - these are the most probable input from most data sets.

In the figure below, we compare Escherichia coli (which is very common) with Prevotella brevis (which is moderately common) and with Thermus islandicus (which is very uncommon):

par(mar = c(5, 16, 4, 2)) # set more space for left margin text (16)
 
@@ -255,8 +255,8 @@
 Repetitive results
 

Repetitive results are unique values that are present more than once. Unique values will only be calculated once by as.mo(). We will use mo_name() for this test - a helper function that returns the full microbial name (genus, species and possibly subspecies) which uses as.mo() internally.

-

So transforming 500,000 values (!!) of 50 unique values only takes 0.68 seconds (684 ms). You only lose time on your unique input values.

+# mo_name(x) 611 618 646 642 656 720 10
+

So transforming 500,000 values (!!) of 50 unique values only takes 0.64 seconds (641 ms). You only lose time on your unique input values.

@@ -294,10 +294,10 @@ print(run_it, unit = "ms", signif = 3) # Unit: milliseconds # expr min lq mean median uq max neval -# A 6.760 7.320 7.630 7.54 8.070 8.500 10 -# B 23.800 25.300 28.500 25.50 26.100 50.100 10 -# C 0.906 0.911 0.941 0.93 0.969 0.991 10

-

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

+# A 6.440 6.690 9.070 7.040 7.500 27.800 10 +# B 21.800 22.200 23.600 23.400 23.800 30.200 10 +# C 0.661 0.826 0.844 0.836 0.928 0.936 10 +

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

run_it <- microbenchmark(A = mo_species("aureus"),
                          B = mo_genus("Staphylococcus"),
                          C = mo_name("Staphylococcus aureus"),
@@ -310,14 +310,14 @@
 print(run_it, unit = "ms", signif = 3)
 # Unit: milliseconds
 #  expr   min    lq  mean median    uq   max neval
-#     A 0.464 0.465 0.484  0.482 0.485 0.528    10
-#     B 0.621 0.632 0.659  0.636 0.650 0.784    10
-#     C 0.673 0.749 0.785  0.788 0.826 0.918    10
-#     D 0.446 0.451 0.477  0.467 0.474 0.586    10
-#     E 0.442 0.456 0.481  0.464 0.469 0.648    10
-#     F 0.442 0.459 0.470  0.466 0.490 0.494    10
-#     G 0.446 0.449 0.469  0.471 0.481 0.499    10
-#     H 0.445 0.452 0.466  0.458 0.463 0.522    10
+# A 0.468 0.472 0.483 0.483 0.487 0.520 10 +# B 0.619 0.621 0.649 0.648 0.656 0.698 10 +# C 0.702 0.732 0.770 0.788 0.799 0.809 10 +# D 0.456 0.457 0.487 0.466 0.475 0.684 10 +# E 0.451 0.463 0.466 0.466 0.471 0.479 10 +# F 0.437 0.457 0.464 0.463 0.469 0.497 10 +# G 0.450 0.454 0.468 0.466 0.477 0.495 10 +# H 0.454 0.458 0.471 0.464 0.471 0.510 10

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

@@ -344,13 +344,13 @@ print(run_it, unit = "ms", signif = 4) # Unit: milliseconds # expr min lq mean median uq max neval -# en 18.92 19.31 19.46 19.45 19.65 20.00 10 -# de 20.65 20.85 21.77 21.28 22.33 25.34 10 -# nl 26.17 26.78 32.00 28.27 31.87 49.90 10 -# es 19.94 20.45 23.13 20.95 22.09 40.02 10 -# it 20.43 20.65 23.48 21.71 22.62 40.72 10 -# fr 20.28 20.69 22.35 21.09 21.32 31.54 10 -# pt 19.92 20.28 23.24 21.67 22.46 41.19 10
+# en 17.37 18.13 21.04 18.34 20.65 35.24 10 +# de 18.69 19.32 19.49 19.44 19.77 20.06 10 +# nl 24.85 25.07 27.07 25.37 25.58 42.68 10 +# es 18.96 19.55 23.91 19.88 21.02 41.15 10 +# it 18.85 19.34 21.08 19.52 20.22 35.18 10 +# fr 18.80 19.32 21.40 19.56 20.29 37.00 10 +# pt 18.81 19.45 19.57 19.59 19.64 20.20 10

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

@@ -362,7 +362,7 @@