(v1.2.0.9011) mo_domain(), improved error handling

This commit is contained in:
dr. M.S. (Matthijs) Berends 2020-06-22 11:18:40 +02:00
parent e88d7853f5
commit 93a158aebd
49 changed files with 523 additions and 590 deletions

View File

@ -1,6 +1,6 @@
Package: AMR Package: AMR
Version: 1.2.0.9010 Version: 1.2.0.9011
Date: 2020-06-17 Date: 2020-06-22
Title: Antimicrobial Resistance Analysis Title: Antimicrobial Resistance Analysis
Authors@R: c( Authors@R: c(
person(role = c("aut", "cre"), person(role = c("aut", "cre"),

View File

@ -156,6 +156,7 @@ export(mdr_tb)
export(mdro) export(mdro)
export(mo_authors) export(mo_authors)
export(mo_class) export(mo_class)
export(mo_domain)
export(mo_failures) export(mo_failures)
export(mo_family) export(mo_family)
export(mo_fullname) export(mo_fullname)

16
NEWS.md
View File

@ -1,11 +1,12 @@
# AMR 1.2.0.9010 # AMR 1.2.0.9011
## <small>Last updated: 17-Jun-2020</small> ## <small>Last updated: 22-Jun-2020</small>
### New ### New
* [Tidyverse selections](https://tidyselect.r-lib.org/reference/language.html), that help to select the columns of antibiotics that are of a specific antibiotic class, without the need to define the columns or antibiotic abbreviations. They can be used in any function that allows Tidyverse selections, like `dplyr::select()` and `tidyr::pivot_longer()`: * [Tidyverse selections](https://tidyselect.r-lib.org/reference/language.html) for antibiotic classes, that help to select the columns of antibiotics that are of a specific antibiotic class, without the need to define the columns or antibiotic abbreviations. They can be used in any function that allows Tidyverse selections, like `dplyr::select()` and `tidyr::pivot_longer()`:
```r ```r
library(dplyr) library(dplyr)
# Columns 'IPM' and 'MEM' are in the example_isolates data set
example_isolates %>% example_isolates %>%
select(carbapenems()) select(carbapenems())
#> Selecting carbapenems: `IPM` (imipenem), `MEM` (meropenem) #> Selecting carbapenems: `IPM` (imipenem), `MEM` (meropenem)
@ -19,17 +20,20 @@
select(ab_class("mycobact")) select(ab_class("mycobact"))
#> Selecting antimycobacterials: `RIF` (rifampicin) #> Selecting antimycobacterials: `RIF` (rifampicin)
``` ```
* Added `mo_domain()` as an alias to `mo_kingdom()`
* Added function `filter_penicillins()` to filter isolates on a specific result in any column with a name in the antimicrobial 'penicillins' class (more specific: ATC subgroup *Beta-lactam antibacterials, penicillins*)
* Added official antimicrobial names to all `filter_ab_class()` functions, such as `filter_aminoglycosides()`
* Added antibiotics code "FOX1" for cefoxitin screening (abbreviation "cfsc") to the `antibiotics` data set
### Changed ### Changed
* Fixed a bug where `eucast_rules()` would not work on a tibble when the `tibble` or `dplyr` package was loaded * Fixed a bug where `eucast_rules()` would not work on a tibble when the `tibble` or `dplyr` package was loaded
* All `*_join_microorganisms()` functions and `bug_drug_combinations()` now return the original data class (e.g. `tibble`s and `data.table`s) * All `*_join_microorganisms()` functions and `bug_drug_combinations()` now return the original data class (e.g. `tibble`s and `data.table`s)
* Fixed a bug where `as.ab()` would return an error on invalid input values * Fixed a bug where `as.ab()` would return an error on invalid input values
* Fixed a bug for using grouped versions of `rsi_df()`, `proportion_df()` and `count_df()`, and fixed a bug where not all different antimicrobial results were added as rows * Fixed a bug for using grouped versions of `rsi_df()`, `proportion_df()` and `count_df()`, and fixed a bug where not all different antimicrobial results were added as rows
* Added function `filter_penicillins()` to filter isolates on a specific result in any column with a name in the antimicrobial 'penicillins' class (more specific: ATC subgroup *Beta-lactam antibacterials, penicillins*)
* Added official antimicrobial names to all `filter_ab_class()` functions, such as `filter_aminoglycosides()`
* Added antibiotics code "FOX1" for cefoxitin screening (abbreviation "cfsc") to the `antibiotics` data set
* Improved auto-determination for columns of types `<mo>` and `<Date>` * Improved auto-determination for columns of types `<mo>` and `<Date>`
* Fixed a bug in `bug_drug_combinations()` for when only one antibiotic was in the input data * Fixed a bug in `bug_drug_combinations()` for when only one antibiotic was in the input data
* Changed the summary for class `<mo>`, to highlight the %SI vs. %R
* Improved error handling, giving more useful info when functions return an error
# AMR 1.2.0 # AMR 1.2.0

View File

@ -179,7 +179,7 @@ search_type_in_df <- function(x, type) {
found found
} }
stopifnot_installed_package <- function(package) { stop_ifnot_installed <- function(package) {
# no "utils::installed.packages()" since it requires non-staged install since R 3.6.0 # no "utils::installed.packages()" since it requires non-staged install since R 3.6.0
# https://developer.r-project.org/Blog/public/2019/02/14/staged-install/index.html # https://developer.r-project.org/Blog/public/2019/02/14/staged-install/index.html
sapply(package, function(pkg) sapply(package, function(pkg)
@ -197,16 +197,41 @@ stopifnot_installed_package <- function(package) {
} }
import_fn <- function(name, pkg) { import_fn <- function(name, pkg) {
stopifnot_installed_package(pkg) stop_ifnot_installed(pkg)
get(name, envir = asNamespace(pkg)) get(name, envir = asNamespace(pkg))
} }
stopifnot_msg <- function(expr, msg) { stop_if <- function(expr, ..., call = TRUE) {
if (!isTRUE(expr)) { msg <- paste0(c(...), collapse = "")
if (!isFALSE(call)) {
if (isTRUE(call)) {
call <- as.character(sys.call(-1)[1])
} else {
# so you can go back more than 1 call, as used in rsi_calc(), that now throws a reference to e.g. n_rsi()
call <- as.character(sys.call(call)[1])
}
msg <- paste0("in ", call, "(): ", msg)
}
if (isTRUE(expr)) {
stop(msg, call. = FALSE) stop(msg, call. = FALSE)
} }
} }
stop_ifnot <- function(expr, ..., call = TRUE) {
msg <- paste0(c(...), collapse = "")
if (!isFALSE(call)) {
if (isTRUE(call)) {
call <- as.character(sys.call(-1)[1])
} else {
# so you can go back more than 1 call, as used in rsi_calc(), that now throws a reference to e.g. n_rsi()
call <- as.character(sys.call(call)[1])
}
msg <- paste0("in ", call, "(): ", msg)
}
if (!isTRUE(expr)) {
stop(msg, call. = FALSE)
}
}
"%or%" <- function(x, y) { "%or%" <- function(x, y) {
if (is.null(x) | is.null(y)) { if (is.null(x) | is.null(y)) {
@ -396,7 +421,7 @@ progress_estimated <- function(n = 1, n_min = 0, ...) {
} }
} }
# works exactly like round(), but rounds `round(44.55, 1)` as 44.6 instead of 44.5 # works exactly like round(), but rounds `round2(44.55, 1)` to 44.6 instead of 44.5
# and adds decimal zeroes until `digits` is reached when force_zero = TRUE # and adds decimal zeroes until `digits` is reached when force_zero = TRUE
round2 <- function(x, digits = 0, force_zero = TRUE) { round2 <- function(x, digits = 0, force_zero = TRUE) {
x <- as.double(x) x <- as.double(x)

View File

@ -157,9 +157,7 @@ ab_loinc <- function(x, ...) {
#' @rdname ab_property #' @rdname ab_property
#' @export #' @export
ab_ddd <- function(x, administration = "oral", units = FALSE, ...) { ab_ddd <- function(x, administration = "oral", units = FALSE, ...) {
if (!administration %in% c("oral", "iv")) { stop_ifnot(administration %in% c("oral", "iv"), "`administration` must be 'oral' or 'iv'")
stop("`administration` must be 'oral' or 'iv'", call. = FALSE)
}
ddd_prop <- administration ddd_prop <- administration
if (units == TRUE) { if (units == TRUE) {
ddd_prop <- paste0(ddd_prop, "_units") ddd_prop <- paste0(ddd_prop, "_units")
@ -215,12 +213,9 @@ ab_url <- function(x, open = FALSE, ...) {
#' @rdname ab_property #' @rdname ab_property
#' @export #' @export
ab_property <- function(x, property = "name", language = get_locale(), ...) { ab_property <- function(x, property = "name", language = get_locale(), ...) {
if (length(property) != 1L) { stop_if(length(property) != 1L, "'property' must be of length 1.")
stop("'property' must be of length 1.") stop_ifnot(property %in% colnames(antibiotics),
} "invalid property: '", property, "' - use a column name of the `antibiotics` data set")
if (!property %in% colnames(antibiotics)) {
stop("invalid property: '", property, "' - use a column name of the `antibiotics` data set")
}
translate_AMR(ab_validate(x = x, property = property, ...), language = language) translate_AMR(ab_validate(x = x, property = property, ...), language = language)
} }

16
R/age.R
View File

@ -42,11 +42,8 @@
#' df #' df
age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE) { age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE) {
if (length(x) != length(reference)) { if (length(x) != length(reference)) {
if (length(reference) == 1) { stop_if(length(reference) != 1, "`x` and `reference` must be of same length, or `reference` must be of length 1.")
reference <- rep(reference, length(x)) reference <- rep(reference, length(x))
} else {
stop("`x` and `reference` must be of same length, or `reference` must be of length 1.")
}
} }
x <- as.POSIXlt(x) x <- as.POSIXlt(x)
reference <- as.POSIXlt(reference) reference <- as.POSIXlt(reference)
@ -141,9 +138,7 @@ age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE) {
#' ggplot_rsi(x = "age_group") #' ggplot_rsi(x = "age_group")
#' } #' }
age_groups <- function(x, split_at = c(12, 25, 55, 75), na.rm = FALSE) { age_groups <- function(x, split_at = c(12, 25, 55, 75), na.rm = FALSE) {
if (!is.numeric(x)) { stop_ifnot(is.numeric(x), "`x` must be numeric, not ", paste0(class(x), collapse = "/"))
stop("`x` and must be numeric, not a ", paste0(class(x), collapse = "/"), ".")
}
if (any(x < 0, na.rm = TRUE)) { if (any(x < 0, na.rm = TRUE)) {
x[x < 0] <- NA x[x < 0] <- NA
warning("NAs introduced for ages below 0.") warning("NAs introduced for ages below 0.")
@ -166,10 +161,7 @@ age_groups <- function(x, split_at = c(12, 25, 55, 75), na.rm = FALSE) {
split_at <- c(0, split_at) split_at <- c(0, split_at)
} }
split_at <- split_at[!is.na(split_at)] split_at <- split_at[!is.na(split_at)]
if (length(split_at) == 1) { stop_if(length(split_at) == 1, "invalid value for `split_at`") # only 0 is available
# only 0 is available
stop("invalid value for `split_at`.")
}
# turn input values to 'split_at' indices # turn input values to 'split_at' indices
y <- x y <- x

View File

@ -96,12 +96,8 @@ atc_online_property <- function(atc_code,
return(rep(NA, length(atc_code))) return(rep(NA, length(atc_code)))
} }
if (length(property) != 1L) { stop_if(length(property) != 1L, "`property` must be of length 1")
stop("`property` must be of length 1", call. = FALSE) stop_if(length(administration) != 1L, "`administration` must be of length 1")
}
if (length(administration) != 1L) {
stop("`administration` must be of length 1", call. = FALSE)
}
# also allow unit as property # also allow unit as property
if (property %like% "unit") { if (property %like% "unit") {
@ -115,9 +111,8 @@ atc_online_property <- function(atc_code,
property <- tolower(property) property <- tolower(property)
valid_properties <- tolower(valid_properties) valid_properties <- tolower(valid_properties)
if (!property %in% valid_properties) { stop_ifnot(property %in% valid_properties,
stop("Invalid `property`, use one of ", paste(valid_properties.bak, collapse = ", "), ".") "Invalid `property`, use one of ", paste(valid_properties.bak, collapse = ", "))
}
if (property == "ddd") { if (property == "ddd") {
returnvalue <- rep(NA_real_, length(atc_code)) returnvalue <- rep(NA_real_, length(atc_code))

View File

@ -46,6 +46,7 @@
#' availability() #' availability()
#' } #' }
availability <- function(tbl, width = NULL) { availability <- function(tbl, width = NULL) {
stop_ifnot(is.data.frame(tbl), "`tbl` must be a data.frame")
x <- base::sapply(tbl, function(x) { x <- base::sapply(tbl, function(x) {
1 - base::sum(base::is.na(x)) / base::length(x) 1 - base::sum(base::is.na(x)) / base::length(x)
}) })

View File

@ -59,21 +59,15 @@ bug_drug_combinations <- function(x,
col_mo = NULL, col_mo = NULL,
FUN = mo_shortname, FUN = mo_shortname,
...) { ...) {
if (!is.data.frame(x)) { stop_ifnot(is.data.frame(x), "`x` must be a data frame")
stop("`x` must be a data frame.", call. = FALSE) stop_ifnot(any(sapply(x, is.rsi), na.rm = TRUE), "No columns with class <rsi> found. See ?as.rsi.")
}
if (!any(sapply(x, is.rsi), na.rm = TRUE)) {
stop("No columns with class <rsi> found. See ?as.rsi.", call. = FALSE)
}
# try to find columns based on type # try to find columns based on type
# -- mo # -- mo
if (is.null(col_mo)) { if (is.null(col_mo)) {
col_mo <- search_type_in_df(x = x, type = "mo") col_mo <- search_type_in_df(x = x, type = "mo")
} }
if (is.null(col_mo)) { stop_if(is.null(col_mo), "`col_mo` must be set")
stop("`col_mo` must be set.", call. = FALSE)
}
x_class <- class(x) x_class <- class(x)
x <- as.data.frame(x, stringsAsFactors = FALSE) x <- as.data.frame(x, stringsAsFactors = FALSE)

View File

@ -217,26 +217,17 @@ eucast_rules <- function(x,
} }
} }
if (!is.data.frame(x)) { stop_ifnot(is.data.frame(x), "`x` must be a data frame")
stop("`x` must be a data frame.", call. = FALSE)
}
# try to find columns based on type # try to find columns based on type
# -- mo # -- mo
if (is.null(col_mo)) { if (is.null(col_mo)) {
col_mo <- search_type_in_df(x = x, type = "mo") col_mo <- search_type_in_df(x = x, type = "mo")
} }
if (is.null(col_mo)) { stop_if(is.null(col_mo), "`col_mo` must be set")
stop("`col_mo` must be set.", call. = FALSE)
}
if (!all(rules %in% c("breakpoints", "expert", "other", "all"))) { stop_ifnot(all(rules %in% c("breakpoints", "expert", "other", "all")),
stop('`rules` must be one or more of: "breakpoints", "expert", "other", "all".') '`rules` must be one or more of: "breakpoints", "expert", "other", "all".')
}
if (is.null(col_mo)) {
stop("`col_mo` must be set")
}
decimal.mark <- getOption("OutDec") decimal.mark <- getOption("OutDec")
big.mark <- ifelse(decimal.mark != ",", ",", ".") big.mark <- ifelse(decimal.mark != ",", ",", ".")

View File

@ -71,10 +71,7 @@ filter_ab_class <- function(x,
...) { ...) {
check_dataset_integrity() check_dataset_integrity()
stop_ifnot(is.data.frame(x), "`x` must be a data frame")
if (!is.data.frame(x)) {
stop("`x` must be a data frame.", call. = FALSE)
}
# save to return later # save to return later
x_class <- class(x) x_class <- class(x)
@ -88,12 +85,8 @@ filter_ab_class <- function(x,
# make result = "SI" works too: # make result = "SI" works too:
result <- unlist(strsplit(result, "")) result <- unlist(strsplit(result, ""))
if (!all(result %in% c("S", "I", "R"))) { stop_ifnot(all(result %in% c("S", "I", "R")), "`result` must be one or more of: S, I, R")
stop("`result` must be one or more of: S, I, R", call. = FALSE) stop_ifnot(all(scope %in% c("any", "all")), "`scope` must be one of: any, all")
}
if (!all(scope %in% c("any", "all"))) {
stop("`scope` must be one of: any, all", call. = FALSE)
}
# get all columns in data with names that resemble antibiotics # get all columns in data with names that resemble antibiotics
ab_in_data <- suppressMessages(get_column_abx(x)) ab_in_data <- suppressMessages(get_column_abx(x))

View File

@ -156,9 +156,9 @@ first_isolate <- function(x,
} }
} }
if (!is.data.frame(x)) { stop_ifnot(is.data.frame(x), "`x` must be a data.frame")
stop("`x` must be a data.frame.", call. = FALSE) stop_if(any(dim(x) == 0), "`x` must contain rows and columns")
}
# remove data.table, grouping from tibbles, etc. # remove data.table, grouping from tibbles, etc.
x <- as.data.frame(x, stringsAsFactors = FALSE) x <- as.data.frame(x, stringsAsFactors = FALSE)
@ -166,17 +166,13 @@ first_isolate <- function(x,
# -- mo # -- mo
if (is.null(col_mo)) { if (is.null(col_mo)) {
col_mo <- search_type_in_df(x = x, type = "mo") col_mo <- search_type_in_df(x = x, type = "mo")
if (is.null(col_mo)) { stop_if(is.null(col_mo), "`col_mo` must be set")
stop("`col_mo` must be set.", call. = FALSE)
}
} }
# -- date # -- date
if (is.null(col_date)) { if (is.null(col_date)) {
col_date <- search_type_in_df(x = x, type = "date") col_date <- search_type_in_df(x = x, type = "date")
if (is.null(col_date)) { stop_if(is.null(col_date), "`col_date` must be set")
stop("`col_date` must be set.", call. = FALSE)
}
} }
# convert to Date # convert to Date
dates <- as.Date(x[, col_date, drop = TRUE]) dates <- as.Date(x[, col_date, drop = TRUE])
@ -193,9 +189,7 @@ first_isolate <- function(x,
} else { } else {
col_patient_id <- search_type_in_df(x = x, type = "patient_id") col_patient_id <- search_type_in_df(x = x, type = "patient_id")
} }
if (is.null(col_patient_id)) { stop_if(is.null(col_patient_id), "`col_patient_id` must be set")
stop("`col_patient_id` must be set.", call. = FALSE)
}
} }
# -- key antibiotics # -- key antibiotics
@ -216,14 +210,9 @@ first_isolate <- function(x,
# check if columns exist # check if columns exist
check_columns_existance <- function(column, tblname = x) { check_columns_existance <- function(column, tblname = x) {
if (NROW(tblname) <= 1 | NCOL(tblname) <= 1) {
stop("Please check tbl for existance.")
}
if (!is.null(column)) { if (!is.null(column)) {
if (!(column %in% colnames(tblname))) { stop_ifnot(column %in% colnames(tblname),
stop("Column `", column, "` not found.") "Column `", column, "` not found.", call = FALSE)
}
} }
} }

View File

@ -95,22 +95,22 @@ ggplot_pca <- function(x,
base_textsize = 10, base_textsize = 10,
...) { ...) {
stopifnot_installed_package("ggplot2") stop_ifnot_installed("ggplot2")
stopifnot_msg(length(choices) == 2, "`choices` must be of length 2") stop_ifnot(length(choices) == 2, "`choices` must be of length 2")
stopifnot_msg(is.logical(scale), "`scale` must be TRUE or FALSE") stop_ifnot(is.logical(scale), "`scale` must be TRUE or FALSE")
stopifnot_msg(is.logical(pc.biplot), "`pc.biplot` must be TRUE or FALSE") stop_ifnot(is.logical(pc.biplot), "`pc.biplot` must be TRUE or FALSE")
stopifnot_msg(is.numeric(choices), "`choices` must be numeric") stop_ifnot(is.numeric(choices), "`choices` must be numeric")
stopifnot_msg(is.numeric(labels_textsize), "`labels_textsize` must be numeric") stop_ifnot(is.numeric(labels_textsize), "`labels_textsize` must be numeric")
stopifnot_msg(is.numeric(labels_text_placement), "`labels_text_placement` must be numeric") stop_ifnot(is.numeric(labels_text_placement), "`labels_text_placement` must be numeric")
stopifnot_msg(is.logical(ellipse), "`ellipse` must be TRUE or FALSE") stop_ifnot(is.logical(ellipse), "`ellipse` must be TRUE or FALSE")
stopifnot_msg(is.numeric(ellipse_prob), "`ellipse_prob` must be numeric") stop_ifnot(is.numeric(ellipse_prob), "`ellipse_prob` must be numeric")
stopifnot_msg(is.numeric(ellipse_size), "`ellipse_size` must be numeric") stop_ifnot(is.numeric(ellipse_size), "`ellipse_size` must be numeric")
stopifnot_msg(is.numeric(ellipse_alpha), "`ellipse_alpha` must be numeric") stop_ifnot(is.numeric(ellipse_alpha), "`ellipse_alpha` must be numeric")
stopifnot_msg(is.logical(arrows), "`arrows` must be TRUE or FALSE") stop_ifnot(is.logical(arrows), "`arrows` must be TRUE or FALSE")
stopifnot_msg(is.numeric(arrows_size), "`arrows_size` must be numeric") stop_ifnot(is.numeric(arrows_size), "`arrows_size` must be numeric")
stopifnot_msg(is.numeric(arrows_textsize), "`arrows_textsize` must be numeric") stop_ifnot(is.numeric(arrows_textsize), "`arrows_textsize` must be numeric")
stopifnot_msg(is.numeric(arrows_alpha), "`arrows_alpha` must be numeric") stop_ifnot(is.numeric(arrows_alpha), "`arrows_alpha` must be numeric")
stopifnot_msg(is.numeric(base_textsize), "`base_textsize` must be numeric") stop_ifnot(is.numeric(base_textsize), "`base_textsize` must be numeric")
calculations <- pca_calculations(pca_model = x, calculations <- pca_calculations(pca_model = x,
groups = groups, groups = groups,

View File

@ -164,7 +164,7 @@ ggplot_rsi <- function(data,
y.title = "Proportion", y.title = "Proportion",
...) { ...) {
stopifnot_installed_package("ggplot2") stop_ifnot_installed("ggplot2")
x <- x[1] x <- x[1]
facet <- facet[1] facet <- facet[1]
@ -245,11 +245,8 @@ geom_rsi <- function(position = NULL,
combine_IR = FALSE, combine_IR = FALSE,
...) { ...) {
stopifnot_installed_package("ggplot2") stop_ifnot_installed("ggplot2")
stop_if(is.data.frame(position), "`position` is invalid. Did you accidentally use '%>%' instead of '+'?")
if (is.data.frame(position)) {
stop("`position` is invalid. Did you accidentally use '%>%' instead of '+'?", call. = FALSE)
}
y <- "value" y <- "value"
if (missing(position) | is.null(position)) { if (missing(position) | is.null(position)) {
@ -293,7 +290,7 @@ geom_rsi <- function(position = NULL,
#' @export #' @export
facet_rsi <- function(facet = c("interpretation", "antibiotic"), nrow = NULL) { facet_rsi <- function(facet = c("interpretation", "antibiotic"), nrow = NULL) {
stopifnot_installed_package("ggplot2") stop_ifnot_installed("ggplot2")
facet <- facet[1] facet <- facet[1]
@ -318,7 +315,7 @@ facet_rsi <- function(facet = c("interpretation", "antibiotic"), nrow = NULL) {
#' @rdname ggplot_rsi #' @rdname ggplot_rsi
#' @export #' @export
scale_y_percent <- function(breaks = seq(0, 1, 0.1), limits = NULL) { scale_y_percent <- function(breaks = seq(0, 1, 0.1), limits = NULL) {
stopifnot_installed_package("ggplot2") stop_ifnot_installed("ggplot2")
if (all(breaks[breaks != 0] > 1)) { if (all(breaks[breaks != 0] > 1)) {
breaks <- breaks / 100 breaks <- breaks / 100
@ -335,7 +332,7 @@ scale_rsi_colours <- function(colours = c(S = "#61a8ff",
I = "#61f7ff", I = "#61f7ff",
IR = "#ff6961", IR = "#ff6961",
R = "#ff6961")) { R = "#ff6961")) {
stopifnot_installed_package("ggplot2") stop_ifnot_installed("ggplot2")
# previous colour: palette = "RdYlGn" # previous colour: palette = "RdYlGn"
# previous colours: values = c("#b22222", "#ae9c20", "#7cfc00") # previous colours: values = c("#b22222", "#ae9c20", "#7cfc00")
@ -353,7 +350,7 @@ scale_rsi_colours <- function(colours = c(S = "#61a8ff",
#' @rdname ggplot_rsi #' @rdname ggplot_rsi
#' @export #' @export
theme_rsi <- function() { theme_rsi <- function() {
stopifnot_installed_package("ggplot2") stop_ifnot_installed("ggplot2")
ggplot2::theme_minimal(base_size = 10) + ggplot2::theme_minimal(base_size = 10) +
ggplot2::theme(panel.grid.major.x = ggplot2::element_blank(), ggplot2::theme(panel.grid.major.x = ggplot2::element_blank(),
panel.grid.minor = ggplot2::element_blank(), panel.grid.minor = ggplot2::element_blank(),
@ -372,7 +369,7 @@ labels_rsi_count <- function(position = NULL,
combine_IR = FALSE, combine_IR = FALSE,
datalabels.size = 3, datalabels.size = 3,
datalabels.colour = "gray15") { datalabels.colour = "gray15") {
stopifnot_installed_package("ggplot2") stop_ifnot_installed("ggplot2")
if (is.null(position)) { if (is.null(position)) {
position <- "fill" position <- "fill"
} }

View File

@ -62,9 +62,7 @@ guess_ab_col <- function(x = NULL, search_string = NULL, verbose = FALSE) {
if (is.null(x) & is.null(search_string)) { if (is.null(x) & is.null(search_string)) {
return(as.name("guess_ab_col")) return(as.name("guess_ab_col"))
} }
if (!is.data.frame(x)) { stop_ifnot(is.data.frame(x), "`x` must be a data.frame")
stop("`x` must be a data.frame")
}
if (length(search_string) > 1) { if (length(search_string) > 1) {
warning("argument 'search_string' has length > 1 and only the first element will be used") warning("argument 'search_string' has length > 1 and only the first element will be used")

View File

@ -175,7 +175,7 @@ joins_check_df <- function(x, by) {
by <- "mo" by <- "mo"
x[, "mo"] <- as.mo(x[, "mo"]) x[, "mo"] <- as.mo(x[, "mo"])
} else { } else {
stop("Cannot join - no column found with name or class <mo>.", call. = FALSE) stop("Cannot join - no column found with name 'mo' or with class <mo>.", call. = FALSE)
} }
} }
message('Joining, by = "', by, '"') # message same as dplyr::join functions message('Joining, by = "', by, '"') # message same as dplyr::join functions

View File

@ -136,9 +136,7 @@ key_antibiotics <- function(x,
if (is.null(col_mo)) { if (is.null(col_mo)) {
col_mo <- search_type_in_df(x = x, type = "mo") col_mo <- search_type_in_df(x = x, type = "mo")
} }
if (is.null(col_mo)) { stop_if(is.null(col_mo), "`col_mo` must be set")
stop("`col_mo` must be set.", call. = FALSE)
}
# check columns # check columns
col.list <- c(universal_1, universal_2, universal_3, universal_4, universal_5, universal_6, col.list <- c(universal_1, universal_2, universal_3, universal_4, universal_5, universal_6,
@ -260,9 +258,7 @@ key_antibiotics_equal <- function(y,
type <- type[1] type <- type[1]
if (length(x) != length(y)) { stop_ifnot(length(x) == length(y), "length of `x` and `y` must be equal")
stop("Length of `x` and `y` must be equal.")
}
# only show progress bar on points or when at least 5000 isolates # only show progress bar on points or when at least 5000 isolates
info_needed <- info == TRUE & (type == "points" | length(x) > 5000) info_needed <- info == TRUE & (type == "points" | length(x) > 5000)

View File

@ -106,15 +106,13 @@ mdro <- function(x,
} }
} }
if (!is.data.frame(x)) { stop_ifnot(is.data.frame(x), "`x` must be a data.frame")
stop("`x` must be a data frame.", call. = FALSE) stop_if(any(dim(x) == 0), "`x` must contain rows and columns")
}
# force regular data.frame, not a tibble or data.table # force regular data.frame, not a tibble or data.table
x <- as.data.frame(x, stringsAsFactors = FALSE) x <- as.data.frame(x, stringsAsFactors = FALSE)
if (!is.numeric(pct_required_classes)) { stop_ifnot(is.numeric(pct_required_classes), "`pct_required_classes` must be numeric")
stop("`pct_required_classes` must be numeric.", call. = FALSE)
}
if (pct_required_classes > 1) { if (pct_required_classes > 1) {
# allow pct_required_classes = 75 -> pct_required_classes = 0.75 # allow pct_required_classes = 75 -> pct_required_classes = 0.75
pct_required_classes <- pct_required_classes / 100 pct_required_classes <- pct_required_classes / 100
@ -124,9 +122,7 @@ mdro <- function(x,
warning("Using `country` is deprecated, use `guideline` instead. Please see ?mdro.", call. = FALSE) warning("Using `country` is deprecated, use `guideline` instead. Please see ?mdro.", call. = FALSE)
guideline <- list(...)$country guideline <- list(...)$country
} }
if (length(guideline) > 1) { stop_ifnot(length(guideline) == 1, "`guideline` must be of length 1")
stop("`guideline` must be a length one character string.", call. = FALSE)
}
if (is.null(guideline)) { if (is.null(guideline)) {
# default to the paper by Magiorakos et al. (2012) # default to the paper by Magiorakos et al. (2012)
@ -138,9 +134,8 @@ mdro <- function(x,
if (tolower(guideline) == "de") { if (tolower(guideline) == "de") {
guideline <- "MRGN" guideline <- "MRGN"
} }
if (!tolower(guideline) %in% c("brmo", "mrgn", "eucast", "tb", "cmi2012")) { stop_ifnot(tolower(guideline) %in% c("brmo", "mrgn", "eucast", "tb", "cmi2012"),
stop("invalid guideline: ", guideline, call. = FALSE) "invalid guideline: ", guideline)
}
guideline <- list(code = tolower(guideline)) guideline <- list(code = tolower(guideline))
# try to find columns based on type # try to find columns based on type
@ -154,9 +149,7 @@ mdro <- function(x,
x$mo <- as.mo("Mycobacterium tuberculosis") x$mo <- as.mo("Mycobacterium tuberculosis")
col_mo <- "mo" col_mo <- "mo"
} }
if (is.null(col_mo)) { stop_if(is.null(col_mo), "`col_mo` must be set")
stop("`col_mo` must be set.", call. = FALSE)
}
if (guideline$code == "cmi2012") { if (guideline$code == "cmi2012") {
guideline$name <- "Multidrug-resistant, extensively drug-resistant and pandrug-resistant bacteria: an international expert proposal for interim standard definitions for acquired resistance." guideline$name <- "Multidrug-resistant, extensively drug-resistant and pandrug-resistant bacteria: an international expert proposal for interim standard definitions for acquired resistance."
@ -417,9 +410,7 @@ mdro <- function(x,
RFP <- cols_ab["RFP"] RFP <- cols_ab["RFP"]
abx_tb <- c(CAP, ETH, GAT, INH, PZA, RIF, RIB, RFP) abx_tb <- c(CAP, ETH, GAT, INH, PZA, RIF, RIB, RFP)
abx_tb <- abx_tb[!is.na(abx_tb)] abx_tb <- abx_tb[!is.na(abx_tb)]
if (guideline$code == "tb" & length(abx_tb) == 0) { stop_if(guideline$code == "tb" & length(abx_tb) == 0, "no antimycobacterials found in data set")
stop("No antimycobacterials found in data set.", call. = FALSE)
}
if (combine_SI == TRUE) { if (combine_SI == TRUE) {
search_result <- "R" search_result <- "R"

12
R/mo.R
View File

@ -350,9 +350,8 @@ exec_as.mo <- function(x,
# defined df to check for # defined df to check for
if (!is.null(reference_df)) { if (!is.null(reference_df)) {
if (!mo_source_isvalid(reference_df)) { mo_source_isvalid(reference_df)
stop("`reference_df` must contain a column `mo` with values from the 'microorganisms' data set.", call. = FALSE)
}
reference_df <- reference_df %>% filter(!is.na(mo)) reference_df <- reference_df %>% filter(!is.na(mo))
# keep only first two columns, second must be mo # keep only first two columns, second must be mo
if (colnames(reference_df)[1] == "mo") { if (colnames(reference_df)[1] == "mo") {
@ -1760,9 +1759,8 @@ translate_allow_uncertain <- function(allow_uncertain) {
allow_uncertain[tolower(allow_uncertain) == "none"] <- 0 allow_uncertain[tolower(allow_uncertain) == "none"] <- 0
allow_uncertain[tolower(allow_uncertain) == "all"] <- 3 allow_uncertain[tolower(allow_uncertain) == "all"] <- 3
allow_uncertain <- as.integer(allow_uncertain) allow_uncertain <- as.integer(allow_uncertain)
if (!allow_uncertain %in% c(0:3)) { stop_ifnot(allow_uncertain %in% c(0:3),
stop('`allow_uncertain` must be a number between 0 (or "none") and 3 (or "all"), or TRUE (= 2) or FALSE (= 0).', call. = FALSE) '`allow_uncertain` must be a number between 0 (or "none") and 3 (or "all"), or TRUE (= 2) or FALSE (= 0)', call = FALSE)
}
} }
allow_uncertain allow_uncertain
} }
@ -1803,7 +1801,7 @@ parse_and_convert <- function(x) {
tryCatch({ tryCatch({
if (!is.null(dim(x))) { if (!is.null(dim(x))) {
if (NCOL(x) > 2) { if (NCOL(x) > 2) {
stop("A maximum of two columns is allowed.", call. = FALSE) stop("a maximum of two columns is allowed", call. = FALSE)
} else if (NCOL(x) == 2) { } else if (NCOL(x) == 2) {
# support Tidyverse selection like: df %>% select(colA, colB) # support Tidyverse selection like: df %>% select(colA, colB)
# paste these columns together # paste these columns together

View File

@ -28,14 +28,16 @@
#' @param language language of the returned text, defaults to system language (see [get_locale()]) and can also be set with `getOption("AMR_locale")`. Use `language = NULL` or `language = ""` to prevent translation. #' @param language language of the returned text, defaults to system language (see [get_locale()]) and can also be set with `getOption("AMR_locale")`. Use `language = NULL` or `language = ""` to prevent translation.
#' @param ... other parameters passed on to [as.mo()] #' @param ... other parameters passed on to [as.mo()]
#' @param open browse the URL using [utils::browseURL()] #' @param open browse the URL using [utils::browseURL()]
#' @details All functions will return the most recently known taxonomic property according to the Catalogue of Life, except for [mo_ref()], [mo_authors()] and [mo_year()]. This leads to the following results: #' @details All functions will return the most recently known taxonomic property according to the Catalogue of Life, except for [mo_ref()], [mo_authors()] and [mo_year()]. Please refer to this example, knowing that *Escherichia blattae* was renamed to *Shimwellia blattae* in 2010:
#' - `mo_name("Chlamydia psittaci")` will return `"Chlamydophila psittaci"` (with a warning about the renaming) #' - `mo_name("Escherichia blattae")` will return `"Shimwellia blattae"` (with a message about the renaming)
#' - `mo_ref("Chlamydia psittaci")` will return `"Page, 1968"` (with a warning about the renaming) #' - `mo_ref("Escherichia blattae")` will return `"Burgess et al., 1973"` (with a message about the renaming)
#' - `mo_ref("Chlamydophila psittaci")` will return `"Everett et al., 1999"` (without a warning) #' - `mo_ref("Shimwellia blattae")` will return `"Priest et al., 2010"` (without a message)
#' #'
#' The short name - [mo_shortname()] - almost always returns the first character of the genus and the full species, like *"E. coli"*. Exceptions are abbreviations of staphylococci and beta-haemolytic streptococci, like *"CoNS"* (Coagulase-Negative Staphylococci) and *"GBS"* (Group B Streptococci). #' The short name - [mo_shortname()] - almost always returns the first character of the genus and the full species, like `"E. coli"`. Exceptions are abbreviations of staphylococci (like *"CoNS"*, Coagulase-Negative Staphylococci) and beta-haemolytic streptococci (like *"GBS"*, Group B Streptococci). Please bear in mind that e.g. *E. coli* could mean *Escherichia coli* (kingdom of Bacteria) as well as *Entamoeba coli* (kingdom of Protozoa). Returning to the full name will be done using [as.mo()] internally, giving priority to bacteria and human pathogens, i.e. `"E. coli"` will be considered *Escherichia coli*. In other words, `mo_fullname(mo_shortname("Entamoeba coli"))` returns `"Escherichia coli"`.
#'
#' Since the top-level of the taxonomy is sometimes referred to as 'kingdom' and sometimes as 'domain', the functions [mo_kingdom()] and [mo_domain()] return the exact same results.
#' #'
#' The Gram stain - [mo_gramstain()] - will be determined on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002) who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value `NA`. #' The Gram stain - [mo_gramstain()] - will be determined based on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002, [PMID 11837318](https://pubmed.ncbi.nlm.nih.gov/11837318)), who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value `NA`.
#' #'
#' All output will be [translate]d where possible. #' All output will be [translate]d where possible.
#' #'
@ -218,6 +220,10 @@ mo_kingdom <- function(x, language = get_locale(), ...) {
translate_AMR(mo_validate(x = x, property = "kingdom", ...), language = language, only_unknown = TRUE) translate_AMR(mo_validate(x = x, property = "kingdom", ...), language = language, only_unknown = TRUE)
} }
#' @rdname mo_property
#' @export
mo_domain <- mo_kingdom
#' @rdname mo_property #' @rdname mo_property
#' @export #' @export
mo_type <- function(x, language = get_locale(), ...) { mo_type <- function(x, language = get_locale(), ...) {
@ -391,12 +397,9 @@ mo_url <- function(x, open = FALSE, ...) {
#' @rdname mo_property #' @rdname mo_property
#' @export #' @export
mo_property <- function(x, property = "fullname", language = get_locale(), ...) { mo_property <- function(x, property = "fullname", language = get_locale(), ...) {
if (length(property) != 1L) { stop_ifnot(length(property) == 1L, "'property' must be of length 1")
stop("'property' must be of length 1.") stop_ifnot(property %in% colnames(microorganisms),
} "invalid property: '", property, "' - use a column name of the `microorganisms` data set")
if (!property %in% colnames(microorganisms)) {
stop("invalid property: '", property, "' - use a column name of the `microorganisms` data set")
}
translate_AMR(mo_validate(x = x, property = property, ...), language = language, only_unknown = TRUE) translate_AMR(mo_validate(x = x, property = property, ...), language = language, only_unknown = TRUE)
} }

View File

@ -112,9 +112,7 @@ set_mo_source <- function(path) {
file_location <- path.expand("~/mo_source.rds") file_location <- path.expand("~/mo_source.rds")
if (length(path) > 1) { stop_ifnot(length(path) == 1, "`path` must be of length 1")
stop("`path` must be of length 1.")
}
if (is.null(path) || path %in% c(FALSE, "")) { if (is.null(path) || path %in% c(FALSE, "")) {
options(mo_source = NULL) options(mo_source = NULL)
@ -126,9 +124,8 @@ set_mo_source <- function(path) {
return(invisible()) return(invisible())
} }
if (!file.exists(path)) { stop_ifnot(file.exists(path),
stop("File not found: ", path) "file not found: ", path)
}
if (path %like% "[.]rds$") { if (path %like% "[.]rds$") {
df <- readRDS(path) df <- readRDS(path)
@ -231,21 +228,21 @@ mo_source_isvalid <- function(x, refer_to_name = "`reference_df`", stop_on_error
} }
if (is.null(x)) { if (is.null(x)) {
if (stop_on_error == TRUE) { if (stop_on_error == TRUE) {
stop(refer_to_name, " cannot be NULL.", call. = FALSE) stop(refer_to_name, " cannot be NULL", call. = FALSE)
} else { } else {
return(FALSE) return(FALSE)
} }
} }
if (!is.data.frame(x)) { if (!is.data.frame(x)) {
if (stop_on_error == TRUE) { if (stop_on_error == TRUE) {
stop(refer_to_name, " must be a data.frame.", call. = FALSE) stop(refer_to_name, " must be a data.frame", call. = FALSE)
} else { } else {
return(FALSE) return(FALSE)
} }
} }
if (!"mo" %in% colnames(x)) { if (!"mo" %in% colnames(x)) {
if (stop_on_error == TRUE) { if (stop_on_error == TRUE) {
stop(refer_to_name, " must contain a column 'mo'.", call. = FALSE) stop(refer_to_name, " must contain a column 'mo'", call. = FALSE)
} else { } else {
return(FALSE) return(FALSE)
} }
@ -260,7 +257,7 @@ mo_source_isvalid <- function(x, refer_to_name = "`reference_df`", stop_on_error
} }
stop("Value", plural, " ", paste0("'", invalid[, 1, drop = TRUE], "'", collapse = ", "), stop("Value", plural, " ", paste0("'", invalid[, 1, drop = TRUE], "'", collapse = ", "),
" found in ", tolower(refer_to_name), " found in ", tolower(refer_to_name),
", but with invalid microorganism code", plural, " ", paste0("'", invalid$mo, "'", collapse = ", "), ".", ", but with invalid microorganism code", plural, " ", paste0("'", invalid$mo, "'", collapse = ", "),
call. = FALSE) call. = FALSE)
} else { } else {
return(FALSE) return(FALSE)

View File

@ -61,9 +61,8 @@ pca <- function(x,
tol = NULL, tol = NULL,
rank. = NULL) { rank. = NULL) {
if (!is.data.frame(x)) { stop_ifnot(is.data.frame(x), "`x` must be a data.frame")
stop("this function only takes a data.frame as input") stop_if(any(dim(x) == 0), "`x` must contain rows and columns")
}
# unset data.table, tibble, etc. # unset data.table, tibble, etc.
# also removes groups made by dplyr::group_by # also removes groups made by dplyr::group_by

View File

@ -123,18 +123,12 @@ resistance_predict <- function(x,
info = interactive(), info = interactive(),
...) { ...) {
if (nrow(x) == 0) { stop_ifnot(is.data.frame(x), "`x` must be a data.frame")
stop("This table does not contain any observations.") stop_if(any(dim(x) == 0), "`x` must contain rows and columns")
} stop_if(is.null(model), 'choose a regression model with the `model` parameter, e.g. resistance_predict(..., model = "binomial")')
stop_ifnot(col_ab %in% colnames(x),
"column `", col_ab, "` not found")
if (is.null(model)) {
stop('Choose a regression model with the `model` parameter, e.g. resistance_predict(..., model = "binomial").')
}
if (!col_ab %in% colnames(x)) {
stop("Column ", col_ab, " not found.")
}
dots <- unlist(list(...)) dots <- unlist(list(...))
if (length(dots) != 0) { if (length(dots) != 0) {
# backwards compatibility with old parameters # backwards compatibility with old parameters
@ -150,16 +144,12 @@ resistance_predict <- function(x,
# -- date # -- date
if (is.null(col_date)) { if (is.null(col_date)) {
col_date <- search_type_in_df(x = x, type = "date") col_date <- search_type_in_df(x = x, type = "date")
stop_if(is.null(col_date), "`col_date` must be set")
} }
if (is.null(col_date)) { stop_ifnot(col_date %in% colnames(x),
stop("`col_date` must be set.", call. = FALSE) "column `", col_date, "` not found")
}
if (!col_date %in% colnames(x)) { # no grouped tibbles
stop("Column ", col_date, " not found.")
}
# no grouped tibbles, mutate will throw errors
x <- as.data.frame(x, stringsAsFactors = FALSE) x <- as.data.frame(x, stringsAsFactors = FALSE)
year <- function(x) { year <- function(x) {
@ -192,10 +182,8 @@ resistance_predict <- function(x,
df <- subset(df, sum(df$R + df$S, na.rm = TRUE) >= minimum) df <- subset(df, sum(df$R + df$S, na.rm = TRUE) >= minimum)
df_matrix <- as.matrix(df[, c("R", "S"), drop = FALSE]) df_matrix <- as.matrix(df[, c("R", "S"), drop = FALSE])
if (NROW(df) == 0) { stop_if(NROW(df) == 0, "there are no observations")
stop("There are no observations.")
}
year_lowest <- min(df$year) year_lowest <- min(df$year)
if (is.null(year_min)) { if (is.null(year_min)) {
year_min <- year_lowest year_min <- year_lowest
@ -248,7 +236,7 @@ resistance_predict <- function(x,
se <- predictmodel$se.fit se <- predictmodel$se.fit
} else { } else {
stop("No valid model selected. See ?resistance_predict.") stop("no valid model selected. See ?resistance_predict.")
} }
# prepare the output dataframe # prepare the output dataframe
@ -355,12 +343,9 @@ ggplot_rsi_predict <- function(x,
main = paste("Resistance Prediction of", x_name), main = paste("Resistance Prediction of", x_name),
ribbon = TRUE, ribbon = TRUE,
...) { ...) {
stopifnot_installed_package("ggplot2") stop_ifnot_installed("ggplot2")
stop_ifnot(inherits(x, "resistance_predict"), "`x` must be a resistance prediction model created with resistance_predict()")
if (!"resistance_predict" %in% class(x)) {
stop("`x` must be a resistance prediction model created with resistance_predict().")
}
x_name <- paste0(ab_name(attributes(x)$ab), " (", attributes(x)$ab, ")") x_name <- paste0(ab_name(attributes(x)$ab), " (", attributes(x)$ab, ")")

58
R/rsi.R
View File

@ -209,12 +209,11 @@ as.rsi.default <- function(x, ...) {
#' @rdname as.rsi #' @rdname as.rsi
#' @export #' @export
as.rsi.mic <- function(x, mo, ab = deparse(substitute(x)), guideline = "EUCAST", uti = FALSE, ...) { as.rsi.mic <- function(x, mo, ab = deparse(substitute(x)), guideline = "EUCAST", uti = FALSE, ...) {
if (missing(mo)) { stop_if(missing(mo),
stop('No information was supplied about the microorganisms (missing parameter "mo"). See ?as.rsi.\n\n', 'No information was supplied about the microorganisms (missing parameter "mo"). See ?as.rsi.\n\n',
"To transform certain columns with e.g. mutate_at(), use\n", "To transform certain columns with e.g. mutate_at(), use\n",
"`data %>% mutate_at(vars(...), as.rsi, mo = .$x)`, where x is your column with microorganisms.\n\n", "`data %>% mutate_at(vars(...), as.rsi, mo = .$x)`, where x is your column with microorganisms.\n\n",
"To tranform all MIC variables in a data set, use `as.rsi(data)` or `data %>% as.rsi()`.", call. = FALSE) "To tranform all MIC variables in a data set, use `as.rsi(data)` or `data %>% as.rsi()`.", call = FALSE)
}
ab_coerced <- suppressWarnings(as.ab(ab)) ab_coerced <- suppressWarnings(as.ab(ab))
mo_coerced <- suppressWarnings(as.mo(mo)) mo_coerced <- suppressWarnings(as.mo(mo))
@ -246,12 +245,11 @@ as.rsi.mic <- function(x, mo, ab = deparse(substitute(x)), guideline = "EUCAST",
#' @rdname as.rsi #' @rdname as.rsi
#' @export #' @export
as.rsi.disk <- function(x, mo, ab = deparse(substitute(x)), guideline = "EUCAST", uti = FALSE, ...) { as.rsi.disk <- function(x, mo, ab = deparse(substitute(x)), guideline = "EUCAST", uti = FALSE, ...) {
if (missing(mo)) { stop_if(missing(mo),
stop('No information was supplied about the microorganisms (missing parameter "mo"). See ?as.rsi.\n\n', 'No information was supplied about the microorganisms (missing parameter "mo"). See ?as.rsi.\n\n',
"To transform certain columns with e.g. mutate_at(), use\n", "To transform certain columns with e.g. mutate_at(), use\n",
"`data %>% mutate_at(vars(...), as.rsi, mo = .$x)`, where x is your column with microorganisms.\n\n", "`data %>% mutate_at(vars(...), as.rsi, mo = .$x)`, where x is your column with microorganisms.\n\n",
"To tranform all disk diffusion zones in a data set, use `as.rsi(data)` or `data %>% as.rsi()`.", call. = FALSE) "To tranform all disk diffusion zones in a data set, use `as.rsi(data)` or `data %>% as.rsi()`.", call = FALSE)
}
ab_coerced <- suppressWarnings(as.ab(ab)) ab_coerced <- suppressWarnings(as.ab(ab))
mo_coerced <- suppressWarnings(as.mo(mo)) mo_coerced <- suppressWarnings(as.mo(mo))
@ -287,10 +285,9 @@ as.rsi.data.frame <- function(x, col_mo = NULL, guideline = "EUCAST", uti = NULL
# -- mo # -- mo
if (is.null(col_mo)) { if (is.null(col_mo)) {
col_mo <- search_type_in_df(x = x, type = "mo") col_mo <- search_type_in_df(x = x, type = "mo")
stop_if(is.null(col_mo), "`col_mo` must be set")
} }
if (is.null(col_mo)) {
stop("`col_mo` must be set.", call. = FALSE)
}
# -- UTIs # -- UTIs
col_uti <- uti col_uti <- uti
if (is.null(col_uti)) { if (is.null(col_uti)) {
@ -353,9 +350,8 @@ as.rsi.data.frame <- function(x, col_mo = NULL, guideline = "EUCAST", uti = NULL
} }
})] })]
if (length(ab_cols) == 0) { stop_if(length(ab_cols) == 0,
stop("No columns with MIC values or disk zones found in this data set. Use as.mic() or as.disk() to transform antimicrobial columns.", call. = FALSE) "no columns with MIC values or disk zones found in this data set. Use as.mic() or as.disk() to transform antimicrobial columns.")
}
# set type per column # set type per column
types <- character(length(ab_cols)) types <- character(length(ab_cols))
@ -393,11 +389,9 @@ get_guideline <- function(guideline) {
guideline_param <- gsub("([a-z]+)([0-9]+)", "\\1 \\2", guideline_param, ignore.case = TRUE) guideline_param <- gsub("([a-z]+)([0-9]+)", "\\1 \\2", guideline_param, ignore.case = TRUE)
} }
if (!guideline_param %in% rsi_translation$guideline) { stop_ifnot(guideline_param %in% rsi_translation$guideline,
stop(paste0("invalid guideline: '", guideline, "invalid guideline: '", guideline,
"'.\nValid guidelines are: ", paste0("'", unique(rsi_translation$guideline), "'", collapse = ", "), "."), "'.\nValid guidelines are: ", paste0("'", unique(rsi_translation$guideline), "'", collapse = ", "), call = FALSE)
call. = FALSE)
}
guideline_param guideline_param
@ -503,9 +497,8 @@ is.rsi <- function(x) {
#' @rdname as.rsi #' @rdname as.rsi
#' @export #' @export
is.rsi.eligible <- function(x, threshold = 0.05) { is.rsi.eligible <- function(x, threshold = 0.05) {
if (NCOL(x) > 1) { stop_if(NCOL(x) > 1, "`x` must be a one-dimensional vector.")
stop("`x` must be a one-dimensional vector.")
}
if (any(c("logical", if (any(c("logical",
"numeric", "numeric",
"integer", "integer",
@ -551,13 +544,16 @@ droplevels.rsi <- function(x, exclude = if (anyNA(levels(x))) NULL else NA, ...)
#' @noRd #' @noRd
summary.rsi <- function(object, ...) { summary.rsi <- function(object, ...) {
x <- object x <- object
n <- sum(!is.na(x))
S <- sum(x == "S", na.rm = TRUE)
I <- sum(x == "I", na.rm = TRUE)
R <- sum(x == "R", na.rm = TRUE)
c( c(
"Class" = "rsi", "Class" = "rsi",
"<NA>" = sum(is.na(x)), "%R" = paste0(percentage(R / n), " (n=", R, ")"),
"Sum S" = sum(x == "S", na.rm = TRUE), "%SI" = paste0(percentage((S + I) / n), " (n=", S + I, ")"),
"Sum IR" = sum(x %in% c("I", "R"), na.rm = TRUE), "- %S" = paste0(percentage(S / n), " (n=", S, ")"),
"-Sum R" = sum(x == "R", na.rm = TRUE), "- %I" = paste0(percentage(I / n), " (n=", I, ")")
"-Sum I" = sum(x == "I", na.rm = TRUE)
) )
} }

View File

@ -33,23 +33,19 @@ rsi_calc <- function(...,
only_all_tested = FALSE, only_all_tested = FALSE,
only_count = FALSE) { only_count = FALSE) {
stop_ifnot(is.numeric(minimum), "`minimum` must be numeric", call = -2)
stop_ifnot(is.logical(as_percent), "`as_percent` must be logical", call = -2)
stop_ifnot(is.logical(only_all_tested), "`only_all_tested` must be logical", call = -2)
data_vars <- dots2vars(...) data_vars <- dots2vars(...)
if (!is.numeric(minimum)) {
stop("`minimum` must be numeric", call. = FALSE)
}
if (!is.logical(as_percent)) {
stop("`as_percent` must be logical", call. = FALSE)
}
if (!is.logical(only_all_tested)) {
stop("`only_all_tested` must be logical", call. = FALSE)
}
dots_df <- switch(1, ...) dots_df <- switch(1, ...)
dots <- base::eval(base::substitute(base::alist(...))) dots <- base::eval(base::substitute(base::alist(...)))
if ("also_single_tested" %in% names(dots)) { stop_if(length(dots) == 0, "no variables selected", call = -2)
stop("`also_single_tested` was replaced by `only_all_tested`. Please read Details in the help page (`?proportion`) as this may have a considerable impact on your analysis.", call. = FALSE)
} stop_if("also_single_tested" %in% names(dots),
"`also_single_tested` was replaced by `only_all_tested`.\n",
"Please read Details in the help page (`?proportion`) as this may have a considerable impact on your analysis.", call = -2)
ndots <- length(dots) ndots <- length(dots)
if ("data.frame" %in% class(dots_df)) { if ("data.frame" %in% class(dots_df)) {
@ -164,22 +160,15 @@ rsi_calc_df <- function(type, # "proportion", "count" or "both"
combine_SI_missing = FALSE) { combine_SI_missing = FALSE) {
check_dataset_integrity() check_dataset_integrity()
stop_ifnot(is.data.frame(data), "`data` must be a data.frame", call = -2)
if (!"data.frame" %in% class(data)) { stop_if(any(dim(data) == 0), "`data` must contain rows and columns", call = -2)
stop(paste0("`", type, "_df` must be called on a data.frame"), call. = FALSE) stop_ifnot(any(sapply(data, is.rsi), na.rm = TRUE), "no columns with class <rsi> found. See ?as.rsi.", call = -2)
} stop_if(isTRUE(combine_SI) & isTRUE(combine_IR), "either `combine_SI` or `combine_IR` can be TRUE, not both", call = -2)
if (isTRUE(combine_IR) & isTRUE(combine_SI_missing)) { if (isTRUE(combine_IR) & isTRUE(combine_SI_missing)) {
combine_SI <- FALSE combine_SI <- FALSE
} }
if (isTRUE(combine_SI) & isTRUE(combine_IR)) {
stop("either `combine_SI` or `combine_IR` can be TRUE, not both", call. = FALSE)
}
if (!any(sapply(data, is.rsi), na.rm = TRUE)) {
stop("No columns with class <rsi> found. See ?as.rsi.", call. = FALSE)
}
if (as.character(translate_ab) %in% c("TRUE", "official")) { if (as.character(translate_ab) %in% c("TRUE", "official")) {
translate_ab <- "name" translate_ab <- "name"
} }

View File

@ -108,11 +108,10 @@ translate_AMR <- function(from, language = get_locale(), only_unknown = FALSE) {
df_trans <- translations_file # internal data file df_trans <- translations_file # internal data file
if (!language %in% df_trans$lang) { stop_ifnot(language %in% df_trans$lang,
stop("Unsupported language: '", language, "' - use one of: ", "unsupported language: '", language, "' - use one of: ",
paste0("'", sort(unique(df_trans$lang)), "'", collapse = ", "), paste0("'", sort(unique(df_trans$lang)), "'", collapse = ", "),
call. = FALSE) call = FALSE)
}
df_trans <- df_trans %>% subset(lang == language) df_trans <- df_trans %>% subset(lang == language)
if (only_unknown == TRUE) { if (only_unknown == TRUE) {

10
R/zzz.R
View File

@ -23,11 +23,11 @@
assign(x = "MO_lookup", assign(x = "MO_lookup",
value = create_MO_lookup(), value = create_MO_lookup(),
envir = asNamespace("AMR")) envir = asNamespace("AMR"))
assign(x = "MO.old_lookup", assign(x = "MO.old_lookup",
value = create_MO.old_lookup(), value = create_MO.old_lookup(),
envir = asNamespace("AMR")) envir = asNamespace("AMR"))
assign(x = "mo_codes_v0.5.0", assign(x = "mo_codes_v0.5.0",
value = make_trans_tbl(), value = make_trans_tbl(),
envir = asNamespace("AMR")) envir = asNamespace("AMR"))
@ -47,10 +47,10 @@ create_MO_lookup <- function() {
# use this paste instead of `fullname` to # use this paste instead of `fullname` to
# work with Viridans Group Streptococci, etc. # work with Viridans Group Streptococci, etc.
MO_lookup$fullname_lower <- tolower(trimws(paste(MO_lookup$genus, MO_lookup$fullname_lower <- tolower(trimws(paste(MO_lookup$genus,
MO_lookup$species, MO_lookup$species,
MO_lookup$subspecies))) MO_lookup$subspecies)))
MO_lookup[MO_lookup$genus == "" | grepl("^[(]unknown ", MO_lookup$fullname), "fullname_lower"] <- tolower(trimws(MO_lookup[MO_lookup$genus == "" | grepl("^[(]unknown ", MO_lookup$fullname), MO_lookup[MO_lookup$genus == "" | grepl("^[(]unknown ", MO_lookup$fullname), "fullname_lower"] <- tolower(trimws(MO_lookup[MO_lookup$genus == "" | grepl("^[(]unknown ", MO_lookup$fullname),
"fullname"])) "fullname"]))
MO_lookup$fullname_lower <- gsub("[^.a-z0-9/ \\-]+", "", MO_lookup$fullname_lower) MO_lookup$fullname_lower <- gsub("[^.a-z0-9/ \\-]+", "", MO_lookup$fullname_lower)
# add a column with only "e coli" like combinations # add a column with only "e coli" like combinations

View File

@ -81,7 +81,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="https://msberends.gitlab.io/AMR/index.html">AMR (for R)</a> <a class="navbar-link" href="https://msberends.gitlab.io/AMR/index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>

View File

@ -81,7 +81,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a> <a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>

View File

@ -39,7 +39,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9008</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>
@ -186,7 +186,7 @@
<h1 data-toc-skip>How to conduct AMR analysis</h1> <h1 data-toc-skip>How to conduct AMR analysis</h1>
<h4 class="author">Matthijs S. Berends</h4> <h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">17 June 2020</h4> <h4 class="date">22 June 2020</h4>
<small class="dont-index">Source: <a href="https://gitlab.com/msberends/AMR/blob/master/vignettes/AMR.Rmd"><code>vignettes/AMR.Rmd</code></a></small> <small class="dont-index">Source: <a href="https://gitlab.com/msberends/AMR/blob/master/vignettes/AMR.Rmd"><code>vignettes/AMR.Rmd</code></a></small>
<div class="hidden name"><code>AMR.Rmd</code></div> <div class="hidden name"><code>AMR.Rmd</code></div>
@ -195,7 +195,7 @@
<p><strong>Note:</strong> values on this page will change with every website update since they are based on randomly created values and the page was written in <a href="https://rmarkdown.rstudio.com/">R Markdown</a>. However, the methodology remains unchanged. This page was generated on 17 June 2020.</p> <p><strong>Note:</strong> values on this page will change with every website update since they are based on randomly created values and the page was written in <a href="https://rmarkdown.rstudio.com/">R Markdown</a>. However, the methodology remains unchanged. This page was generated on 22 June 2020.</p>
<div id="introduction" class="section level1"> <div id="introduction" class="section level1">
<h1 class="hasAnchor"> <h1 class="hasAnchor">
<a href="#introduction" class="anchor"></a>Introduction</h1> <a href="#introduction" class="anchor"></a>Introduction</h1>
@ -226,21 +226,21 @@
</tr></thead> </tr></thead>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">2020-06-17</td> <td align="center">2020-06-22</td>
<td align="center">abcd</td> <td align="center">abcd</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2020-06-17</td> <td align="center">2020-06-22</td>
<td align="center">abcd</td> <td align="center">abcd</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">R</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">2020-06-17</td> <td align="center">2020-06-22</td>
<td align="center">efgh</td> <td align="center">efgh</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">R</td> <td align="center">R</td>
@ -336,71 +336,71 @@
</tr></thead> </tr></thead>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">2014-09-10</td> <td align="center">2014-04-15</td>
<td align="center">V9</td> <td align="center">I4</td>
<td align="center">Hospital A</td> <td align="center">Hospital D</td>
<td align="center">Streptococcus pneumoniae</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="even">
<td align="center">2011-09-21</td>
<td align="center">Y7</td>
<td align="center">Hospital B</td>
<td align="center">Streptococcus pneumoniae</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="odd">
<td align="center">2014-05-27</td>
<td align="center">U4</td>
<td align="center">Hospital B</td>
<td align="center">Klebsiella pneumoniae</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="even">
<td align="center">2013-01-03</td>
<td align="center">I8</td>
<td align="center">Hospital B</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">M</td>
</tr>
<tr class="even">
<td align="center">2011-02-09</td>
<td align="center">D1</td>
<td align="center">Hospital A</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">M</td> <td align="center">M</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">2011-06-08</td> <td align="center">2013-12-16</td>
<td align="center">K4</td> <td align="center">K4</td>
<td align="center">Hospital B</td> <td align="center">Hospital C</td>
<td align="center">Streptococcus pneumoniae</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">M</td>
</tr>
<tr class="even">
<td align="center">2017-09-29</td>
<td align="center">T5</td>
<td align="center">Hospital A</td>
<td align="center">Staphylococcus aureus</td> <td align="center">Staphylococcus aureus</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">I</td> <td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">M</td>
</tr>
<tr class="even">
<td align="center">2017-08-23</td>
<td align="center">Z9</td>
<td align="center">Hospital B</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">F</td> <td align="center">F</td>
</tr> </tr>
<tr class="odd">
<td align="center">2010-01-14</td>
<td align="center">N4</td>
<td align="center">Hospital A</td>
<td align="center">Staphylococcus aureus</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td>
</tr>
<tr class="even">
<td align="center">2016-01-31</td>
<td align="center">N1</td>
<td align="center">Hospital D</td>
<td align="center">Staphylococcus aureus</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">M</td>
</tr>
</tbody> </tbody>
</table> </table>
<p>Now, lets start the cleaning and the analysis!</p> <p>Now, lets start the cleaning and the analysis!</p>
@ -432,16 +432,16 @@ Longest: 1</p>
<tr class="odd"> <tr class="odd">
<td align="left">1</td> <td align="left">1</td>
<td align="left">M</td> <td align="left">M</td>
<td align="right">10,319</td> <td align="right">10,328</td>
<td align="right">51.60%</td> <td align="right">51.64%</td>
<td align="right">10,319</td> <td align="right">10,328</td>
<td align="right">51.60%</td> <td align="right">51.64%</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="left">2</td> <td align="left">2</td>
<td align="left">F</td> <td align="left">F</td>
<td align="right">9,681</td> <td align="right">9,672</td>
<td align="right">48.41%</td> <td align="right">48.36%</td>
<td align="right">20,000</td> <td align="right">20,000</td>
<td align="right">100.00%</td> <td align="right">100.00%</td>
</tr> </tr>
@ -481,7 +481,7 @@ Longest: 1</p>
<span class="co"># NOTE: Using column `bacteria` as input for `col_mo`.</span> <span class="co"># NOTE: Using column `bacteria` as input for `col_mo`.</span>
<span class="co"># NOTE: Using column `date` as input for `col_date`.</span> <span class="co"># NOTE: Using column `date` as input for `col_date`.</span>
<span class="co"># NOTE: Using column `patient_id` as input for `col_patient_id`.</span></pre></body></html></div> <span class="co"># NOTE: Using column `patient_id` as input for `col_patient_id`.</span></pre></body></html></div>
<p>So only 28.2% is suitable for resistance analysis! We can now filter on it with the <code><a href="https://dplyr.tidyverse.org/reference/filter.html">filter()</a></code> function, also from the <code>dplyr</code> package:</p> <p>So only 28.3% is suitable for resistance analysis! We can now filter on it with the <code><a href="https://dplyr.tidyverse.org/reference/filter.html">filter()</a></code> function, also from the <code>dplyr</code> package:</p>
<div class="sourceCode" id="cb16"><html><body><pre class="r"><span class="no">data_1st</span> <span class="kw">&lt;-</span> <span class="no">data</span> <span class="kw">%&gt;%</span> <div class="sourceCode" id="cb16"><html><body><pre class="r"><span class="no">data_1st</span> <span class="kw">&lt;-</span> <span class="no">data</span> <span class="kw">%&gt;%</span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(<span class="no">first</span> <span class="kw">==</span> <span class="fl">TRUE</span>)</pre></body></html></div> <span class="fu"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(<span class="no">first</span> <span class="kw">==</span> <span class="fl">TRUE</span>)</pre></body></html></div>
<p>For future use, the above two syntaxes can be shortened with the <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> function:</p> <p>For future use, the above two syntaxes can be shortened with the <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> function:</p>
@ -491,7 +491,7 @@ Longest: 1</p>
<div id="first-weighted-isolates" class="section level2"> <div id="first-weighted-isolates" class="section level2">
<h2 class="hasAnchor"> <h2 class="hasAnchor">
<a href="#first-weighted-isolates" class="anchor"></a>First <em>weighted</em> isolates</h2> <a href="#first-weighted-isolates" class="anchor"></a>First <em>weighted</em> isolates</h2>
<p>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 A2, sorted on date:</p> <p>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 N3, sorted on date:</p>
<table class="table"> <table class="table">
<thead><tr class="header"> <thead><tr class="header">
<th align="center">isolate</th> <th align="center">isolate</th>
@ -507,10 +507,10 @@ Longest: 1</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">1</td> <td align="center">1</td>
<td align="center">2010-02-14</td> <td align="center">2010-03-10</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td> <td align="center">I</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@ -518,8 +518,8 @@ Longest: 1</p>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2</td> <td align="center">2</td>
<td align="center">2010-03-19</td> <td align="center">2010-05-11</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@ -529,21 +529,21 @@ Longest: 1</p>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">3</td> <td align="center">3</td>
<td align="center">2010-08-09</td> <td align="center">2010-05-17</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">4</td> <td align="center">4</td>
<td align="center">2010-12-29</td> <td align="center">2010-05-18</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@ -551,8 +551,8 @@ Longest: 1</p>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">5</td> <td align="center">5</td>
<td align="center">2011-02-03</td> <td align="center">2010-07-30</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@ -562,62 +562,62 @@ Longest: 1</p>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">6</td> <td align="center">6</td>
<td align="center">2011-04-15</td> <td align="center">2010-09-15</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">R</td>
<td align="center">TRUE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">7</td> <td align="center">7</td>
<td align="center">2011-04-22</td> <td align="center">2010-10-06</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">8</td> <td align="center">8</td>
<td align="center">2011-06-10</td> <td align="center">2010-11-30</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">9</td> <td align="center">9</td>
<td align="center">2011-07-20</td> <td align="center">2011-01-27</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">I</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">10</td> <td align="center">10</td>
<td align="center">2011-08-06</td> <td align="center">2011-01-30</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
<p>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 <code><a href="../reference/key_antibiotics.html">key_antibiotics()</a></code> 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.</p> <p>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 <code><a href="../reference/key_antibiotics.html">key_antibiotics()</a></code> 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.</p>
<p>If a column exists with a name like key(…)ab the <code><a href="../reference/first_isolate.html">first_isolate()</a></code> function will automatically use it and determine the first weighted isolates. Mind the NOTEs in below output:</p> <p>If a column exists with a name like key(…)ab the <code><a href="../reference/first_isolate.html">first_isolate()</a></code> function will automatically use it and determine the first weighted isolates. Mind the NOTEs in below output:</p>
<div class="sourceCode" id="cb18"><html><body><pre class="r"><span class="no">data</span> <span class="kw">&lt;-</span> <span class="no">data</span> <span class="kw">%&gt;%</span> <div class="sourceCode" id="cb18"><html><body><pre class="r"><span class="no">data</span> <span class="kw">&lt;-</span> <span class="no">data</span> <span class="kw">%&gt;%</span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="kw">keyab</span> <span class="kw">=</span> <span class="fu"><a href="../reference/key_antibiotics.html">key_antibiotics</a></span>(<span class="no">.</span>)) <span class="kw">%&gt;%</span> <span class="fu"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="kw">keyab</span> <span class="kw">=</span> <span class="fu"><a href="../reference/key_antibiotics.html">key_antibiotics</a></span>(<span class="no">.</span>)) <span class="kw">%&gt;%</span>
@ -643,10 +643,10 @@ Longest: 1</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">1</td> <td align="center">1</td>
<td align="center">2010-02-14</td> <td align="center">2010-03-10</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td> <td align="center">I</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@ -655,95 +655,95 @@ Longest: 1</p>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2</td> <td align="center">2</td>
<td align="center">2010-03-19</td> <td align="center">2010-05-11</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">TRUE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">3</td> <td align="center">3</td>
<td align="center">2010-08-09</td> <td align="center">2010-05-17</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">4</td> <td align="center">4</td>
<td align="center">2010-12-29</td> <td align="center">2010-05-18</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">TRUE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">5</td> <td align="center">5</td>
<td align="center">2011-02-03</td> <td align="center">2010-07-30</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">FALSE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">6</td> <td align="center">6</td>
<td align="center">2011-04-15</td> <td align="center">2010-09-15</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">R</td>
<td align="center">TRUE</td> <td align="center">FALSE</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">7</td> <td align="center">7</td>
<td align="center">2011-04-22</td> <td align="center">2010-10-06</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">FALSE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">8</td> <td align="center">8</td>
<td align="center">2011-06-10</td> <td align="center">2010-11-30</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">9</td> <td align="center">9</td>
<td align="center">2011-07-20</td> <td align="center">2011-01-27</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">I</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
@ -751,23 +751,23 @@ Longest: 1</p>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">10</td> <td align="center">10</td>
<td align="center">2011-08-06</td> <td align="center">2011-01-30</td>
<td align="center">A2</td> <td align="center">N3</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
<p>Instead of 2, now 8 isolates are flagged. In total, 78.6% of all isolates are marked first weighted - 50.4% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.</p> <p>Instead of 1, now 7 isolates are flagged. In total, 78.7% of all isolates are marked first weighted - 50.4% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.</p>
<p>As with <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code>, theres a shortcut for this new algorithm too:</p> <p>As with <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code>, theres a shortcut for this new algorithm too:</p>
<div class="sourceCode" id="cb19"><html><body><pre class="r"><span class="no">data_1st</span> <span class="kw">&lt;-</span> <span class="no">data</span> <span class="kw">%&gt;%</span> <div class="sourceCode" id="cb19"><html><body><pre class="r"><span class="no">data_1st</span> <span class="kw">&lt;-</span> <span class="no">data</span> <span class="kw">%&gt;%</span>
<span class="fu"><a href="../reference/first_isolate.html">filter_first_weighted_isolate</a></span>()</pre></body></html></div> <span class="fu"><a href="../reference/first_isolate.html">filter_first_weighted_isolate</a></span>()</pre></body></html></div>
<p>So we end up with 15,719 isolates for analysis.</p> <p>So we end up with 15,740 isolates for analysis.</p>
<p>We can remove unneeded columns:</p> <p>We can remove unneeded columns:</p>
<div class="sourceCode" id="cb20"><html><body><pre class="r"><span class="no">data_1st</span> <span class="kw">&lt;-</span> <span class="no">data_1st</span> <span class="kw">%&gt;%</span> <div class="sourceCode" id="cb20"><html><body><pre class="r"><span class="no">data_1st</span> <span class="kw">&lt;-</span> <span class="no">data_1st</span> <span class="kw">%&gt;%</span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(-<span class="fu"><a href="https://rdrr.io/r/base/c.html">c</a></span>(<span class="no">first</span>, <span class="no">keyab</span>))</pre></body></html></div> <span class="fu"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(-<span class="fu"><a href="https://rdrr.io/r/base/c.html">c</a></span>(<span class="no">first</span>, <span class="no">keyab</span>))</pre></body></html></div>
@ -775,7 +775,6 @@ Longest: 1</p>
<div class="sourceCode" id="cb21"><html><body><pre class="r"><span class="fu"><a href="https://rdrr.io/r/utils/head.html">head</a></span>(<span class="no">data_1st</span>)</pre></body></html></div> <div class="sourceCode" id="cb21"><html><body><pre class="r"><span class="fu"><a href="https://rdrr.io/r/utils/head.html">head</a></span>(<span class="no">data_1st</span>)</pre></body></html></div>
<table class="table"> <table class="table">
<thead><tr class="header"> <thead><tr class="header">
<th></th>
<th align="center">date</th> <th align="center">date</th>
<th align="center">patient_id</th> <th align="center">patient_id</th>
<th align="center">hospital</th> <th align="center">hospital</th>
@ -792,46 +791,13 @@ Longest: 1</p>
</tr></thead> </tr></thead>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td>1</td> <td align="center">2014-04-15</td>
<td align="center">2014-09-10</td> <td align="center">I4</td>
<td align="center">V9</td> <td align="center">Hospital D</td>
<td align="center">Hospital A</td>
<td align="center">B_STRPT_PNMN</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">F</td>
<td align="center">Gram-positive</td>
<td align="center">Streptococcus</td>
<td align="center">pneumoniae</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td>3</td>
<td align="center">2014-05-27</td>
<td align="center">U4</td>
<td align="center">Hospital B</td>
<td align="center">B_KLBSL_PNMN</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
<td align="center">Gram-negative</td>
<td align="center">Klebsiella</td>
<td align="center">pneumoniae</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td>4</td>
<td align="center">2013-01-03</td>
<td align="center">I8</td>
<td align="center">Hospital B</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">M</td> <td align="center">M</td>
<td align="center">Gram-negative</td> <td align="center">Gram-negative</td>
@ -840,51 +806,78 @@ Longest: 1</p>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td>6</td> <td align="center">2011-02-09</td>
<td align="center">2017-09-29</td> <td align="center">D1</td>
<td align="center">T5</td>
<td align="center">Hospital A</td> <td align="center">Hospital A</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td>
<td align="center">Gram-negative</td>
<td align="center">Escherichia</td>
<td align="center">coli</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">2013-12-16</td>
<td align="center">K4</td>
<td align="center">Hospital C</td>
<td align="center">B_STPHY_AURS</td> <td align="center">B_STPHY_AURS</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">M</td>
<td align="center">F</td>
<td align="center">Gram-positive</td> <td align="center">Gram-positive</td>
<td align="center">Staphylococcus</td> <td align="center">Staphylococcus</td>
<td align="center">aureus</td> <td align="center">aureus</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="odd"> <tr class="even">
<td>8</td> <td align="center">2017-08-23</td>
<td align="center">2012-07-08</td> <td align="center">Z9</td>
<td align="center">B2</td>
<td align="center">Hospital B</td> <td align="center">Hospital B</td>
<td align="center">B_ESCHR_COLI</td> <td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">M</td> <td align="center">S</td>
<td align="center">F</td>
<td align="center">Gram-negative</td> <td align="center">Gram-negative</td>
<td align="center">Escherichia</td> <td align="center">Escherichia</td>
<td align="center">coli</td> <td align="center">coli</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="odd">
<td>9</td> <td align="center">2010-01-14</td>
<td align="center">2014-01-07</td> <td align="center">N4</td>
<td align="center">G7</td>
<td align="center">Hospital A</td> <td align="center">Hospital A</td>
<td align="center">B_STRPT_PNMN</td> <td align="center">B_STPHY_AURS</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td> <td align="center">M</td>
<td align="center">Gram-positive</td> <td align="center">Gram-positive</td>
<td align="center">Streptococcus</td> <td align="center">Staphylococcus</td>
<td align="center">pneumoniae</td> <td align="center">aureus</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">2016-01-31</td>
<td align="center">N1</td>
<td align="center">Hospital D</td>
<td align="center">B_STPHY_AURS</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">M</td>
<td align="center">Gram-positive</td>
<td align="center">Staphylococcus</td>
<td align="center">aureus</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
</tbody> </tbody>
@ -906,8 +899,8 @@ Longest: 1</p>
<div class="sourceCode" id="cb23"><html><body><pre class="r"><span class="no">data_1st</span> <span class="kw">%&gt;%</span> <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(<span class="no">genus</span>, <span class="no">species</span>)</pre></body></html></div> <div class="sourceCode" id="cb23"><html><body><pre class="r"><span class="no">data_1st</span> <span class="kw">%&gt;%</span> <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(<span class="no">genus</span>, <span class="no">species</span>)</pre></body></html></div>
<p><strong>Frequency table</strong></p> <p><strong>Frequency table</strong></p>
<p>Class: character<br> <p>Class: character<br>
Length: 15,719<br> Length: 15,740<br>
Available: 15,719 (100%, NA: 0 = 0%)<br> Available: 15,740 (100%, NA: 0 = 0%)<br>
Unique: 4</p> Unique: 4</p>
<p>Shortest: 16<br> <p>Shortest: 16<br>
Longest: 24</p> Longest: 24</p>
@ -924,33 +917,33 @@ Longest: 24</p>
<tr class="odd"> <tr class="odd">
<td align="left">1</td> <td align="left">1</td>
<td align="left">Escherichia coli</td> <td align="left">Escherichia coli</td>
<td align="right">7,906</td> <td align="right">7,938</td>
<td align="right">50.30%</td> <td align="right">50.43%</td>
<td align="right">7,906</td> <td align="right">7,938</td>
<td align="right">50.30%</td> <td align="right">50.43%</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="left">2</td> <td align="left">2</td>
<td align="left">Staphylococcus aureus</td> <td align="left">Staphylococcus aureus</td>
<td align="right">3,898</td> <td align="right">3,883</td>
<td align="right">24.80%</td> <td align="right">24.67%</td>
<td align="right">11,804</td> <td align="right">11,821</td>
<td align="right">75.09%</td> <td align="right">75.10%</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="left">3</td> <td align="left">3</td>
<td align="left">Streptococcus pneumoniae</td> <td align="left">Streptococcus pneumoniae</td>
<td align="right">2,330</td> <td align="right">2,317</td>
<td align="right">14.82%</td> <td align="right">14.72%</td>
<td align="right">14,134</td> <td align="right">14,138</td>
<td align="right">89.92%</td> <td align="right">89.82%</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="left">4</td> <td align="left">4</td>
<td align="left">Klebsiella pneumoniae</td> <td align="left">Klebsiella pneumoniae</td>
<td align="right">1,585</td> <td align="right">1,602</td>
<td align="right">10.08%</td> <td align="right">10.18%</td>
<td align="right">15,719</td> <td align="right">15,740</td>
<td align="right">100.00%</td> <td align="right">100.00%</td>
</tr> </tr>
</tbody> </tbody>
@ -977,50 +970,50 @@ Longest: 24</p>
<tr class="odd"> <tr class="odd">
<td align="center">E. coli</td> <td align="center">E. coli</td>
<td align="center">AMX</td> <td align="center">AMX</td>
<td align="center">3784</td> <td align="center">3808</td>
<td align="center">244</td> <td align="center">236</td>
<td align="center">3878</td> <td align="center">3894</td>
<td align="center">7906</td> <td align="center">7938</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">E. coli</td> <td align="center">E. coli</td>
<td align="center">AMC</td> <td align="center">AMC</td>
<td align="center">6252</td> <td align="center">6223</td>
<td align="center">274</td> <td align="center">317</td>
<td align="center">1380</td> <td align="center">1398</td>
<td align="center">7906</td> <td align="center">7938</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">E. coli</td> <td align="center">E. coli</td>
<td align="center">CIP</td> <td align="center">CIP</td>
<td align="center">6028</td> <td align="center">6050</td>
<td align="center">0</td> <td align="center">0</td>
<td align="center">1878</td> <td align="center">1888</td>
<td align="center">7906</td> <td align="center">7938</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">E. coli</td> <td align="center">E. coli</td>
<td align="center">GEN</td> <td align="center">GEN</td>
<td align="center">7176</td> <td align="center">7130</td>
<td align="center">0</td> <td align="center">0</td>
<td align="center">730</td> <td align="center">808</td>
<td align="center">7906</td> <td align="center">7938</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">K. pneumoniae</td> <td align="center">K. pneumoniae</td>
<td align="center">AMX</td> <td align="center">AMX</td>
<td align="center">0</td> <td align="center">0</td>
<td align="center">0</td> <td align="center">0</td>
<td align="center">1585</td> <td align="center">1602</td>
<td align="center">1585</td> <td align="center">1602</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">K. pneumoniae</td> <td align="center">K. pneumoniae</td>
<td align="center">AMC</td> <td align="center">AMC</td>
<td align="center">1241</td> <td align="center">1241</td>
<td align="center">60</td> <td align="center">61</td>
<td align="center">284</td> <td align="center">300</td>
<td align="center">1585</td> <td align="center">1602</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
@ -1043,34 +1036,34 @@ Longest: 24</p>
<tr class="odd"> <tr class="odd">
<td align="center">E. coli</td> <td align="center">E. coli</td>
<td align="center">CIP</td> <td align="center">CIP</td>
<td align="center">6028</td> <td align="center">6050</td>
<td align="center">0</td> <td align="center">0</td>
<td align="center">1878</td> <td align="center">1888</td>
<td align="center">7906</td> <td align="center">7938</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">K. pneumoniae</td> <td align="center">K. pneumoniae</td>
<td align="center">CIP</td> <td align="center">CIP</td>
<td align="center">1223</td> <td align="center">1218</td>
<td align="center">0</td> <td align="center">0</td>
<td align="center">362</td> <td align="center">384</td>
<td align="center">1585</td> <td align="center">1602</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">S. aureus</td> <td align="center">S. aureus</td>
<td align="center">CIP</td> <td align="center">CIP</td>
<td align="center">2961</td> <td align="center">2967</td>
<td align="center">0</td> <td align="center">0</td>
<td align="center">937</td> <td align="center">916</td>
<td align="center">3898</td> <td align="center">3883</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">S. pneumoniae</td> <td align="center">S. pneumoniae</td>
<td align="center">CIP</td> <td align="center">CIP</td>
<td align="center">1777</td> <td align="center">1756</td>
<td align="center">0</td> <td align="center">0</td>
<td align="center">553</td> <td align="center">561</td>
<td align="center">2330</td> <td align="center">2317</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
@ -1082,7 +1075,7 @@ Longest: 24</p>
<p>The functions <code><a href="../reference/proportion.html">resistance()</a></code> and <code><a href="../reference/proportion.html">susceptibility()</a></code> can be used to calculate antimicrobial resistance or susceptibility. For more specific analyses, the functions <code><a href="../reference/proportion.html">proportion_S()</a></code>, <code><a href="../reference/proportion.html">proportion_SI()</a></code>, <code><a href="../reference/proportion.html">proportion_I()</a></code>, <code><a href="../reference/proportion.html">proportion_IR()</a></code> and <code><a href="../reference/proportion.html">proportion_R()</a></code> can be used to determine the proportion of a specific antimicrobial outcome.</p> <p>The functions <code><a href="../reference/proportion.html">resistance()</a></code> and <code><a href="../reference/proportion.html">susceptibility()</a></code> can be used to calculate antimicrobial resistance or susceptibility. For more specific analyses, the functions <code><a href="../reference/proportion.html">proportion_S()</a></code>, <code><a href="../reference/proportion.html">proportion_SI()</a></code>, <code><a href="../reference/proportion.html">proportion_I()</a></code>, <code><a href="../reference/proportion.html">proportion_IR()</a></code> and <code><a href="../reference/proportion.html">proportion_R()</a></code> can be used to determine the proportion of a specific antimicrobial outcome.</p>
<p>As per the EUCAST guideline of 2019, we calculate resistance as the proportion of R (<code><a href="../reference/proportion.html">proportion_R()</a></code>, equal to <code><a href="../reference/proportion.html">resistance()</a></code>) and susceptibility as the proportion of S and I (<code><a href="../reference/proportion.html">proportion_SI()</a></code>, equal to <code><a href="../reference/proportion.html">susceptibility()</a></code>). These functions can be used on their own:</p> <p>As per the EUCAST guideline of 2019, we calculate resistance as the proportion of R (<code><a href="../reference/proportion.html">proportion_R()</a></code>, equal to <code><a href="../reference/proportion.html">resistance()</a></code>) and susceptibility as the proportion of S and I (<code><a href="../reference/proportion.html">proportion_SI()</a></code>, equal to <code><a href="../reference/proportion.html">susceptibility()</a></code>). These functions can be used on their own:</p>
<div class="sourceCode" id="cb28"><html><body><pre class="r"><span class="no">data_1st</span> <span class="kw">%&gt;%</span> <span class="fu"><a href="../reference/proportion.html">resistance</a></span>(<span class="no">AMX</span>) <div class="sourceCode" id="cb28"><html><body><pre class="r"><span class="no">data_1st</span> <span class="kw">%&gt;%</span> <span class="fu"><a href="../reference/proportion.html">resistance</a></span>(<span class="no">AMX</span>)
<span class="co"># [1] 0.5382022</span></pre></body></html></div> <span class="co"># [1] 0.535324</span></pre></body></html></div>
<p>Or can be used in conjuction with <code><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by()</a></code> and <code><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise()</a></code>, both from the <code>dplyr</code> package:</p> <p>Or can be used in conjuction with <code><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by()</a></code> and <code><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise()</a></code>, both from the <code>dplyr</code> package:</p>
<div class="sourceCode" id="cb29"><html><body><pre class="r"><span class="no">data_1st</span> <span class="kw">%&gt;%</span> <div class="sourceCode" id="cb29"><html><body><pre class="r"><span class="no">data_1st</span> <span class="kw">%&gt;%</span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(<span class="no">hospital</span>) <span class="kw">%&gt;%</span> <span class="fu"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(<span class="no">hospital</span>) <span class="kw">%&gt;%</span>
@ -1096,19 +1089,19 @@ Longest: 24</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">Hospital A</td> <td align="center">Hospital A</td>
<td align="center">0.5410830</td> <td align="center">0.5322921</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Hospital B</td> <td align="center">Hospital B</td>
<td align="center">0.5318994</td> <td align="center">0.5393839</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">Hospital C</td> <td align="center">Hospital C</td>
<td align="center">0.5342585</td> <td align="center">0.5327529</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Hospital D</td> <td align="center">Hospital D</td>
<td align="center">0.5477099</td> <td align="center">0.5348690</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
@ -1127,23 +1120,23 @@ Longest: 24</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">Hospital A</td> <td align="center">Hospital A</td>
<td align="center">0.5410830</td> <td align="center">0.5322921</td>
<td align="center">4783</td> <td align="center">4738</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Hospital B</td> <td align="center">Hospital B</td>
<td align="center">0.5318994</td> <td align="center">0.5393839</td>
<td align="center">5486</td> <td align="center">5421</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">Hospital C</td> <td align="center">Hospital C</td>
<td align="center">0.5342585</td> <td align="center">0.5327529</td>
<td align="center">2306</td> <td align="center">2412</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Hospital D</td> <td align="center">Hospital D</td>
<td align="center">0.5477099</td> <td align="center">0.5348690</td>
<td align="center">3144</td> <td align="center">3169</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
@ -1164,27 +1157,27 @@ Longest: 24</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">Escherichia</td> <td align="center">Escherichia</td>
<td align="center">0.8254490</td> <td align="center">0.8238851</td>
<td align="center">0.9076651</td> <td align="center">0.8982111</td>
<td align="center">0.9864660</td> <td align="center">0.9840010</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Klebsiella</td> <td align="center">Klebsiella</td>
<td align="center">0.8208202</td> <td align="center">0.8127341</td>
<td align="center">0.9015773</td> <td align="center">0.8951311</td>
<td align="center">0.9892744</td> <td align="center">0.9818976</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">Staphylococcus</td> <td align="center">Staphylococcus</td>
<td align="center">0.8134941</td> <td align="center">0.8246201</td>
<td align="center">0.9214982</td> <td align="center">0.9260881</td>
<td align="center">0.9858902</td> <td align="center">0.9863508</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Streptococcus</td> <td align="center">Streptococcus</td>
<td align="center">0.5454936</td> <td align="center">0.5463962</td>
<td align="center">0.0000000</td> <td align="center">0.0000000</td>
<td align="center">0.5454936</td> <td align="center">0.5463962</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>

Binary file not shown.

Before

Width:  |  Height:  |  Size: 64 KiB

After

Width:  |  Height:  |  Size: 64 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 51 KiB

After

Width:  |  Height:  |  Size: 51 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 102 KiB

After

Width:  |  Height:  |  Size: 102 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 83 KiB

After

Width:  |  Height:  |  Size: 83 KiB

View File

@ -81,7 +81,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>

View File

@ -81,7 +81,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a> <a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>

View File

@ -43,7 +43,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a> <a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>

View File

@ -81,7 +81,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>
@ -229,22 +229,23 @@
<small>Source: <a href='https://gitlab.com/msberends/AMR/blob/master/NEWS.md'><code>NEWS.md</code></a></small> <small>Source: <a href='https://gitlab.com/msberends/AMR/blob/master/NEWS.md'><code>NEWS.md</code></a></small>
</div> </div>
<div id="amr-1209010" class="section level1"> <div id="amr-1209011" class="section level1">
<h1 class="page-header" data-toc-text="1.2.0.9010"> <h1 class="page-header" data-toc-text="1.2.0.9011">
<a href="#amr-1209010" class="anchor"></a>AMR 1.2.0.9010<small> Unreleased </small> <a href="#amr-1209011" class="anchor"></a>AMR 1.2.0.9011<small> Unreleased </small>
</h1> </h1>
<div id="last-updated-17-jun-2020" class="section level2"> <div id="last-updated-22-jun-2020" class="section level2">
<h2 class="hasAnchor"> <h2 class="hasAnchor">
<a href="#last-updated-17-jun-2020" class="anchor"></a><small>Last updated: 17-Jun-2020</small> <a href="#last-updated-22-jun-2020" class="anchor"></a><small>Last updated: 22-Jun-2020</small>
</h2> </h2>
<div id="new" class="section level3"> <div id="new" class="section level3">
<h3 class="hasAnchor"> <h3 class="hasAnchor">
<a href="#new" class="anchor"></a>New</h3> <a href="#new" class="anchor"></a>New</h3>
<ul> <ul>
<li> <li>
<p><a href="https://tidyselect.r-lib.org/reference/language.html">Tidyverse selections</a>, that help to select the columns of antibiotics that are of a specific antibiotic class, without the need to define the columns or antibiotic abbreviations. They can be used in any function that allows Tidyverse selections, like <code><a href="https://dplyr.tidyverse.org/reference/select.html">dplyr::select()</a></code> and <code><a href="https://tidyr.tidyverse.org/reference/pivot_longer.html">tidyr::pivot_longer()</a></code>:</p> <p><a href="https://tidyselect.r-lib.org/reference/language.html">Tidyverse selections</a> for antibiotic classes, that help to select the columns of antibiotics that are of a specific antibiotic class, without the need to define the columns or antibiotic abbreviations. They can be used in any function that allows Tidyverse selections, like <code><a href="https://dplyr.tidyverse.org/reference/select.html">dplyr::select()</a></code> and <code><a href="https://tidyr.tidyverse.org/reference/pivot_longer.html">tidyr::pivot_longer()</a></code>:</p>
<div class="sourceCode" id="cb1"><pre class="r"><span class="fu"><a href="https://rdrr.io/r/base/library.html">library</a></span>(<span class="no">dplyr</span>) <div class="sourceCode" id="cb1"><pre class="r"><span class="fu"><a href="https://rdrr.io/r/base/library.html">library</a></span>(<span class="no">dplyr</span>)
<span class="co"># Columns 'IPM' and 'MEM' are in the example_isolates data set</span>
<span class="no">example_isolates</span> <span class="kw">%&gt;%</span> <span class="no">example_isolates</span> <span class="kw">%&gt;%</span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(<span class="fu"><a href="../reference/antibiotic_class_selectors.html">carbapenems</a></span>()) <span class="fu"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(<span class="fu"><a href="../reference/antibiotic_class_selectors.html">carbapenems</a></span>())
<span class="co">#&gt; Selecting carbapenems: `IPM` (imipenem), `MEM` (meropenem)</span> <span class="co">#&gt; Selecting carbapenems: `IPM` (imipenem), `MEM` (meropenem)</span>
@ -258,6 +259,10 @@
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(<span class="fu"><a href="../reference/antibiotic_class_selectors.html">ab_class</a></span>(<span class="st">"mycobact"</span>)) <span class="fu"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(<span class="fu"><a href="../reference/antibiotic_class_selectors.html">ab_class</a></span>(<span class="st">"mycobact"</span>))
<span class="co">#&gt; Selecting antimycobacterials: `RIF` (rifampicin)</span></pre></div> <span class="co">#&gt; Selecting antimycobacterials: `RIF` (rifampicin)</span></pre></div>
</li> </li>
<li><p>Added <code><a href="../reference/mo_property.html">mo_domain()</a></code> as an alias to <code><a href="../reference/mo_property.html">mo_kingdom()</a></code></p></li>
<li><p>Added function <code><a href="../reference/filter_ab_class.html">filter_penicillins()</a></code> to filter isolates on a specific result in any column with a name in the antimicrobial penicillins class (more specific: ATC subgroup <em>Beta-lactam antibacterials, penicillins</em>)</p></li>
<li><p>Added official antimicrobial names to all <code><a href="../reference/filter_ab_class.html">filter_ab_class()</a></code> functions, such as <code><a href="../reference/filter_ab_class.html">filter_aminoglycosides()</a></code></p></li>
<li><p>Added antibiotics code “FOX1” for cefoxitin screening (abbreviation “cfsc”) to the <code>antibiotics</code> data set</p></li>
</ul> </ul>
</div> </div>
<div id="changed" class="section level3"> <div id="changed" class="section level3">
@ -268,13 +273,11 @@
<li>All <code>*_join_microorganisms()</code> functions and <code><a href="../reference/bug_drug_combinations.html">bug_drug_combinations()</a></code> now return the original data class (e.g. <code>tibble</code>s and <code>data.table</code>s)</li> <li>All <code>*_join_microorganisms()</code> functions and <code><a href="../reference/bug_drug_combinations.html">bug_drug_combinations()</a></code> now return the original data class (e.g. <code>tibble</code>s and <code>data.table</code>s)</li>
<li>Fixed a bug where <code><a href="../reference/as.ab.html">as.ab()</a></code> would return an error on invalid input values</li> <li>Fixed a bug where <code><a href="../reference/as.ab.html">as.ab()</a></code> would return an error on invalid input values</li>
<li>Fixed a bug for using grouped versions of <code><a href="../reference/proportion.html">rsi_df()</a></code>, <code><a href="../reference/proportion.html">proportion_df()</a></code> and <code><a href="../reference/count.html">count_df()</a></code>, and fixed a bug where not all different antimicrobial results were added as rows</li> <li>Fixed a bug for using grouped versions of <code><a href="../reference/proportion.html">rsi_df()</a></code>, <code><a href="../reference/proportion.html">proportion_df()</a></code> and <code><a href="../reference/count.html">count_df()</a></code>, and fixed a bug where not all different antimicrobial results were added as rows</li>
<li>Added function <code><a href="../reference/filter_ab_class.html">filter_penicillins()</a></code> to filter isolates on a specific result in any column with a name in the antimicrobial penicillins class (more specific: ATC subgroup <em>Beta-lactam antibacterials, penicillins</em>)</li>
<li>Added official antimicrobial names to all <code><a href="../reference/filter_ab_class.html">filter_ab_class()</a></code> functions, such as <code><a href="../reference/filter_ab_class.html">filter_aminoglycosides()</a></code>
</li>
<li>Added antibiotics code “FOX1” for cefoxitin screening (abbreviation “cfsc”) to the <code>antibiotics</code> data set</li>
<li>Improved auto-determination for columns of types <code>&lt;mo&gt;</code> and <code>&lt;Date&gt;</code> <li>Improved auto-determination for columns of types <code>&lt;mo&gt;</code> and <code>&lt;Date&gt;</code>
</li> </li>
<li>Fixed a bug in <code><a href="../reference/bug_drug_combinations.html">bug_drug_combinations()</a></code> for when only one antibiotic was in the input data</li> <li>Fixed a bug in <code><a href="../reference/bug_drug_combinations.html">bug_drug_combinations()</a></code> for when only one antibiotic was in the input data</li>
<li>Changed the summary for class <code>&lt;mo&gt;</code>, to highlight the %SI vs. %R</li>
<li>Improved error handling, giving more useful info when functions return an error</li>
</ul> </ul>
</div> </div>
</div> </div>

View File

@ -10,7 +10,7 @@ articles:
WHONET: WHONET.html WHONET: WHONET.html
benchmarks: benchmarks.html benchmarks: benchmarks.html
resistance_predict: resistance_predict.html resistance_predict: resistance_predict.html
last_built: 2020-06-17T19:33Z last_built: 2020-06-22T09:16Z
urls: urls:
reference: https://msberends.gitlab.io/AMR/reference reference: https://msberends.gitlab.io/AMR/reference
article: https://msberends.gitlab.io/AMR/articles article: https://msberends.gitlab.io/AMR/articles

View File

@ -82,7 +82,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9008</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>

View File

@ -82,7 +82,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9008</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>

View File

@ -82,7 +82,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9007</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>

View File

@ -81,7 +81,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>
@ -360,7 +360,7 @@
</tr><tr> </tr><tr>
<td> <td>
<p><code><a href="mo_property.html">mo_name()</a></code> <code><a href="mo_property.html">mo_fullname()</a></code> <code><a href="mo_property.html">mo_shortname()</a></code> <code><a href="mo_property.html">mo_subspecies()</a></code> <code><a href="mo_property.html">mo_species()</a></code> <code><a href="mo_property.html">mo_genus()</a></code> <code><a href="mo_property.html">mo_family()</a></code> <code><a href="mo_property.html">mo_order()</a></code> <code><a href="mo_property.html">mo_class()</a></code> <code><a href="mo_property.html">mo_phylum()</a></code> <code><a href="mo_property.html">mo_kingdom()</a></code> <code><a href="mo_property.html">mo_type()</a></code> <code><a href="mo_property.html">mo_gramstain()</a></code> <code><a href="mo_property.html">mo_snomed()</a></code> <code><a href="mo_property.html">mo_ref()</a></code> <code><a href="mo_property.html">mo_authors()</a></code> <code><a href="mo_property.html">mo_year()</a></code> <code><a href="mo_property.html">mo_rank()</a></code> <code><a href="mo_property.html">mo_taxonomy()</a></code> <code><a href="mo_property.html">mo_synonyms()</a></code> <code><a href="mo_property.html">mo_info()</a></code> <code><a href="mo_property.html">mo_url()</a></code> <code><a href="mo_property.html">mo_property()</a></code> </p> <p><code><a href="mo_property.html">mo_name()</a></code> <code><a href="mo_property.html">mo_fullname()</a></code> <code><a href="mo_property.html">mo_shortname()</a></code> <code><a href="mo_property.html">mo_subspecies()</a></code> <code><a href="mo_property.html">mo_species()</a></code> <code><a href="mo_property.html">mo_genus()</a></code> <code><a href="mo_property.html">mo_family()</a></code> <code><a href="mo_property.html">mo_order()</a></code> <code><a href="mo_property.html">mo_class()</a></code> <code><a href="mo_property.html">mo_phylum()</a></code> <code><a href="mo_property.html">mo_kingdom()</a></code> <code><a href="mo_property.html">mo_domain()</a></code> <code><a href="mo_property.html">mo_type()</a></code> <code><a href="mo_property.html">mo_gramstain()</a></code> <code><a href="mo_property.html">mo_snomed()</a></code> <code><a href="mo_property.html">mo_ref()</a></code> <code><a href="mo_property.html">mo_authors()</a></code> <code><a href="mo_property.html">mo_year()</a></code> <code><a href="mo_property.html">mo_rank()</a></code> <code><a href="mo_property.html">mo_taxonomy()</a></code> <code><a href="mo_property.html">mo_synonyms()</a></code> <code><a href="mo_property.html">mo_info()</a></code> <code><a href="mo_property.html">mo_url()</a></code> <code><a href="mo_property.html">mo_property()</a></code> </p>
</td> </td>
<td><p>Property of a microorganism</p></td> <td><p>Property of a microorganism</p></td>
</tr><tr> </tr><tr>

View File

@ -82,7 +82,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>

View File

@ -84,7 +84,7 @@ This page contains a section for every lifecycle (with text borrowed from the af
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9008</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>

View File

@ -82,7 +82,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>
@ -257,6 +257,8 @@
<span class='fu'>mo_kingdom</span>(<span class='no'>x</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='no'>...</span>) <span class='fu'>mo_kingdom</span>(<span class='no'>x</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='no'>...</span>)
<span class='fu'>mo_domain</span>(<span class='no'>x</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='no'>...</span>)
<span class='fu'>mo_type</span>(<span class='no'>x</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='no'>...</span>) <span class='fu'>mo_type</span>(<span class='no'>x</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='no'>...</span>)
<span class='fu'>mo_gramstain</span>(<span class='no'>x</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='no'>...</span>) <span class='fu'>mo_gramstain</span>(<span class='no'>x</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='no'>...</span>)
@ -319,14 +321,15 @@
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2> <h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p>All functions will return the most recently known taxonomic property according to the Catalogue of Life, except for <code>mo_ref()</code>, <code>mo_authors()</code> and <code>mo_year()</code>. This leads to the following results:</p><ul> <p>All functions will return the most recently known taxonomic property according to the Catalogue of Life, except for <code>mo_ref()</code>, <code>mo_authors()</code> and <code>mo_year()</code>. Please refer to this example, knowing that <em>Escherichia blattae</em> was renamed to <em>Shimwellia blattae</em> in 2010:</p><ul>
<li><p><code>mo_name("Chlamydia psittaci")</code> will return <code>"Chlamydophila psittaci"</code> (with a warning about the renaming)</p></li> <li><p><code>mo_name("Escherichia blattae")</code> will return <code>"Shimwellia blattae"</code> (with a message about the renaming)</p></li>
<li><p><code>mo_ref("Chlamydia psittaci")</code> will return <code>"Page, 1968"</code> (with a warning about the renaming)</p></li> <li><p><code>mo_ref("Escherichia blattae")</code> will return <code>"Burgess et al., 1973"</code> (with a message about the renaming)</p></li>
<li><p><code>mo_ref("Chlamydophila psittaci")</code> will return <code>"Everett et al., 1999"</code> (without a warning)</p></li> <li><p><code>mo_ref("Shimwellia blattae")</code> will return <code>"Priest et al., 2010"</code> (without a message)</p></li>
</ul> </ul>
<p>The short name - <code>mo_shortname()</code> - almost always returns the first character of the genus and the full species, like <em>"E. coli"</em>. Exceptions are abbreviations of staphylococci and beta-haemolytic streptococci, like <em>"CoNS"</em> (Coagulase-Negative Staphylococci) and <em>"GBS"</em> (Group B Streptococci).</p> <p>The short name - <code>mo_shortname()</code> - almost always returns the first character of the genus and the full species, like <code>"E. coli"</code>. Exceptions are abbreviations of staphylococci (like <em>"CoNS"</em>, Coagulase-Negative Staphylococci) and beta-haemolytic streptococci (like <em>"GBS"</em>, Group B Streptococci). Please bear in mind that e.g. <em>E. coli</em> could mean <em>Escherichia coli</em> (kingdom of Bacteria) as well as <em>Entamoeba coli</em> (kingdom of Protozoa). Returning to the full name will be done using <code><a href='as.mo.html'>as.mo()</a></code> internally, giving priority to bacteria and human pathogens, i.e. <code>"E. coli"</code> will be considered <em>Escherichia coli</em>. In other words, <code>mo_fullname(mo_shortname("Entamoeba coli"))</code> returns <code>"Escherichia coli"</code>.</p>
<p>The Gram stain - <code>mo_gramstain()</code> - will be determined on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002) who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value <code>NA</code>.</p> <p>Since the top-level of the taxonomy is sometimes referred to as 'kingdom' and sometimes as 'domain', the functions <code>mo_kingdom()</code> and <code>mo_domain()</code> return the exact same results.</p>
<p>The Gram stain - <code>mo_gramstain()</code> - will be determined based on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002, <a href='https://pubmed.ncbi.nlm.nih.gov/11837318'>PMID 11837318</a>), who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value <code>NA</code>.</p>
<p>All output will be <a href='translate.html'>translate</a>d where possible.</p> <p>All output will be <a href='translate.html'>translate</a>d where possible.</p>
<p>The function <code>mo_url()</code> will return the direct URL to the online database entry, which also shows the scientific reference of the concerned species.</p> <p>The function <code>mo_url()</code> will return the direct URL to the online database entry, which also shows the scientific reference of the concerned species.</p>
<h2 class="hasAnchor" id="stable-lifecycle"><a class="anchor" href="#stable-lifecycle"></a>Stable lifecycle</h2> <h2 class="hasAnchor" id="stable-lifecycle"><a class="anchor" href="#stable-lifecycle"></a>Stable lifecycle</h2>

View File

@ -83,7 +83,7 @@ resistance() should be used to calculate resistance, susceptibility() should be
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9008</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.2.0.9011</span>
</span> </span>
</div> </div>

View File

@ -13,6 +13,7 @@
\alias{mo_class} \alias{mo_class}
\alias{mo_phylum} \alias{mo_phylum}
\alias{mo_kingdom} \alias{mo_kingdom}
\alias{mo_domain}
\alias{mo_type} \alias{mo_type}
\alias{mo_gramstain} \alias{mo_gramstain}
\alias{mo_snomed} \alias{mo_snomed}
@ -48,6 +49,8 @@ mo_phylum(x, language = get_locale(), ...)
mo_kingdom(x, language = get_locale(), ...) mo_kingdom(x, language = get_locale(), ...)
mo_domain(x, language = get_locale(), ...)
mo_type(x, language = get_locale(), ...) mo_type(x, language = get_locale(), ...)
mo_gramstain(x, language = get_locale(), ...) mo_gramstain(x, language = get_locale(), ...)
@ -96,16 +99,18 @@ mo_property(x, property = "fullname", language = get_locale(), ...)
Use these functions to return a specific property of a microorganism. All input values will be evaluated internally with \code{\link[=as.mo]{as.mo()}}, which makes it possible to use microbial abbreviations, codes and names as input. Please see \emph{Examples}. Use these functions to return a specific property of a microorganism. All input values will be evaluated internally with \code{\link[=as.mo]{as.mo()}}, which makes it possible to use microbial abbreviations, codes and names as input. Please see \emph{Examples}.
} }
\details{ \details{
All functions will return the most recently known taxonomic property according to the Catalogue of Life, except for \code{\link[=mo_ref]{mo_ref()}}, \code{\link[=mo_authors]{mo_authors()}} and \code{\link[=mo_year]{mo_year()}}. This leads to the following results: All functions will return the most recently known taxonomic property according to the Catalogue of Life, except for \code{\link[=mo_ref]{mo_ref()}}, \code{\link[=mo_authors]{mo_authors()}} and \code{\link[=mo_year]{mo_year()}}. Please refer to this example, knowing that \emph{Escherichia blattae} was renamed to \emph{Shimwellia blattae} in 2010:
\itemize{ \itemize{
\item \code{mo_name("Chlamydia psittaci")} will return \code{"Chlamydophila psittaci"} (with a warning about the renaming) \item \code{mo_name("Escherichia blattae")} will return \code{"Shimwellia blattae"} (with a message about the renaming)
\item \code{mo_ref("Chlamydia psittaci")} will return \code{"Page, 1968"} (with a warning about the renaming) \item \code{mo_ref("Escherichia blattae")} will return \code{"Burgess et al., 1973"} (with a message about the renaming)
\item \code{mo_ref("Chlamydophila psittaci")} will return \code{"Everett et al., 1999"} (without a warning) \item \code{mo_ref("Shimwellia blattae")} will return \code{"Priest et al., 2010"} (without a message)
} }
The short name - \code{\link[=mo_shortname]{mo_shortname()}} - almost always returns the first character of the genus and the full species, like \emph{"E. coli"}. Exceptions are abbreviations of staphylococci and beta-haemolytic streptococci, like \emph{"CoNS"} (Coagulase-Negative Staphylococci) and \emph{"GBS"} (Group B Streptococci). The short name - \code{\link[=mo_shortname]{mo_shortname()}} - almost always returns the first character of the genus and the full species, like \code{"E. coli"}. Exceptions are abbreviations of staphylococci (like \emph{"CoNS"}, Coagulase-Negative Staphylococci) and beta-haemolytic streptococci (like \emph{"GBS"}, Group B Streptococci). Please bear in mind that e.g. \emph{E. coli} could mean \emph{Escherichia coli} (kingdom of Bacteria) as well as \emph{Entamoeba coli} (kingdom of Protozoa). Returning to the full name will be done using \code{\link[=as.mo]{as.mo()}} internally, giving priority to bacteria and human pathogens, i.e. \code{"E. coli"} will be considered \emph{Escherichia coli}. In other words, \code{mo_fullname(mo_shortname("Entamoeba coli"))} returns \code{"Escherichia coli"}.
The Gram stain - \code{\link[=mo_gramstain]{mo_gramstain()}} - will be determined on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002) who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value \code{NA}. Since the top-level of the taxonomy is sometimes referred to as 'kingdom' and sometimes as 'domain', the functions \code{\link[=mo_kingdom]{mo_kingdom()}} and \code{\link[=mo_domain]{mo_domain()}} return the exact same results.
The Gram stain - \code{\link[=mo_gramstain]{mo_gramstain()}} - will be determined based on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002, \href{https://pubmed.ncbi.nlm.nih.gov/11837318}{PMID 11837318}), who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value \code{NA}.
All output will be \link{translate}d where possible. All output will be \link{translate}d where possible.

View File

@ -26,6 +26,7 @@ test_that("mo_property works", {
skip_on_cran() skip_on_cran()
expect_equal(mo_kingdom("Escherichia coli"), "Bacteria") expect_equal(mo_kingdom("Escherichia coli"), "Bacteria")
expect_equal(mo_kingdom("Escherichia coli"), mo_domain("Escherichia coli"))
expect_equal(mo_phylum("Escherichia coli"), "Proteobacteria") expect_equal(mo_phylum("Escherichia coli"), "Proteobacteria")
expect_equal(mo_class("Escherichia coli"), "Gammaproteobacteria") expect_equal(mo_class("Escherichia coli"), "Gammaproteobacteria")
expect_equal(mo_order("Escherichia coli"), "Enterobacterales") expect_equal(mo_order("Escherichia coli"), "Enterobacterales")