mirror of
https://github.com/msberends/AMR.git
synced 2025-07-08 18:01:50 +02:00
(v1.4.0.9001) is_gram_positive(), is_gram_negative(), parameter hardening
This commit is contained in:
@ -329,6 +329,89 @@ create_ab_documentation <- function(ab) {
|
||||
out
|
||||
}
|
||||
|
||||
# a check for every single argument in all functions
|
||||
meet_criteria <- function(object,
|
||||
allow_class = NULL,
|
||||
has_length = NULL,
|
||||
looks_like = NULL,
|
||||
is_in = NULL,
|
||||
contains_column_class = NULL,
|
||||
allow_NULL = FALSE,
|
||||
allow_NA = FALSE,
|
||||
ignore.case = FALSE,
|
||||
.call_depth = 0) { # depth in calling
|
||||
|
||||
obj_name <- deparse(substitute(object))
|
||||
call_depth <- -2 - abs(.call_depth)
|
||||
|
||||
if (is.null(object)) {
|
||||
stop_if(allow_NULL == FALSE, "argument `", obj_name, "` must not be NULL", call = call_depth)
|
||||
return(invisible())
|
||||
}
|
||||
if (is.null(dim(object)) && length(object) == 1 && is.na(object)) {
|
||||
stop_if(allow_NA == FALSE, "argument `", obj_name, "` must not be NA", call = call_depth)
|
||||
return(invisible())
|
||||
}
|
||||
|
||||
vector_or <- function(v, quotes) {
|
||||
if (length(v) == 1) {
|
||||
return(paste0(ifelse(quotes, '"', ""), v, ifelse(quotes, '"', "")))
|
||||
}
|
||||
# all commas except for last item, so will become '"val1", "val2", "val3" or "val4"'
|
||||
paste0(paste0(ifelse(quotes, '"', ""), v[seq_len(length(v) - 1)], ifelse(quotes, '"', ""), collapse = ", "),
|
||||
" or ", paste0(ifelse(quotes, '"', ""), v[length(v)], ifelse(quotes, '"', "")))
|
||||
}
|
||||
|
||||
if (!is.null(allow_class)) {
|
||||
stop_ifnot(inherits(object, allow_class), "argument `", obj_name,
|
||||
"` must ", # ifelse(allow_NULL, "be NULL or must ", ""),
|
||||
"be of class ", vector_or(allow_class, quotes = TRUE),
|
||||
", not \"", paste(class(object), collapse = "/"), "\"",
|
||||
call = call_depth)
|
||||
# check data.frames for data
|
||||
if (inherits(object, "data.frame")) {
|
||||
stop_if(any(dim(object) == 0),
|
||||
"the data provided in argument `", obj_name,
|
||||
"` must contain rows and columns (current dimensions: ",
|
||||
paste(dim(object), collapse = " x "), ")",
|
||||
call = call_depth)
|
||||
}
|
||||
}
|
||||
if (!is.null(has_length)) {
|
||||
stop_ifnot(length(object) %in% has_length, "argument `", obj_name,
|
||||
"` must ", # ifelse(allow_NULL, "be NULL or must ", ""),
|
||||
"be of length ", vector_or(has_length, quotes = FALSE),
|
||||
", not ", length(object),
|
||||
call = call_depth)
|
||||
}
|
||||
if (!is.null(looks_like)) {
|
||||
stop_ifnot(object %like% looks_like, "argument `", obj_name,
|
||||
"` must ", # ifelse(allow_NULL, "be NULL or must ", ""),
|
||||
"resemble the regular expression \"", looks_like, "\"",
|
||||
call = call_depth)
|
||||
}
|
||||
if (!is.null(is_in)) {
|
||||
if (ignore.case == TRUE) {
|
||||
object <- tolower(object)
|
||||
is_in <- tolower(is_in)
|
||||
}
|
||||
stop_ifnot(all(object %in% is_in, na.rm = TRUE), "argument `", obj_name,
|
||||
"` must be ",
|
||||
ifelse(!is.null(has_length) && length(has_length) == 1 && has_length == 1, "one of: ", ""),
|
||||
vector_or(is_in, quotes = TRUE),
|
||||
", not ", paste0("\"", object, "\"", collapse = "/"), "",
|
||||
call = call_depth)
|
||||
}
|
||||
if (!is.null(contains_column_class)) {
|
||||
stop_ifnot(any(sapply(object, function(col, columns_class = contains_column_class) inherits(col, columns_class)), na.rm = TRUE),
|
||||
"the data provided in argument `", obj_name,
|
||||
"` must contain at least one column of class <", contains_column_class, ">. ",
|
||||
"See ?as.", contains_column_class, ".",
|
||||
call = call_depth)
|
||||
}
|
||||
return(invisible())
|
||||
}
|
||||
|
||||
has_colour <- function() {
|
||||
# this is a base R version of crayon::has_color
|
||||
enabled <- getOption("crayon.enabled")
|
||||
|
3
R/ab.R
3
R/ab.R
@ -82,6 +82,9 @@
|
||||
#' ab_name("J01FA01") # "Erythromycin"
|
||||
#' ab_name("eryt") # "Erythromycin"
|
||||
as.ab <- function(x, flag_multiple_results = TRUE, info = TRUE, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(flag_multiple_results, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(info, allow_class = "logical", has_length = 1)
|
||||
|
||||
check_dataset_integrity()
|
||||
|
||||
|
@ -54,7 +54,7 @@
|
||||
#'
|
||||
#' # get bug/drug combinations for only macrolides in Gram-positives:
|
||||
#' example_isolates %>%
|
||||
#' filter(mo_gramstain(mo) %like% "pos") %>%
|
||||
#' filter(mo %>% is_gram_positive()) %>%
|
||||
#' select(mo, macrolides()) %>%
|
||||
#' bug_drug_combinations() %>%
|
||||
#' format()
|
||||
@ -148,9 +148,12 @@ tetracyclines <- function() {
|
||||
}
|
||||
|
||||
ab_selector <- function(ab_class, function_name) {
|
||||
meet_criteria(ab_class, allow_class = "character", has_length = 1, .call_depth = 1)
|
||||
meet_criteria(function_name, allow_class = "character", has_length = 1, .call_depth = 1)
|
||||
|
||||
peek_vars_tidyselect <- import_fn("peek_vars", "tidyselect")
|
||||
vars_vct <- peek_vars_tidyselect(fn = function_name)
|
||||
vars_df <- data.frame(as.list(vars_vct))[0, , drop = FALSE]
|
||||
vars_df <- data.frame(as.list(vars_vct))[1, , drop = FALSE]
|
||||
colnames(vars_df) <- vars_vct
|
||||
ab_in_data <- get_column_abx(vars_df, info = FALSE)
|
||||
|
||||
|
@ -92,12 +92,17 @@ ab_from_text <- function(text,
|
||||
translate_ab = FALSE,
|
||||
thorough_search = NULL,
|
||||
...) {
|
||||
|
||||
if (missing(type)) {
|
||||
type <- type[1L]
|
||||
}
|
||||
|
||||
meet_criteria(text)
|
||||
meet_criteria(type, allow_class = "character", has_length = 1)
|
||||
meet_criteria(collapse, has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(translate_ab, allow_NULL = FALSE) # get_translate_ab() will be more informative about what's allowed
|
||||
meet_criteria(thorough_search, allow_class = "logical", has_length = 1, allow_NULL = TRUE)
|
||||
|
||||
type <- tolower(trimws(type))
|
||||
stop_if(length(type) != 1, "`type` must be of length 1")
|
||||
|
||||
text <- tolower(as.character(text))
|
||||
text_split_all <- strsplit(text, "[ ;.,:\\|]")
|
||||
|
@ -89,6 +89,10 @@
|
||||
#' ab_atc("cephthriaxone")
|
||||
#' ab_atc("seephthriaaksone")
|
||||
ab_name <- function(x, language = get_locale(), tolower = FALSE, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(tolower, allow_class = "logical", has_length = 1)
|
||||
|
||||
x <- translate_AMR(ab_validate(x = x, property = "name", ...), language = language)
|
||||
if (tolower == TRUE) {
|
||||
# use perl to only transform the first character
|
||||
@ -102,18 +106,21 @@ ab_name <- function(x, language = get_locale(), tolower = FALSE, ...) {
|
||||
#' @aliases ATC
|
||||
#' @export
|
||||
ab_atc <- function(x, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
ab_validate(x = x, property = "atc", ...)
|
||||
}
|
||||
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_cid <- function(x, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
ab_validate(x = x, property = "cid", ...)
|
||||
}
|
||||
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_synonyms <- function(x, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
syns <- ab_validate(x = x, property = "synonyms", ...)
|
||||
names(syns) <- x
|
||||
if (length(syns) == 1) {
|
||||
@ -126,30 +133,38 @@ ab_synonyms <- function(x, ...) {
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_tradenames <- function(x, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
ab_synonyms(x, ...)
|
||||
}
|
||||
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_group <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
translate_AMR(ab_validate(x = x, property = "group", ...), language = language)
|
||||
}
|
||||
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_atc_group1 <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
translate_AMR(ab_validate(x = x, property = "atc_group1", ...), language = language)
|
||||
}
|
||||
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_atc_group2 <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
translate_AMR(ab_validate(x = x, property = "atc_group2", ...), language = language)
|
||||
}
|
||||
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_loinc <- function(x, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
loincs <- ab_validate(x = x, property = "loinc", ...)
|
||||
names(loincs) <- x
|
||||
if (length(loincs) == 1) {
|
||||
@ -162,7 +177,10 @@ ab_loinc <- function(x, ...) {
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_ddd <- function(x, administration = "oral", units = FALSE, ...) {
|
||||
stop_ifnot(administration %in% c("oral", "iv"), "`administration` must be 'oral' or 'iv'")
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(administration, is_in = c("oral", "iv"), has_length = 1)
|
||||
meet_criteria(units, allow_class = "logical", has_length = 1)
|
||||
|
||||
ddd_prop <- administration
|
||||
if (units == TRUE) {
|
||||
ddd_prop <- paste0(ddd_prop, "_units")
|
||||
@ -175,6 +193,9 @@ ab_ddd <- function(x, administration = "oral", units = FALSE, ...) {
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_info <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
x <- as.ab(x, ...)
|
||||
list(ab = as.character(x),
|
||||
atc = ab_atc(x),
|
||||
@ -194,6 +215,9 @@ ab_info <- function(x, language = get_locale(), ...) {
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_url <- function(x, open = FALSE, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(open, allow_class = "logical", has_length = 1)
|
||||
|
||||
ab <- as.ab(x = x, ... = ...)
|
||||
u <- paste0("https://www.whocc.no/atc_ddd_index/?code=", ab_atc(ab), "&showdescription=no")
|
||||
u[is.na(ab_atc(ab))] <- NA_character_
|
||||
@ -218,10 +242,9 @@ ab_url <- function(x, open = FALSE, ...) {
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_property <- function(x, property = "name", language = get_locale(), ...) {
|
||||
stop_if(length(property) != 1L, "'property' must be of length 1.")
|
||||
stop_ifnot(property %in% colnames(antibiotics),
|
||||
"invalid property: '", property, "' - use a column name of the `antibiotics` data set")
|
||||
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(property, is_in = colnames(antibiotics), has_length = 1)
|
||||
meet_criteria(language, is_in = c(LANGUAGES_SUPPORTED, ""), has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
translate_AMR(ab_validate(x = x, property = property, ...), language = language)
|
||||
}
|
||||
|
||||
|
39
R/age.R
39
R/age.R
@ -28,9 +28,11 @@
|
||||
#' Calculates age in years based on a reference date, which is the sytem date at default.
|
||||
#' @inheritSection lifecycle Stable lifecycle
|
||||
#' @param x date(s), will be coerced with [as.POSIXlt()]
|
||||
#' @param reference reference date(s) (defaults to today), will be coerced with [as.POSIXlt()] and cannot be lower than `x`
|
||||
#' @param reference reference date(s) (defaults to today), will be coerced with [as.POSIXlt()]
|
||||
#' @param exact a logical to indicate whether age calculation should be exact, i.e. with decimals. It divides the number of days of [year-to-date](https://en.wikipedia.org/wiki/Year-to-date) (YTD) of `x` by the number of days in the year of `reference` (either 365 or 366).
|
||||
#' @param na.rm a logical to indicate whether missing values should be removed
|
||||
#' @param ... parameters passed on to [as.POSIXlt()], such as `origin`
|
||||
#' @details Ages below 0 will be returned as `NA` with a warning. Ages above 120 will only give a warning.
|
||||
#' @return An [integer] (no decimals) if `exact = FALSE`, a [double] (with decimals) otherwise
|
||||
#' @seealso To split ages into groups, use the [age_groups()] function.
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
@ -44,13 +46,18 @@
|
||||
#' df$age_exact <- age(df$birth_date, exact = TRUE)
|
||||
#'
|
||||
#' df
|
||||
age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE) {
|
||||
age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "Date", "POSIXt"))
|
||||
meet_criteria(reference, allow_class = c("character", "Date", "POSIXt"))
|
||||
meet_criteria(exact, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(na.rm, allow_class = "logical", has_length = 1)
|
||||
|
||||
if (length(x) != length(reference)) {
|
||||
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))
|
||||
}
|
||||
x <- as.POSIXlt(x)
|
||||
reference <- as.POSIXlt(reference)
|
||||
x <- as.POSIXlt(x, ...)
|
||||
reference <- as.POSIXlt(reference, ...)
|
||||
|
||||
# from https://stackoverflow.com/a/25450756/4575331
|
||||
years_gap <- reference$year - x$year
|
||||
@ -98,13 +105,13 @@ age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE) {
|
||||
#' @param na.rm a [logical] to indicate whether missing values should be removed
|
||||
#' @details To split ages, the input for the `split_at` parameter can be:
|
||||
#'
|
||||
#' * A numeric vector. A vector of e.g. `c(10, 20)` will split on 0-9, 10-19 and 20+. A value of only `50` will split on 0-49 and 50+.
|
||||
#' * A numeric vector. A value of e.g. `c(10, 20)` will split `x` on 0-9, 10-19 and 20+. A value of only `50` will split `x` on 0-49 and 50+.
|
||||
#' The default is to split on young children (0-11), youth (12-24), young adults (25-54), middle-aged adults (55-74) and elderly (75+).
|
||||
#' * A character:
|
||||
#' - `"children"` or `"kids"`, equivalent of: `c(0, 1, 2, 4, 6, 13, 18)`. This will split on 0, 1, 2-3, 4-5, 6-12, 13-17 and 18+.
|
||||
#' - `"elderly"` or `"seniors"`, equivalent of: `c(65, 75, 85)`. This will split on 0-64, 65-74, 75-84, 85+.
|
||||
#' - `"fives"`, equivalent of: `1:20 * 5`. This will split on 0-4, 5-9, 10-14, ..., 90-94, 95-99, 100+.
|
||||
#' - `"tens"`, equivalent of: `1:10 * 10`. This will split on 0-9, 10-19, 20-29, ..., 80-89, 90-99, 100+.
|
||||
#' - `"fives"`, equivalent of: `1:20 * 5`. This will split on 0-4, 5-9, ..., 95-99, 100+.
|
||||
#' - `"tens"`, equivalent of: `1:10 * 10`. This will split on 0-9, 10-19, ..., 90-99, 100+.
|
||||
#' @return Ordered [factor]
|
||||
#' @seealso To determine ages, based on one or more reference dates, use the [age()] function.
|
||||
#' @export
|
||||
@ -127,12 +134,11 @@ age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE) {
|
||||
#' age_groups(ages, split_at = "fives")
|
||||
#'
|
||||
#' # split specifically for children
|
||||
#' age_groups(ages, "children")
|
||||
#' # same:
|
||||
#' age_groups(ages, c(1, 2, 4, 6, 13, 17))
|
||||
#' age_groups(ages, "children")
|
||||
#'
|
||||
#' \donttest{
|
||||
#' # resistance of ciprofloxacine per age group
|
||||
#' # resistance of ciprofloxacin per age group
|
||||
#' library(dplyr)
|
||||
#' example_isolates %>%
|
||||
#' filter_first_isolate() %>%
|
||||
@ -142,7 +148,10 @@ age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE) {
|
||||
#' ggplot_rsi(x = "age_group", minimum = 0)
|
||||
#' }
|
||||
age_groups <- function(x, split_at = c(12, 25, 55, 75), na.rm = FALSE) {
|
||||
stop_ifnot(is.numeric(x), "`x` must be numeric, not ", paste0(class(x), collapse = "/"))
|
||||
meet_criteria(x, allow_class = c("numeric", "integer"))
|
||||
meet_criteria(split_at, allow_class = c("numeric", "integer", "character"))
|
||||
meet_criteria(na.rm, allow_class = "logical", has_length = 1)
|
||||
|
||||
if (any(x < 0, na.rm = TRUE)) {
|
||||
x[x < 0] <- NA
|
||||
warning("NAs introduced for ages below 0.")
|
||||
@ -169,17 +178,17 @@ age_groups <- function(x, split_at = c(12, 25, 55, 75), na.rm = FALSE) {
|
||||
|
||||
# turn input values to 'split_at' indices
|
||||
y <- x
|
||||
labs <- split_at
|
||||
lbls <- split_at
|
||||
for (i in seq_len(length(split_at))) {
|
||||
y[x >= split_at[i]] <- i
|
||||
# create labels
|
||||
labs[i - 1] <- paste0(unique(c(split_at[i - 1], split_at[i] - 1)), collapse = "-")
|
||||
lbls[i - 1] <- paste0(unique(c(split_at[i - 1], split_at[i] - 1)), collapse = "-")
|
||||
}
|
||||
|
||||
# last category
|
||||
labs[length(labs)] <- paste0(split_at[length(split_at)], "+")
|
||||
lbls[length(lbls)] <- paste0(split_at[length(split_at)], "+")
|
||||
|
||||
agegroups <- factor(labs[y], levels = labs, ordered = TRUE)
|
||||
agegroups <- factor(lbls[y], levels = lbls, ordered = TRUE)
|
||||
|
||||
if (isTRUE(na.rm)) {
|
||||
agegroups <- agegroups[!is.na(agegroups)]
|
||||
|
@ -78,6 +78,11 @@ atc_online_property <- function(atc_code,
|
||||
administration = "O",
|
||||
url = "https://www.whocc.no/atc_ddd_index/?code=%s&showdescription=no",
|
||||
url_vet = "https://www.whocc.no/atcvet/atcvet_index/?code=%s&showdescription=no") {
|
||||
meet_criteria(atc_code, allow_class = "character")
|
||||
meet_criteria(property, allow_class = "character", has_length = 1, is_in = c("ATC", "Name", "DDD", "U", "Adm.R", "Note", "groups"), ignore.case = TRUE)
|
||||
meet_criteria(administration, allow_class = "character", has_length = 1)
|
||||
meet_criteria(url, allow_class = "character", has_length = 1, looks_like = "https?://")
|
||||
meet_criteria(url_vet, allow_class = "character", has_length = 1, looks_like = "https?://")
|
||||
|
||||
has_internet <- import_fn("has_internet", "curl")
|
||||
html_attr <- import_fn("html_attr", "rvest")
|
||||
@ -99,24 +104,12 @@ atc_online_property <- function(atc_code,
|
||||
return(rep(NA, length(atc_code)))
|
||||
}
|
||||
|
||||
stop_if(length(property) != 1L, "`property` must be of length 1")
|
||||
stop_if(length(administration) != 1L, "`administration` must be of length 1")
|
||||
|
||||
# also allow unit as property
|
||||
if (property %like% "unit") {
|
||||
property <- "U"
|
||||
}
|
||||
|
||||
# validation of properties
|
||||
valid_properties <- c("ATC", "Name", "DDD", "U", "Adm.R", "Note", "groups")
|
||||
valid_properties.bak <- valid_properties
|
||||
|
||||
property <- tolower(property)
|
||||
valid_properties <- tolower(valid_properties)
|
||||
|
||||
stop_ifnot(property %in% valid_properties,
|
||||
"Invalid `property`, use one of ", paste(valid_properties.bak, collapse = ", "))
|
||||
|
||||
if (property == "ddd") {
|
||||
returnvalue <- rep(NA_real_, length(atc_code))
|
||||
} else if (property == "groups") {
|
||||
@ -199,11 +192,13 @@ atc_online_property <- function(atc_code,
|
||||
#' @rdname atc_online
|
||||
#' @export
|
||||
atc_online_groups <- function(atc_code, ...) {
|
||||
meet_criteria(atc_code, allow_class = "character")
|
||||
atc_online_property(atc_code = atc_code, property = "groups", ...)
|
||||
}
|
||||
|
||||
#' @rdname atc_online
|
||||
#' @export
|
||||
atc_online_ddd <- function(atc_code, ...) {
|
||||
meet_criteria(atc_code, allow_class = "character")
|
||||
atc_online_property(atc_code = atc_code, property = "ddd", ...)
|
||||
}
|
||||
|
@ -43,7 +43,9 @@
|
||||
#' availability()
|
||||
#' }
|
||||
availability <- function(tbl, width = NULL) {
|
||||
stop_ifnot(is.data.frame(tbl), "`tbl` must be a data.frame")
|
||||
meet_criteria(tbl, allow_class = "data.frame")
|
||||
meet_criteria(width, allow_class = "numeric", allow_NULL = TRUE)
|
||||
|
||||
x <- sapply(tbl, function(x) {
|
||||
1 - sum(is.na(x)) / length(x)
|
||||
})
|
||||
|
@ -31,8 +31,8 @@
|
||||
#' @param combine_IR logical to indicate whether values R and I should be summed
|
||||
#' @param add_ab_group logical to indicate where the group of the antimicrobials must be included as a first column
|
||||
#' @param remove_intrinsic_resistant logical to indicate that rows and columns with 100% resistance for all tested antimicrobials must be removed from the table
|
||||
#' @param FUN the function to call on the `mo` column to transform the microorganism IDs, defaults to [mo_shortname()]
|
||||
#' @param translate_ab a character of length 1 containing column names of the [antibiotics] data set
|
||||
#' @param FUN function to call on the `mo` column to transform the microorganism IDs, defaults to [mo_shortname()]
|
||||
#' @param translate_ab character of length 1 containing column names of the [antibiotics] data set
|
||||
#' @param ... arguments passed on to `FUN`
|
||||
#' @inheritParams rsi_df
|
||||
#' @inheritParams base::formatC
|
||||
@ -61,9 +61,10 @@ bug_drug_combinations <- function(x,
|
||||
col_mo = NULL,
|
||||
FUN = mo_shortname,
|
||||
...) {
|
||||
stop_ifnot(is.data.frame(x), "`x` must be a data frame")
|
||||
stop_ifnot(any(sapply(x, is.rsi), na.rm = TRUE), "No columns with class <rsi> found. See ?as.rsi.")
|
||||
|
||||
meet_criteria(x, allow_class = "data.frame", contains_column_class = "rsi")
|
||||
meet_criteria(col_mo, allow_class = "character", is_in = colnames(x), has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(FUN, allow_class = "function", has_length = 1)
|
||||
|
||||
# try to find columns based on type
|
||||
# -- mo
|
||||
if (is.null(col_mo)) {
|
||||
@ -121,6 +122,17 @@ format.bug_drug_combinations <- function(x,
|
||||
decimal.mark = getOption("OutDec"),
|
||||
big.mark = ifelse(decimal.mark == ",", ".", ","),
|
||||
...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(translate_ab, allow_class = c("character", "logical"), has_length = 1, allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(combine_SI, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(combine_IR, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(add_ab_group, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(remove_intrinsic_resistant, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(decimal.mark, allow_class = "character", has_length = 1)
|
||||
meet_criteria(big.mark, allow_class = "character", has_length = 1)
|
||||
|
||||
x <- as.data.frame(x, stringsAsFactors = FALSE)
|
||||
x <- subset(x, total >= minimum)
|
||||
|
||||
|
@ -189,7 +189,6 @@ count_df <- function(data,
|
||||
language = get_locale(),
|
||||
combine_SI = TRUE,
|
||||
combine_IR = FALSE) {
|
||||
|
||||
rsi_calc_df(type = "count",
|
||||
data = data,
|
||||
translate_ab = translate_ab,
|
||||
|
@ -30,4 +30,18 @@
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @keywords internal
|
||||
#' @name AMR-deprecated
|
||||
# @export
|
||||
#' @export
|
||||
p_symbol <- function(p, emptychar = " ") {
|
||||
.Deprecated(package = "AMR")
|
||||
|
||||
p <- as.double(p)
|
||||
s <- rep(NA_character_, length(p))
|
||||
|
||||
s[p <= 1] <- emptychar
|
||||
s[p <= 0.100] <- "."
|
||||
s[p <= 0.050] <- "*"
|
||||
s[p <= 0.010] <- "**"
|
||||
s[p <= 0.001] <- "***"
|
||||
|
||||
s
|
||||
}
|
||||
|
6
R/disk.R
6
R/disk.R
@ -58,6 +58,9 @@
|
||||
#' as.rsi(df)
|
||||
#' }
|
||||
as.disk <- function(x, na.rm = FALSE) {
|
||||
meet_criteria(x, allow_class = c("disk", "character", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(na.rm, allow_class = "logical", has_length = 1)
|
||||
|
||||
if (!is.disk(x)) {
|
||||
x <- x %pm>% unlist()
|
||||
if (na.rm == TRUE) {
|
||||
@ -109,6 +112,9 @@ as.disk <- function(x, na.rm = FALSE) {
|
||||
}
|
||||
|
||||
all_valid_disks <- function(x) {
|
||||
if (!inherits(x, c("disk", "character", "numeric", "integer"))) {
|
||||
return(FALSE)
|
||||
}
|
||||
x_disk <- suppressWarnings(as.disk(x[!is.na(x)]))
|
||||
!any(is.na(x_disk)) & !all(is.na(x))
|
||||
}
|
||||
|
@ -134,6 +134,13 @@ eucast_rules <- function(x,
|
||||
version_breakpoints = 10.0,
|
||||
version_expertrules = 3.2,
|
||||
...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(col_mo, allow_class = "character", has_length = 1, is_in = colnames(x), allow_NULL = TRUE)
|
||||
meet_criteria(info, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(rules, allow_class = "character", has_length = c(1, 2, 3, 4), is_in = c("breakpoints", "expert", "other", "all"))
|
||||
meet_criteria(verbose, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(version_breakpoints, allow_class = "numeric", has_length = 1)
|
||||
meet_criteria(version_expertrules, allow_class = "numeric", has_length = 1)
|
||||
|
||||
x_deparsed <- deparse(substitute(x))
|
||||
if (length(x_deparsed) > 1 || !all(x_deparsed %like% "[a-z]+")) {
|
||||
@ -172,18 +179,12 @@ eucast_rules <- function(x,
|
||||
}
|
||||
}
|
||||
|
||||
stop_ifnot(is.data.frame(x), "`x` must be a data frame")
|
||||
|
||||
# try to find columns based on type
|
||||
# -- mo
|
||||
if (is.null(col_mo)) {
|
||||
col_mo <- search_type_in_df(x = x, type = "mo", info = info)
|
||||
}
|
||||
stop_if(is.null(col_mo), "`col_mo` must be set")
|
||||
stop_ifnot(col_mo %in% colnames(x), "column '", col_mo, "' (`col_mo`) not found")
|
||||
|
||||
stop_ifnot(all(rules %in% c("breakpoints", "expert", "other", "all")),
|
||||
'`rules` must be one or more of: "breakpoints", "expert", "other", "all".')
|
||||
|
||||
decimal.mark <- getOption("OutDec")
|
||||
big.mark <- ifelse(decimal.mark != ",", ",", ".")
|
||||
@ -576,7 +577,7 @@ eucast_rules <- function(x,
|
||||
# big speed gain! only analyse unique rows:
|
||||
pm_distinct(`.rowid`, .keep_all = TRUE) %pm>%
|
||||
as.data.frame(stringsAsFactors = FALSE)
|
||||
x[, col_mo] <- as.mo(x[, col_mo, drop = TRUE])
|
||||
x[, col_mo] <- as.mo(as.character(x[, col_mo, drop = TRUE]))
|
||||
x <- x %pm>%
|
||||
left_join_microorganisms(by = col_mo, suffix = c("_oldcols", ""))
|
||||
x$gramstain <- mo_gramstain(x[, col_mo, drop = TRUE], language = NULL)
|
||||
|
@ -80,16 +80,22 @@ filter_ab_class <- function(x,
|
||||
result = NULL,
|
||||
scope = "any",
|
||||
...) {
|
||||
|
||||
.call_depth <- list(...)$`.call_depth`
|
||||
if (is.null(.call_depth)) {
|
||||
.call_depth <- 0
|
||||
}
|
||||
meet_criteria(x, allow_class = "data.frame", .call_depth = .call_depth)
|
||||
meet_criteria(ab_class, allow_class = "character", has_length = 1, .call_depth = .call_depth)
|
||||
meet_criteria(result, allow_class = "character", has_length = c(1, 2, 3), allow_NULL = TRUE, .call_depth = .call_depth)
|
||||
meet_criteria(scope, allow_class = "character", has_length = 1, is_in = c("all", "any"), .call_depth = .call_depth)
|
||||
|
||||
check_dataset_integrity()
|
||||
stop_ifnot(is.data.frame(x), "`x` must be a data frame")
|
||||
|
||||
|
||||
# save to return later
|
||||
x_class <- class(x)
|
||||
x.bak <- x
|
||||
x <- as.data.frame(x, stringsAsFactors = FALSE)
|
||||
|
||||
scope <- scope[1L]
|
||||
if (is.null(result)) {
|
||||
result <- c("S", "I", "R")
|
||||
}
|
||||
@ -174,6 +180,7 @@ filter_aminoglycosides <- function(x,
|
||||
ab_class = "aminoglycoside",
|
||||
result = result,
|
||||
scope = scope,
|
||||
.call_depth = 1,
|
||||
...)
|
||||
}
|
||||
|
||||
@ -187,6 +194,7 @@ filter_carbapenems <- function(x,
|
||||
ab_class = "carbapenem",
|
||||
result = result,
|
||||
scope = scope,
|
||||
.call_depth = 1,
|
||||
...)
|
||||
}
|
||||
|
||||
@ -200,6 +208,7 @@ filter_cephalosporins <- function(x,
|
||||
ab_class = "cephalosporin",
|
||||
result = result,
|
||||
scope = scope,
|
||||
.call_depth = 1,
|
||||
...)
|
||||
}
|
||||
|
||||
@ -213,6 +222,7 @@ filter_1st_cephalosporins <- function(x,
|
||||
ab_class = "cephalosporins (1st gen.)",
|
||||
result = result,
|
||||
scope = scope,
|
||||
.call_depth = 1,
|
||||
...)
|
||||
}
|
||||
|
||||
@ -226,6 +236,7 @@ filter_2nd_cephalosporins <- function(x,
|
||||
ab_class = "cephalosporins (2nd gen.)",
|
||||
result = result,
|
||||
scope = scope,
|
||||
.call_depth = 1,
|
||||
...)
|
||||
}
|
||||
|
||||
@ -239,6 +250,7 @@ filter_3rd_cephalosporins <- function(x,
|
||||
ab_class = "cephalosporins (3rd gen.)",
|
||||
result = result,
|
||||
scope = scope,
|
||||
.call_depth = 1,
|
||||
...)
|
||||
}
|
||||
|
||||
@ -252,6 +264,7 @@ filter_4th_cephalosporins <- function(x,
|
||||
ab_class = "cephalosporins (4th gen.)",
|
||||
result = result,
|
||||
scope = scope,
|
||||
.call_depth = 1,
|
||||
...)
|
||||
}
|
||||
|
||||
@ -265,6 +278,7 @@ filter_5th_cephalosporins <- function(x,
|
||||
ab_class = "cephalosporins (5th gen.)",
|
||||
result = result,
|
||||
scope = scope,
|
||||
.call_depth = 1,
|
||||
...)
|
||||
}
|
||||
|
||||
@ -278,6 +292,7 @@ filter_fluoroquinolones <- function(x,
|
||||
ab_class = "fluoroquinolone",
|
||||
result = result,
|
||||
scope = scope,
|
||||
.call_depth = 1,
|
||||
...)
|
||||
}
|
||||
|
||||
@ -291,6 +306,7 @@ filter_glycopeptides <- function(x,
|
||||
ab_class = "glycopeptide",
|
||||
result = result,
|
||||
scope = scope,
|
||||
.call_depth = 1,
|
||||
...)
|
||||
}
|
||||
|
||||
@ -304,6 +320,7 @@ filter_macrolides <- function(x,
|
||||
ab_class = "macrolide",
|
||||
result = result,
|
||||
scope = scope,
|
||||
.call_depth = 1,
|
||||
...)
|
||||
}
|
||||
|
||||
@ -317,6 +334,7 @@ filter_penicillins <- function(x,
|
||||
ab_class = "penicillin",
|
||||
result = result,
|
||||
scope = scope,
|
||||
.call_depth = 1,
|
||||
...)
|
||||
}
|
||||
|
||||
@ -330,6 +348,7 @@ filter_tetracyclines <- function(x,
|
||||
ab_class = "tetracycline",
|
||||
result = result,
|
||||
scope = scope,
|
||||
.call_depth = 1,
|
||||
...)
|
||||
}
|
||||
|
||||
|
@ -139,6 +139,23 @@ first_isolate <- function(x,
|
||||
info = interactive(),
|
||||
include_unknown = FALSE,
|
||||
...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(col_date, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
meet_criteria(col_patient_id, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
meet_criteria(col_mo, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
meet_criteria(col_testcode, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
meet_criteria(col_specimen, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
meet_criteria(col_icu, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
meet_criteria(col_keyantibiotics, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
meet_criteria(episode_days, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(testcodes_exclude, allow_class = "character", allow_NULL = TRUE)
|
||||
meet_criteria(icu_exclude, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(specimen_group, allow_class = "character", has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(type, allow_class = "character", has_length = 1)
|
||||
meet_criteria(ignore_I, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(points_threshold, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(info, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(include_unknown, allow_class = "logical", has_length = 1)
|
||||
|
||||
dots <- unlist(list(...))
|
||||
if (length(dots) != 0) {
|
||||
@ -352,20 +369,20 @@ first_isolate <- function(x,
|
||||
info = info)
|
||||
# with key antibiotics
|
||||
x$newvar_first_isolate <- pm_if_else(x$newvar_row_index_sorted >= row.start &
|
||||
x$newvar_row_index_sorted <= row.end &
|
||||
x$newvar_genus_species != "" &
|
||||
(x$other_pat_or_mo | x$more_than_episode_ago | x$other_key_ab),
|
||||
TRUE,
|
||||
FALSE)
|
||||
x$newvar_row_index_sorted <= row.end &
|
||||
x$newvar_genus_species != "" &
|
||||
(x$other_pat_or_mo | x$more_than_episode_ago | x$other_key_ab),
|
||||
TRUE,
|
||||
FALSE)
|
||||
|
||||
} else {
|
||||
# no key antibiotics
|
||||
x$newvar_first_isolate <- pm_if_else(x$newvar_row_index_sorted >= row.start &
|
||||
x$newvar_row_index_sorted <= row.end &
|
||||
x$newvar_genus_species != "" &
|
||||
(x$other_pat_or_mo | x$more_than_episode_ago),
|
||||
TRUE,
|
||||
FALSE)
|
||||
x$newvar_row_index_sorted <= row.end &
|
||||
x$newvar_genus_species != "" &
|
||||
(x$other_pat_or_mo | x$more_than_episode_ago),
|
||||
TRUE,
|
||||
FALSE)
|
||||
}
|
||||
|
||||
# first one as TRUE
|
||||
@ -442,6 +459,10 @@ filter_first_isolate <- function(x,
|
||||
col_patient_id = NULL,
|
||||
col_mo = NULL,
|
||||
...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(col_date, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
meet_criteria(col_patient_id, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
meet_criteria(col_mo, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
subset(x, first_isolate(x = x,
|
||||
col_date = col_date,
|
||||
col_patient_id = col_patient_id,
|
||||
@ -457,6 +478,11 @@ filter_first_weighted_isolate <- function(x,
|
||||
col_mo = NULL,
|
||||
col_keyantibiotics = NULL,
|
||||
...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(col_date, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
meet_criteria(col_patient_id, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
meet_criteria(col_mo, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
meet_criteria(col_keyantibiotics, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x))
|
||||
y <- x
|
||||
if (is.null(col_keyantibiotics)) {
|
||||
# first try to look for it
|
||||
|
@ -53,9 +53,10 @@
|
||||
#' As per their GPL-2 licence that demands documentation of code changes, the changes made based on the source code were:
|
||||
#' 1. Rewritten code to remove the dependency on packages `plyr`, `scales` and `grid`
|
||||
#' 2. Parametrised more options, like arrow and ellipse settings
|
||||
#' 3. Added total amount of explained variance as a caption in the plot
|
||||
#' 4. Cleaned all syntax based on the `lintr` package and added integrity checks
|
||||
#' 5. Updated documentation
|
||||
#' 3. Hardened all input possibilities by defining the exact type of user input for every parameter
|
||||
#' 4. Added total amount of explained variance as a caption in the plot
|
||||
#' 5. Cleaned all syntax based on the `lintr` package, fixed grammatical errors and added integrity checks
|
||||
#' 6. Updated documentation
|
||||
#' @details The colours for labels and points can be changed by adding another scale layer for colour, like `scale_colour_viridis_d()` or `scale_colour_brewer()`.
|
||||
#' @rdname ggplot_pca
|
||||
#' @export
|
||||
@ -85,7 +86,7 @@
|
||||
#' }
|
||||
ggplot_pca <- function(x,
|
||||
choices = 1:2,
|
||||
scale = TRUE,
|
||||
scale = 1,
|
||||
pc.biplot = TRUE,
|
||||
labels = NULL,
|
||||
labels_textsize = 3,
|
||||
@ -107,22 +108,27 @@ ggplot_pca <- function(x,
|
||||
...) {
|
||||
|
||||
stop_ifnot_installed("ggplot2")
|
||||
stop_ifnot(length(choices) == 2, "`choices` must be of length 2")
|
||||
stop_ifnot(is.logical(arrows), "`arrows` must be TRUE or FALSE")
|
||||
stop_ifnot(is.logical(arrows_textangled), "`arrows_textangled` must be TRUE or FALSE")
|
||||
stop_ifnot(is.logical(ellipse), "`ellipse` must be TRUE or FALSE")
|
||||
stop_ifnot(is.logical(pc.biplot), "`pc.biplot` must be TRUE or FALSE")
|
||||
stop_ifnot(is.logical(scale), "`scale` must be TRUE or FALSE")
|
||||
stop_ifnot(is.numeric(arrows_alpha), "`arrows_alpha` must be numeric")
|
||||
stop_ifnot(is.numeric(arrows_size), "`arrows_size` must be numeric")
|
||||
stop_ifnot(is.numeric(arrows_textsize), "`arrows_textsize` must be numeric")
|
||||
stop_ifnot(is.numeric(base_textsize), "`base_textsize` must be numeric")
|
||||
stop_ifnot(is.numeric(choices), "`choices` must be numeric")
|
||||
stop_ifnot(is.numeric(ellipse_alpha), "`ellipse_alpha` must be numeric")
|
||||
stop_ifnot(is.numeric(ellipse_prob), "`ellipse_prob` must be numeric")
|
||||
stop_ifnot(is.numeric(ellipse_size), "`ellipse_size` must be numeric")
|
||||
stop_ifnot(is.numeric(labels_text_placement), "`labels_text_placement` must be numeric")
|
||||
stop_ifnot(is.numeric(labels_textsize), "`labels_textsize` must be numeric")
|
||||
meet_criteria(x, allow_class = c("prcomp", "princomp", "PCA", "lda"))
|
||||
meet_criteria(choices, allow_class = c("numeric", "integer"), has_length = 2)
|
||||
meet_criteria(scale, allow_class = c("numeric", "integer", "logical"), has_length = 1)
|
||||
meet_criteria(pc.biplot, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(labels, allow_class = "character", allow_NULL = TRUE)
|
||||
meet_criteria(labels_textsize, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(labels_text_placement, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(groups, allow_class = "character", allow_NULL = TRUE)
|
||||
meet_criteria(ellipse, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(ellipse_prob, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(ellipse_size, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(ellipse_alpha, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(points_size, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(points_alpha, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(arrows, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(arrows_colour, allow_class = "character", has_length = 1)
|
||||
meet_criteria(arrows_size, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(arrows_textsize, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(arrows_textangled, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(arrows_alpha, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(base_textsize, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
|
||||
calculations <- pca_calculations(pca_model = x,
|
||||
groups = groups,
|
||||
@ -302,7 +308,7 @@ pca_calculations <- function(pca_model,
|
||||
v <- pca_model$scaling
|
||||
d.total <- sum(d ^ 2)
|
||||
} else {
|
||||
stop("Expected a object of class prcomp, princomp, PCA, or lda")
|
||||
stop("Expected an object of class prcomp, princomp, PCA, or lda")
|
||||
}
|
||||
|
||||
# Scores
|
||||
|
@ -171,10 +171,29 @@ ggplot_rsi <- function(data,
|
||||
...) {
|
||||
|
||||
stop_ifnot_installed("ggplot2")
|
||||
|
||||
x <- x[1]
|
||||
facet <- facet[1]
|
||||
|
||||
meet_criteria(data, allow_class = "data.frame", contains_column_class = "rsi")
|
||||
meet_criteria(position, allow_class = "character", has_length = 1, is_in = c("fill", "stack", "dodge"), allow_NULL = TRUE)
|
||||
meet_criteria(x, allow_class = "character", has_length = 1)
|
||||
meet_criteria(fill, allow_class = "character", has_length = 1)
|
||||
meet_criteria(facet, allow_class = "character", has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(breaks, allow_class = c("numeric", "integer"))
|
||||
meet_criteria(limits, allow_class = c("numeric", "integer"), has_length = 2, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(translate_ab, allow_class = c("character", "logical"), has_length = 1, allow_NA = TRUE)
|
||||
meet_criteria(combine_SI, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(combine_IR, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(nrow, allow_class = c("numeric", "integer"), has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(colours, allow_class = "character")
|
||||
meet_criteria(datalabels, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(datalabels.size, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(datalabels.colour, allow_class = "character", has_length = 1)
|
||||
meet_criteria(title, allow_class = "character", has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(subtitle, allow_class = "character", has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(caption, allow_class = "character", has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(x.title, allow_class = "character", has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(y.title, allow_class = "character", has_length = 1, allow_NULL = TRUE)
|
||||
|
||||
# we work with aes_string later on
|
||||
x_deparse <- deparse(substitute(x))
|
||||
if (x_deparse != "x") {
|
||||
@ -256,7 +275,15 @@ geom_rsi <- function(position = NULL,
|
||||
...) {
|
||||
|
||||
stop_ifnot_installed("ggplot2")
|
||||
stop_if(is.data.frame(position), "`position` is invalid. Did you accidentally use '%pm>%' instead of '+'?")
|
||||
stop_if(is.data.frame(position), "`position` is invalid. Did you accidentally use '%>%' instead of '+'?")
|
||||
meet_criteria(position, allow_class = "character", has_length = 1, is_in = c("fill", "stack", "dodge"), allow_NULL = TRUE)
|
||||
meet_criteria(x, allow_class = "character", has_length = 1)
|
||||
meet_criteria(fill, allow_class = "character", has_length = 1)
|
||||
meet_criteria(translate_ab, allow_class = c("character", "logical"), has_length = 1, allow_NA = TRUE)
|
||||
meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(combine_SI, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(combine_IR, allow_class = "logical", has_length = 1)
|
||||
|
||||
y <- "value"
|
||||
if (missing(position) | is.null(position)) {
|
||||
@ -300,10 +327,10 @@ geom_rsi <- function(position = NULL,
|
||||
#' @rdname ggplot_rsi
|
||||
#' @export
|
||||
facet_rsi <- function(facet = c("interpretation", "antibiotic"), nrow = NULL) {
|
||||
|
||||
stop_ifnot_installed("ggplot2")
|
||||
|
||||
facet <- facet[1]
|
||||
stop_ifnot_installed("ggplot2")
|
||||
meet_criteria(facet, allow_class = "character", has_length = 1)
|
||||
meet_criteria(nrow, allow_class = c("numeric", "integer"), has_length = 1, allow_NULL = TRUE)
|
||||
|
||||
# we work with aes_string later on
|
||||
facet_deparse <- deparse(substitute(facet))
|
||||
@ -327,6 +354,8 @@ facet_rsi <- function(facet = c("interpretation", "antibiotic"), nrow = NULL) {
|
||||
#' @export
|
||||
scale_y_percent <- function(breaks = seq(0, 1, 0.1), limits = NULL) {
|
||||
stop_ifnot_installed("ggplot2")
|
||||
meet_criteria(breaks, allow_class = c("numeric", "integer"))
|
||||
meet_criteria(limits, allow_class = c("numeric", "integer"), has_length = 2, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
if (all(breaks[breaks != 0] > 1)) {
|
||||
breaks <- breaks / 100
|
||||
@ -344,6 +373,8 @@ scale_rsi_colours <- function(colours = c(S = "#61a8ff",
|
||||
IR = "#ff6961",
|
||||
R = "#ff6961")) {
|
||||
stop_ifnot_installed("ggplot2")
|
||||
meet_criteria(colours, allow_class = "character")
|
||||
|
||||
# previous colour: palette = "RdYlGn"
|
||||
# previous colours: values = c("#b22222", "#ae9c20", "#7cfc00")
|
||||
|
||||
@ -383,6 +414,16 @@ labels_rsi_count <- function(position = NULL,
|
||||
datalabels.size = 3,
|
||||
datalabels.colour = "gray15") {
|
||||
stop_ifnot_installed("ggplot2")
|
||||
meet_criteria(position, allow_class = "character", has_length = 1, is_in = c("fill", "stack", "dodge"), allow_NULL = TRUE)
|
||||
meet_criteria(x, allow_class = "character", has_length = 1)
|
||||
meet_criteria(translate_ab, allow_class = c("character", "logical"), has_length = 1, allow_NA = TRUE)
|
||||
meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(combine_SI, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(combine_IR, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(datalabels.size, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(datalabels.colour, allow_class = "character", has_length = 1)
|
||||
|
||||
if (is.null(position)) {
|
||||
position <- "fill"
|
||||
}
|
||||
|
@ -30,7 +30,7 @@
|
||||
#' @param x a [data.frame]
|
||||
#' @param search_string a text to search `x` for, will be checked with [as.ab()] if this value is not a column in `x`
|
||||
#' @param verbose a logical to indicate whether additional info should be printed
|
||||
#' @details You can look for an antibiotic (trade) name or abbreviation and it will search `x` and the [antibiotics] data set for any column containing a name or code of that antibiotic. **Longer columns names take precendence over shorter column names.**
|
||||
#' @details You can look for an antibiotic (trade) name or abbreviation and it will search `x` and the [antibiotics] data set for any column containing a name or code of that antibiotic. **Longer columns names take precedence over shorter column names.**
|
||||
#' @return A column name of `x`, or `NULL` when no result is found.
|
||||
#' @export
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
@ -63,16 +63,13 @@
|
||||
#' guess_ab_col(df, "ampicillin")
|
||||
#' # [1] "AMP_ED20"
|
||||
guess_ab_col <- function(x = NULL, search_string = NULL, verbose = FALSE) {
|
||||
meet_criteria(x, allow_class = "data.frame", allow_NULL = TRUE)
|
||||
meet_criteria(search_string, allow_class = "character", has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(verbose, allow_class = "logical", has_length = 1)
|
||||
|
||||
if (is.null(x) & is.null(search_string)) {
|
||||
return(as.name("guess_ab_col"))
|
||||
}
|
||||
stop_ifnot(is.data.frame(x), "`x` must be a data.frame")
|
||||
|
||||
if (length(search_string) > 1) {
|
||||
warning("argument 'search_string' has length > 1 and only the first element will be used")
|
||||
search_string <- search_string[1]
|
||||
}
|
||||
search_string <- as.character(search_string)
|
||||
|
||||
if (search_string %in% colnames(x)) {
|
||||
ab_result <- search_string
|
||||
@ -116,6 +113,11 @@ get_column_abx <- function(x,
|
||||
verbose = FALSE,
|
||||
info = TRUE,
|
||||
...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(soft_dependencies, allow_class = "character", allow_NULL = TRUE)
|
||||
meet_criteria(hard_dependencies, allow_class = "character", allow_NULL = TRUE)
|
||||
meet_criteria(verbose, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(info, allow_class = "logical", has_length = 1)
|
||||
|
||||
if (info == TRUE) {
|
||||
message(font_blue("NOTE: Auto-guessing columns suitable for analysis"), appendLF = FALSE)
|
||||
|
@ -61,8 +61,12 @@
|
||||
#' }
|
||||
#' }
|
||||
inner_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) {
|
||||
meet_criteria(x, allow_class = c("data.frame", "character"))
|
||||
meet_criteria(by, allow_class = "character", allow_NULL = TRUE)
|
||||
meet_criteria(suffix, allow_class = "character", has_length = 2)
|
||||
|
||||
check_dataset_integrity()
|
||||
check_groups_before_join(x, "inner_join_microorganisms")
|
||||
x <- check_groups_before_join(x, "inner_join_microorganisms")
|
||||
checked <- joins_check_df(x, by)
|
||||
x_class <- get_prejoined_class(x)
|
||||
x <- checked$x
|
||||
@ -88,8 +92,12 @@ inner_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) {
|
||||
#' @rdname join
|
||||
#' @export
|
||||
left_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) {
|
||||
meet_criteria(x, allow_class = c("data.frame", "character"))
|
||||
meet_criteria(by, allow_class = "character", allow_NULL = TRUE)
|
||||
meet_criteria(suffix, allow_class = "character", has_length = 2)
|
||||
|
||||
check_dataset_integrity()
|
||||
check_groups_before_join(x, "left_join_microorganisms")
|
||||
x <- check_groups_before_join(x, "left_join_microorganisms")
|
||||
checked <- joins_check_df(x, by)
|
||||
x_class <- get_prejoined_class(x)
|
||||
x <- checked$x
|
||||
@ -115,8 +123,12 @@ left_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) {
|
||||
#' @rdname join
|
||||
#' @export
|
||||
right_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) {
|
||||
meet_criteria(x, allow_class = c("data.frame", "character"))
|
||||
meet_criteria(by, allow_class = "character", allow_NULL = TRUE)
|
||||
meet_criteria(suffix, allow_class = "character", has_length = 2)
|
||||
|
||||
check_dataset_integrity()
|
||||
check_groups_before_join(x, "right_join_microorganisms")
|
||||
x <- check_groups_before_join(x, "right_join_microorganisms")
|
||||
checked <- joins_check_df(x, by)
|
||||
x_class <- get_prejoined_class(x)
|
||||
x <- checked$x
|
||||
@ -142,8 +154,12 @@ right_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) {
|
||||
#' @rdname join
|
||||
#' @export
|
||||
full_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) {
|
||||
meet_criteria(x, allow_class = c("data.frame", "character"))
|
||||
meet_criteria(by, allow_class = "character", allow_NULL = TRUE)
|
||||
meet_criteria(suffix, allow_class = "character", has_length = 2)
|
||||
|
||||
check_dataset_integrity()
|
||||
check_groups_before_join(x, "full_join_microorganisms")
|
||||
x <- check_groups_before_join(x, "full_join_microorganisms")
|
||||
checked <- joins_check_df(x, by)
|
||||
x_class <- get_prejoined_class(x)
|
||||
x <- checked$x
|
||||
@ -169,8 +185,11 @@ full_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) {
|
||||
#' @rdname join
|
||||
#' @export
|
||||
semi_join_microorganisms <- function(x, by = NULL, ...) {
|
||||
meet_criteria(x, allow_class = c("data.frame", "character"))
|
||||
meet_criteria(by, allow_class = "character", allow_NULL = TRUE)
|
||||
|
||||
check_dataset_integrity()
|
||||
check_groups_before_join(x, "semi_join_microorganisms")
|
||||
x <- check_groups_before_join(x, "semi_join_microorganisms")
|
||||
x_class <- get_prejoined_class(x)
|
||||
checked <- joins_check_df(x, by)
|
||||
x <- checked$x
|
||||
@ -193,8 +212,11 @@ semi_join_microorganisms <- function(x, by = NULL, ...) {
|
||||
#' @rdname join
|
||||
#' @export
|
||||
anti_join_microorganisms <- function(x, by = NULL, ...) {
|
||||
meet_criteria(x, allow_class = c("data.frame", "character"))
|
||||
meet_criteria(by, allow_class = "character", allow_NULL = TRUE)
|
||||
|
||||
check_dataset_integrity()
|
||||
check_groups_before_join(x, "anti_join_microorganisms")
|
||||
x <- check_groups_before_join(x, "anti_join_microorganisms")
|
||||
checked <- joins_check_df(x, by)
|
||||
x_class <- get_prejoined_class(x)
|
||||
x <- checked$x
|
||||
@ -255,6 +277,10 @@ get_prejoined_class <- function(x) {
|
||||
|
||||
check_groups_before_join <- function(x, fn) {
|
||||
if (is.data.frame(x) && !is.null(attributes(x)$groups)) {
|
||||
warning("Groups are dropped, since the ", fn, "() function relies on merge() from base R, not on join() from dplyr.", call. = FALSE)
|
||||
x <- pm_ungroup(x)
|
||||
attr(x, "groups") <- NULL
|
||||
class(x) <- class(x)[!class(x) %like% "group"]
|
||||
warning("Groups are dropped, since the ", fn, "() function relies on merge() from base R if dplyr is not installed.", call. = FALSE)
|
||||
}
|
||||
x
|
||||
}
|
||||
|
@ -27,14 +27,14 @@
|
||||
#'
|
||||
#' These function can be used to determine first isolates (see [first_isolate()]). Using key antibiotics to determine first isolates is more reliable than without key antibiotics. These selected isolates will then be called first *weighted* isolates.
|
||||
#' @inheritSection lifecycle Stable lifecycle
|
||||
#' @param x table with antibiotics coloms, like `AMX` or `amox`
|
||||
#' @param y,z characters to compare
|
||||
#' @param x a data.frame with antibiotics columns, like `AMX` or `amox`
|
||||
#' @param y,z character vectors to compare
|
||||
#' @inheritParams first_isolate
|
||||
#' @param universal_1,universal_2,universal_3,universal_4,universal_5,universal_6 column names of **broad-spectrum** antibiotics, case-insensitive. At default, the columns containing these antibiotics will be guessed with [guess_ab_col()].
|
||||
#' @param GramPos_1,GramPos_2,GramPos_3,GramPos_4,GramPos_5,GramPos_6 column names of antibiotics for **Gram-positives**, case-insensitive. At default, the columns containing these antibiotics will be guessed with [guess_ab_col()].
|
||||
#' @param GramNeg_1,GramNeg_2,GramNeg_3,GramNeg_4,GramNeg_5,GramNeg_6 column names of antibiotics for **Gram-negatives**, case-insensitive. At default, the columns containing these antibiotics will be guessed with [guess_ab_col()].
|
||||
#' @param warnings give warning about missing antibiotic columns, they will anyway be ignored
|
||||
#' @param ... other parameters passed on to function
|
||||
#' @param universal_1,universal_2,universal_3,universal_4,universal_5,universal_6 column names of **broad-spectrum** antibiotics, case-insensitive. See details for which antibiotics will be used at default (which are guessed with [guess_ab_col()]).
|
||||
#' @param GramPos_1,GramPos_2,GramPos_3,GramPos_4,GramPos_5,GramPos_6 column names of antibiotics for **Gram-positives**, case-insensitive. See details for which antibiotics will be used at default (which are guessed with [guess_ab_col()]).
|
||||
#' @param GramNeg_1,GramNeg_2,GramNeg_3,GramNeg_4,GramNeg_5,GramNeg_6 column names of antibiotics for **Gram-negatives**, case-insensitive. See details for which antibiotics will be used at default (which are guessed with [guess_ab_col()]).
|
||||
#' @param warnings give a warning about missing antibiotic columns (they will be ignored)
|
||||
#' @param ... other parameters passed on to functions
|
||||
#' @details The function [key_antibiotics()] returns a character vector with 12 antibiotic results for every isolate. These isolates can then be compared using [key_antibiotics_equal()], to check if two isolates have generally the same antibiogram. Missing and invalid values are replaced with a dot (`"."`) by [key_antibiotics()] and ignored by [key_antibiotics_equal()].
|
||||
#'
|
||||
#' The [first_isolate()] function only uses this function on the same microbial species from the same patient. Using this, e.g. an MRSA will be included after a susceptible *S. aureus* (MSSA) is found within the same patient episode. Without key antibiotic comparison it would not. See [first_isolate()] for more info.
|
||||
@ -127,6 +127,27 @@ key_antibiotics <- function(x,
|
||||
GramNeg_6 = guess_ab_col(x, "meropenem"),
|
||||
warnings = TRUE,
|
||||
...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(col_mo, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(universal_1, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(universal_2, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(universal_3, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(universal_4, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(universal_5, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(universal_6, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(GramPos_1, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(GramPos_2, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(GramPos_3, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(GramPos_4, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(GramPos_5, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(GramPos_6, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(GramNeg_1, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(GramNeg_2, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(GramNeg_3, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(GramNeg_4, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(GramNeg_5, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(GramNeg_6, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(warnings, allow_class = "logical", has_length = 1)
|
||||
|
||||
dots <- unlist(list(...))
|
||||
if (length(dots) != 0) {
|
||||
@ -258,14 +279,20 @@ key_antibiotics_equal <- function(y,
|
||||
ignore_I = TRUE,
|
||||
points_threshold = 2,
|
||||
info = FALSE) {
|
||||
meet_criteria(y, allow_class = "character")
|
||||
meet_criteria(z, allow_class = "character")
|
||||
meet_criteria(type, allow_class = "character", has_length = c(1, 2))
|
||||
meet_criteria(ignore_I, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(points_threshold, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(info, allow_class = "logical", has_length = 1)
|
||||
|
||||
stop_ifnot(length(y) == length(z), "length of `y` and `z` must be equal")
|
||||
# y is active row, z is lag
|
||||
x <- y
|
||||
y <- z
|
||||
|
||||
type <- type[1]
|
||||
|
||||
stop_ifnot(length(x) == length(y), "length of `x` and `y` must be equal")
|
||||
|
||||
# only show progress bar on points or when at least 5000 isolates
|
||||
info_needed <- info == TRUE & (type == "points" | length(x) > 5000)
|
||||
|
||||
|
@ -35,6 +35,8 @@
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @export
|
||||
kurtosis <- function(x, na.rm = FALSE, excess = FALSE) {
|
||||
meet_criteria(na.rm, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(excess, allow_class = "logical", has_length = 1)
|
||||
UseMethod("kurtosis")
|
||||
}
|
||||
|
||||
@ -42,6 +44,8 @@ kurtosis <- function(x, na.rm = FALSE, excess = FALSE) {
|
||||
#' @rdname kurtosis
|
||||
#' @export
|
||||
kurtosis.default <- function(x, na.rm = FALSE, excess = FALSE) {
|
||||
meet_criteria(na.rm, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(excess, allow_class = "logical", has_length = 1)
|
||||
x <- as.vector(x)
|
||||
if (na.rm == TRUE) {
|
||||
x <- x[!is.na(x)]
|
||||
@ -56,6 +60,8 @@ kurtosis.default <- function(x, na.rm = FALSE, excess = FALSE) {
|
||||
#' @rdname kurtosis
|
||||
#' @export
|
||||
kurtosis.matrix <- function(x, na.rm = FALSE, excess = FALSE) {
|
||||
meet_criteria(na.rm, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(excess, allow_class = "logical", has_length = 1)
|
||||
apply(x, 2, kurtosis.default, na.rm = na.rm, excess = excess)
|
||||
}
|
||||
|
||||
@ -63,5 +69,7 @@ kurtosis.matrix <- function(x, na.rm = FALSE, excess = FALSE) {
|
||||
#' @rdname kurtosis
|
||||
#' @export
|
||||
kurtosis.data.frame <- function(x, na.rm = FALSE, excess = FALSE) {
|
||||
meet_criteria(na.rm, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(excess, allow_class = "logical", has_length = 1)
|
||||
sapply(x, kurtosis.default, na.rm = na.rm, excess = excess)
|
||||
}
|
||||
|
14
R/like.R
14
R/like.R
@ -68,6 +68,10 @@
|
||||
#' }
|
||||
#' }
|
||||
like <- function(x, pattern, ignore.case = TRUE) {
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
meet_criteria(pattern, allow_class = "character")
|
||||
meet_criteria(ignore.case, allow_class = "logical", has_length = 1)
|
||||
|
||||
# set to fixed if no regex found
|
||||
fixed <- !any(is_possibly_regex(pattern))
|
||||
if (ignore.case == TRUE) {
|
||||
@ -79,6 +83,10 @@ like <- function(x, pattern, ignore.case = TRUE) {
|
||||
if (length(pattern) > 1 & length(x) == 1) {
|
||||
x <- rep(x, length(pattern))
|
||||
}
|
||||
|
||||
if (all(is.na(x))) {
|
||||
return(rep(FALSE, length(x)))
|
||||
}
|
||||
|
||||
if (length(pattern) > 1) {
|
||||
res <- vector(length = length(pattern))
|
||||
@ -137,18 +145,24 @@ like <- function(x, pattern, ignore.case = TRUE) {
|
||||
#' @rdname like
|
||||
#' @export
|
||||
"%like%" <- function(x, pattern) {
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
meet_criteria(pattern, allow_class = "character")
|
||||
like(x, pattern, ignore.case = TRUE)
|
||||
}
|
||||
|
||||
#' @rdname like
|
||||
#' @export
|
||||
"%like_case%" <- function(x, pattern) {
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
meet_criteria(pattern, allow_class = "character")
|
||||
like(x, pattern, ignore.case = FALSE)
|
||||
}
|
||||
|
||||
# don't export his one, it's just for convenience in eucast_rules()
|
||||
# match all Klebsiella and Raoultella, but not K. aerogenes: fullname %like_perl% "^(Klebsiella(?! aerogenes)|Raoultella)"
|
||||
"%like_perl%" <- function(x, pattern) {
|
||||
meet_criteria(x)
|
||||
meet_criteria(pattern, allow_class = "character")
|
||||
grepl(x = tolower(x),
|
||||
pattern = tolower(pattern),
|
||||
perl = TRUE,
|
||||
|
24
R/mdro.R
24
R/mdro.R
@ -93,6 +93,13 @@ mdro <- function(x,
|
||||
combine_SI = TRUE,
|
||||
verbose = FALSE,
|
||||
...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(guideline, allow_class = "character", has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(col_mo, allow_class = "character", has_length = 1, is_in = colnames(x), allow_NULL = TRUE)
|
||||
meet_criteria(info, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(pct_required_classes, allow_class = "numeric", has_length = 1)
|
||||
meet_criteria(combine_SI, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(verbose, allow_class = "logical", has_length = 1)
|
||||
|
||||
check_dataset_integrity()
|
||||
|
||||
@ -128,9 +135,8 @@ mdro <- function(x,
|
||||
warning("Using `country` is deprecated, use `guideline` instead. Please see ?mdro.", call. = FALSE)
|
||||
guideline <- list(...)$country
|
||||
}
|
||||
stop_ifnot(length(guideline) == 1, "`guideline` must be of length 1")
|
||||
|
||||
guideline.bak <- guideline
|
||||
|
||||
guideline.bak <- guideline
|
||||
guideline <- tolower(gsub("[^a-zA-Z0-9.]+", "", guideline))
|
||||
if (is.null(guideline)) {
|
||||
# default to the paper by Magiorakos et al. (2012)
|
||||
@ -631,7 +637,7 @@ mdro <- function(x,
|
||||
}
|
||||
}
|
||||
|
||||
x[, col_mo] <- as.mo(x[, col_mo, drop = TRUE])
|
||||
x[, col_mo] <- as.mo(as.character(x[, col_mo, drop = TRUE]))
|
||||
# join to microorganisms data set
|
||||
x <- left_join_microorganisms(x, by = col_mo)
|
||||
x$MDRO <- ifelse(!is.na(x$genus), 1, NA_integer_)
|
||||
@ -1243,29 +1249,39 @@ mdro <- function(x,
|
||||
#' @rdname mdro
|
||||
#' @export
|
||||
brmo <- function(x, guideline = "BRMO", ...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(guideline, allow_class = "character", has_length = 1)
|
||||
mdro(x, guideline = "BRMO", ...)
|
||||
}
|
||||
|
||||
#' @rdname mdro
|
||||
#' @export
|
||||
mrgn <- function(x, guideline = "MRGN", ...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(guideline, allow_class = "character", has_length = 1)
|
||||
mdro(x = x, guideline = "MRGN", ...)
|
||||
}
|
||||
|
||||
#' @rdname mdro
|
||||
#' @export
|
||||
mdr_tb <- function(x, guideline = "TB", ...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(guideline, allow_class = "character", has_length = 1)
|
||||
mdro(x = x, guideline = "TB", ...)
|
||||
}
|
||||
|
||||
#' @rdname mdro
|
||||
#' @export
|
||||
mdr_cmi2012 <- function(x, guideline = "CMI2012", ...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(guideline, allow_class = "character", has_length = 1)
|
||||
mdro(x = x, guideline = "CMI2012", ...)
|
||||
}
|
||||
|
||||
#' @rdname mdro
|
||||
#' @export
|
||||
eucast_exceptional_phenotypes <- function(x, guideline = "EUCAST", ...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(guideline, allow_class = "character", has_length = 1)
|
||||
mdro(x = x, guideline = "EUCAST", ...)
|
||||
}
|
||||
|
16
R/mic.R
16
R/mic.R
@ -56,6 +56,9 @@
|
||||
#' plot(mic_data)
|
||||
#' barplot(mic_data)
|
||||
as.mic <- function(x, na.rm = FALSE) {
|
||||
meet_criteria(x, allow_class = c("mic", "character", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(na.rm, allow_class = "logical", has_length = 1)
|
||||
|
||||
if (is.mic(x)) {
|
||||
x
|
||||
} else {
|
||||
@ -134,6 +137,9 @@ as.mic <- function(x, na.rm = FALSE) {
|
||||
}
|
||||
|
||||
all_valid_mics <- function(x) {
|
||||
if (!inherits(x, c("mic", "character", "factor", "numeric", "integer"))) {
|
||||
return(FALSE)
|
||||
}
|
||||
x_mic <- tryCatch(suppressWarnings(as.mic(x[!is.na(x)])),
|
||||
error = function(e) NA)
|
||||
!any(is.na(x_mic)) & !all(is.na(x))
|
||||
@ -221,6 +227,11 @@ plot.mic <- function(x,
|
||||
xlab = "MIC value",
|
||||
axes = FALSE,
|
||||
...) {
|
||||
meet_criteria(main, allow_class = "character", has_length = 1)
|
||||
meet_criteria(ylab, allow_class = "character", has_length = 1)
|
||||
meet_criteria(xlab, allow_class = "character", has_length = 1)
|
||||
meet_criteria(axes, allow_class = "logical", has_length = 1)
|
||||
|
||||
barplot(table(droplevels.factor(x)),
|
||||
ylab = ylab,
|
||||
xlab = xlab,
|
||||
@ -240,6 +251,11 @@ barplot.mic <- function(height,
|
||||
xlab = "MIC value",
|
||||
axes = FALSE,
|
||||
...) {
|
||||
meet_criteria(main, allow_class = "character", has_length = 1)
|
||||
meet_criteria(ylab, allow_class = "character", has_length = 1)
|
||||
meet_criteria(xlab, allow_class = "character", has_length = 1)
|
||||
meet_criteria(axes, allow_class = "logical", has_length = 1)
|
||||
|
||||
barplot(table(droplevels.factor(height)),
|
||||
ylab = ylab,
|
||||
xlab = xlab,
|
||||
|
25
R/mo.R
25
R/mo.R
@ -158,6 +158,13 @@ as.mo <- function(x,
|
||||
ignore_pattern = getOption("AMR_ignore_pattern"),
|
||||
language = get_locale(),
|
||||
...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(Becker, allow_class = c("logical", "character"), has_length = 1)
|
||||
meet_criteria(Lancefield, allow_class = c("logical", "character"), has_length = 1)
|
||||
meet_criteria(allow_uncertain, allow_class = c("logical", "numeric", "integer"), has_length = 1)
|
||||
meet_criteria(reference_df, allow_class = "data.frame", allow_NULL = TRUE)
|
||||
meet_criteria(ignore_pattern, allow_class = "character", has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
check_dataset_integrity()
|
||||
|
||||
@ -268,6 +275,20 @@ exec_as.mo <- function(x,
|
||||
actual_uncertainty = 1,
|
||||
actual_input = NULL,
|
||||
language = get_locale()) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(Becker, allow_class = c("logical", "character"), has_length = 1)
|
||||
meet_criteria(Lancefield, allow_class = c("logical", "character"), has_length = 1)
|
||||
meet_criteria(allow_uncertain, allow_class = c("logical", "numeric", "integer"), has_length = 1)
|
||||
meet_criteria(reference_df, allow_class = "data.frame", allow_NULL = TRUE)
|
||||
meet_criteria(property, allow_class = "character", has_length = 1, is_in = colnames(microorganisms))
|
||||
meet_criteria(initial_search, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(dyslexia_mode, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(debug, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(ignore_pattern, allow_class = "character", has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(reference_data_to_use, allow_class = "data.frame")
|
||||
meet_criteria(actual_uncertainty, allow_class = "numeric", has_length = 1)
|
||||
meet_criteria(actual_input, allow_class = "character", allow_NULL = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
check_dataset_integrity()
|
||||
|
||||
@ -1607,8 +1628,8 @@ get_skimmers.mo <- function(column) {
|
||||
sfl(
|
||||
skim_type = "mo",
|
||||
unique_total = ~pm_n_distinct(., na.rm = TRUE),
|
||||
gram_negative = ~sum(mo_gramstain(stats::na.omit(.), language = NULL) == "Gram-negative", na.rm = TRUE),
|
||||
gram_positive = ~sum(mo_gramstain(stats::na.omit(.), language = NULL) == "Gram-positive", na.rm = TRUE),
|
||||
gram_negative = ~sum(is_gram_negative(stats::na.omit(.))),
|
||||
gram_positive = ~sum(is_gram_positive(stats::na.omit(.))),
|
||||
top_genus = ~names(sort(-table(mo_genus(stats::na.omit(.), language = NULL))))[1L],
|
||||
top_species = ~names(sort(-table(mo_name(stats::na.omit(.), language = NULL))))[1L]
|
||||
)
|
||||
|
@ -53,6 +53,9 @@
|
||||
#' mo_matching_score(x = "E. coli",
|
||||
#' n = c("Escherichia coli", "Entamoeba coli"))
|
||||
mo_matching_score <- function(x, n) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list"))
|
||||
meet_criteria(n, allow_class = "character")
|
||||
|
||||
x <- parse_and_convert(x)
|
||||
# no dots and other non-whitespace characters
|
||||
x <- gsub("[^a-zA-Z0-9 \\(\\)]+", "", x)
|
||||
|
@ -27,7 +27,7 @@
|
||||
#'
|
||||
#' Use these functions to return a specific property of a microorganism based on the latest accepted taxonomy. All input values will be evaluated internally with [as.mo()], which makes it possible to use microbial abbreviations, codes and names as input. Please see *Examples*.
|
||||
#' @inheritSection lifecycle Stable lifecycle
|
||||
#' @param x any (vector of) text that can be coerced to a valid microorganism code with [as.mo()]
|
||||
#' @param x any character (vector) that can be coerced to a valid microorganism code with [as.mo()]
|
||||
#' @param property one of the column names of the [microorganisms] data set or `"shortname"`
|
||||
#' @param language language of the returned text, defaults to system language (see [get_locale()]) and can be overwritten by setting the option `AMR_locale`, e.g. `options(AMR_locale = "de")`, see [translate]. Use `language = NULL` or `language = ""` to prevent translation.
|
||||
#' @param ... other parameters passed on to [as.mo()], such as 'allow_uncertain' and 'ignore_pattern'
|
||||
@ -41,7 +41,7 @@
|
||||
#'
|
||||
#' 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 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`.
|
||||
#' 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`. Functions [is_gram_negative()] and [is_gram_positive()] always return `TRUE` or `FALSE`, even for species outside the kingdom of Bacteria.
|
||||
#'
|
||||
#' All output will be [translate]d where possible.
|
||||
#'
|
||||
@ -146,6 +146,9 @@
|
||||
#' mo_info("E. coli")
|
||||
#' }
|
||||
mo_name <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
translate_AMR(mo_validate(x = x, property = "fullname", language = language, ...), language = language, only_unknown = FALSE)
|
||||
}
|
||||
|
||||
@ -156,6 +159,9 @@ mo_fullname <- mo_name
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_shortname <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
x.mo <- as.mo(x, language = language, ...)
|
||||
|
||||
metadata <- get_mo_failures_uncertainties_renamed()
|
||||
@ -186,48 +192,72 @@ mo_shortname <- function(x, language = get_locale(), ...) {
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_subspecies <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
translate_AMR(mo_validate(x = x, property = "subspecies", language = language, ...), language = language, only_unknown = TRUE)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_species <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
translate_AMR(mo_validate(x = x, property = "species", language = language, ...), language = language, only_unknown = TRUE)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_genus <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
translate_AMR(mo_validate(x = x, property = "genus", language = language, ...), language = language, only_unknown = TRUE)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_family <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
translate_AMR(mo_validate(x = x, property = "family", language = language, ...), language = language, only_unknown = TRUE)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_order <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
translate_AMR(mo_validate(x = x, property = "order", language = language, ...), language = language, only_unknown = TRUE)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_class <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
translate_AMR(mo_validate(x = x, property = "class", language = language, ...), language = language, only_unknown = TRUE)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_phylum <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
translate_AMR(mo_validate(x = x, property = "phylum", language = language, ...), language = language, only_unknown = TRUE)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_kingdom <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
translate_AMR(mo_validate(x = x, property = "kingdom", language = language, ...), language = language, only_unknown = TRUE)
|
||||
}
|
||||
|
||||
@ -238,12 +268,18 @@ mo_domain <- mo_kingdom
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_type <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
translate_AMR(mo_validate(x = x, property = "kingdom", language = language, ...), language = language, only_unknown = FALSE)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_gramstain <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
x.mo <- as.mo(x, language = language, ...)
|
||||
metadata <- get_mo_failures_uncertainties_renamed()
|
||||
|
||||
@ -272,21 +308,46 @@ mo_gramstain <- function(x, language = get_locale(), ...) {
|
||||
translate_AMR(x, language = language, only_unknown = FALSE)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
is_gram_negative <- function(x, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
grams <- mo_gramstain(x, language = NULL, ...)
|
||||
"Gram-negative" == grams & !is.na(grams)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
is_gram_positive <- function(x, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
grams <- mo_gramstain(x, language = NULL, ...)
|
||||
"Gram-positive" == grams & !is.na(grams)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_snomed <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
mo_validate(x = x, property = "snomed", language = language, ...)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_ref <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
mo_validate(x = x, property = "ref", language = language, ...)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_authors <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
x <- mo_validate(x = x, property = "ref", language = language, ...)
|
||||
# remove last 4 digits and presumably the comma and space that preceed them
|
||||
x[!is.na(x)] <- gsub(",? ?[0-9]{4}", "", x[!is.na(x)])
|
||||
@ -296,6 +357,9 @@ mo_authors <- function(x, language = get_locale(), ...) {
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_year <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
x <- mo_validate(x = x, property = "ref", language = language, ...)
|
||||
# get last 4 digits
|
||||
x[!is.na(x)] <- gsub(".*([0-9]{4})$", "\\1", x[!is.na(x)])
|
||||
@ -305,12 +369,18 @@ mo_year <- function(x, language = get_locale(), ...) {
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_rank <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
mo_validate(x = x, property = "rank", language = language, ...)
|
||||
}
|
||||
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_taxonomy <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
x <- as.mo(x, language = language, ...)
|
||||
metadata <- get_mo_failures_uncertainties_renamed()
|
||||
|
||||
@ -330,6 +400,9 @@ mo_taxonomy <- function(x, language = get_locale(), ...) {
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_synonyms <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
x <- as.mo(x, language = language, ...)
|
||||
metadata <- get_mo_failures_uncertainties_renamed()
|
||||
|
||||
@ -356,6 +429,9 @@ mo_synonyms <- function(x, language = get_locale(), ...) {
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_info <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
x <- as.mo(x, language = language, ...)
|
||||
metadata <- get_mo_failures_uncertainties_renamed()
|
||||
|
||||
@ -379,6 +455,10 @@ mo_info <- function(x, language = get_locale(), ...) {
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_url <- function(x, open = FALSE, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(open, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
mo <- as.mo(x = x, language = language, ... = ...)
|
||||
mo_names <- mo_name(mo)
|
||||
metadata <- get_mo_failures_uncertainties_renamed()
|
||||
@ -408,15 +488,14 @@ mo_url <- function(x, open = FALSE, language = get_locale(), ...) {
|
||||
#' @rdname mo_property
|
||||
#' @export
|
||||
mo_property <- function(x, property = "fullname", language = get_locale(), ...) {
|
||||
stop_ifnot(length(property) == 1L, "'property' must be of length 1")
|
||||
stop_ifnot(property %in% colnames(microorganisms),
|
||||
"invalid property: '", property, "' - use a column name of the `microorganisms` data set")
|
||||
|
||||
meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE)
|
||||
meet_criteria(property, allow_class = "character", has_length = 1, is_in = colnames(microorganisms))
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
translate_AMR(mo_validate(x = x, property = property, language = language, ...), language = language, only_unknown = TRUE)
|
||||
}
|
||||
|
||||
mo_validate <- function(x, property, language, ...) {
|
||||
|
||||
check_dataset_integrity()
|
||||
|
||||
if (tryCatch(all(x[!is.na(x)] %in% MO_lookup$mo) & length(list(...)) == 0, error = function(e) FALSE)) {
|
||||
|
@ -115,12 +115,12 @@
|
||||
#' @export
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
set_mo_source <- function(path) {
|
||||
meet_criteria(path, allow_class = "character", has_length = 1)
|
||||
|
||||
file_location <- path.expand("~/mo_source.rds")
|
||||
|
||||
stop_ifnot(interactive(), "This function can only be used in interactive mode, since it must ask for the user's permission to write a file to their home folder.")
|
||||
stop_ifnot(length(path) == 1, "`path` must be of length 1")
|
||||
|
||||
|
||||
if (is.null(path) || path %in% c(FALSE, "")) {
|
||||
options(mo_source = NULL)
|
||||
options(mo_source_timestamp = NULL)
|
||||
@ -131,8 +131,7 @@ set_mo_source <- function(path) {
|
||||
return(invisible())
|
||||
}
|
||||
|
||||
stop_ifnot(file.exists(path),
|
||||
"file not found: ", path)
|
||||
stop_ifnot(file.exists(path), "file not found: ", path)
|
||||
|
||||
if (path %like% "[.]rds$") {
|
||||
df <- readRDS(path)
|
||||
@ -237,7 +236,6 @@ get_mo_source <- function() {
|
||||
}
|
||||
|
||||
mo_source_isvalid <- function(x, refer_to_name = "`reference_df`", stop_on_error = TRUE) {
|
||||
|
||||
check_dataset_integrity()
|
||||
|
||||
if (deparse(substitute(x)) == "get_mo_source()") {
|
||||
|
48
R/p_symbol.R
48
R/p_symbol.R
@ -1,48 +0,0 @@
|
||||
# ==================================================================== #
|
||||
# TITLE #
|
||||
# Antimicrobial Resistance (AMR) Analysis for R #
|
||||
# #
|
||||
# SOURCE #
|
||||
# https://github.com/msberends/AMR #
|
||||
# #
|
||||
# LICENCE #
|
||||
# (c) 2018-2020 Berends MS, Luz CF et al. #
|
||||
# Developed at the University of Groningen, the Netherlands, in #
|
||||
# collaboration with non-profit organisations Certe Medical #
|
||||
# Diagnostics & Advice, and University Medical Center Groningen. #
|
||||
# #
|
||||
# This R package is free software; you can freely use and distribute #
|
||||
# it for both personal and commercial purposes under the terms of the #
|
||||
# GNU General Public License version 2.0 (GNU GPL-2), as published by #
|
||||
# the Free Software Foundation. #
|
||||
# We created this package for both routine data analysis and academic #
|
||||
# research and it was publicly released in the hope that it will be #
|
||||
# useful, but it comes WITHOUT ANY WARRANTY OR LIABILITY. #
|
||||
# #
|
||||
# Visit our website for the full manual and a complete tutorial about #
|
||||
# how to conduct AMR analysis: https://msberends.github.io/AMR/ #
|
||||
# ==================================================================== #
|
||||
|
||||
#' Symbol of a p-value
|
||||
#'
|
||||
#' Return the symbol related to the p-value: 0 '`***`' 0.001 '`**`' 0.01 '`*`' 0.05 '`.`' 0.1 ' ' 1. Values above `p = 1` will return `NA`.
|
||||
#' @inheritSection lifecycle Questioning lifecycle
|
||||
#' @param p p value
|
||||
#' @param emptychar text to show when `p > 0.1`
|
||||
#' @details **NOTE**: this function will be moved to the `cleaner` package when a new version is being published on CRAN.
|
||||
#' @return Text
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @export
|
||||
p_symbol <- function(p, emptychar = " ") {
|
||||
|
||||
p <- as.double(p)
|
||||
s <- rep(NA_character_, length(p))
|
||||
|
||||
s[p <= 1] <- emptychar
|
||||
s[p <= 0.100] <- "."
|
||||
s[p <= 0.050] <- "*"
|
||||
s[p <= 0.010] <- "**"
|
||||
s[p <= 0.001] <- "***"
|
||||
|
||||
s
|
||||
}
|
9
R/pca.R
9
R/pca.R
@ -66,9 +66,12 @@ pca <- function(x,
|
||||
scale. = TRUE,
|
||||
tol = NULL,
|
||||
rank. = NULL) {
|
||||
|
||||
stop_ifnot(is.data.frame(x), "`x` must be a data.frame")
|
||||
stop_if(any(dim(x) == 0), "`x` must contain rows and columns")
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(retx, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(center, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(scale., allow_class = "logical", has_length = 1)
|
||||
meet_criteria(tol, allow_class = "numeric", has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(rank., allow_class = "numeric", has_length = 1, allow_NULL = TRUE)
|
||||
|
||||
# unset data.table, tibble, etc.
|
||||
# also removes groups made by dplyr::group_by
|
||||
|
@ -266,7 +266,6 @@ proportion_df <- function(data,
|
||||
as_percent = FALSE,
|
||||
combine_SI = TRUE,
|
||||
combine_IR = FALSE) {
|
||||
|
||||
rsi_calc_df(type = "proportion",
|
||||
data = data,
|
||||
translate_ab = translate_ab,
|
||||
|
@ -126,13 +126,20 @@ resistance_predict <- function(x,
|
||||
preserve_measurements = TRUE,
|
||||
info = interactive(),
|
||||
...) {
|
||||
meet_criteria(x, allow_class = "data.frame")
|
||||
meet_criteria(col_ab, allow_class = "character", has_length = 1, is_in = colnames(x))
|
||||
meet_criteria(col_date, allow_class = "character", has_length = 1, is_in = colnames(x), allow_NULL = TRUE)
|
||||
meet_criteria(year_min, allow_class = c("numeric", "integer"), has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(year_max, allow_class = c("numeric", "integer"), has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(year_every, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(model, allow_class = c("character", "function"), has_length = 1, allow_NULL = TRUE)
|
||||
meet_criteria(I_as_S, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(preserve_measurements, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(info, allow_class = "logical", has_length = 1)
|
||||
|
||||
stop_ifnot(is.data.frame(x), "`x` must be a data.frame")
|
||||
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")
|
||||
|
||||
|
||||
dots <- unlist(list(...))
|
||||
if (length(dots) != 0) {
|
||||
# backwards compatibility with old parameters
|
||||
@ -300,6 +307,7 @@ rsi_predict <- resistance_predict
|
||||
#' @rdname resistance_predict
|
||||
plot.resistance_predict <- function(x, main = paste("Resistance Prediction of", x_name), ...) {
|
||||
x_name <- paste0(ab_name(attributes(x)$ab), " (", attributes(x)$ab, ")")
|
||||
meet_criteria(main, allow_class = "character", has_length = 1)
|
||||
|
||||
if (attributes(x)$I_as_S == TRUE) {
|
||||
ylab <- "%R"
|
||||
@ -342,11 +350,13 @@ ggplot_rsi_predict <- function(x,
|
||||
main = paste("Resistance Prediction of", x_name),
|
||||
ribbon = TRUE,
|
||||
...) {
|
||||
x_name <- paste0(ab_name(attributes(x)$ab), " (", attributes(x)$ab, ")")
|
||||
meet_criteria(main, allow_class = "character", has_length = 1)
|
||||
meet_criteria(ribbon, allow_class = "logical", has_length = 1)
|
||||
|
||||
stop_ifnot_installed("ggplot2")
|
||||
stop_ifnot(inherits(x, "resistance_predict"), "`x` must be a resistance prediction model created with resistance_predict()")
|
||||
|
||||
x_name <- paste0(ab_name(attributes(x)$ab), " (", attributes(x)$ab, ")")
|
||||
|
||||
if (attributes(x)$I_as_S == TRUE) {
|
||||
ylab <- "%R"
|
||||
|
50
R/rsi.R
50
R/rsi.R
@ -31,7 +31,7 @@
|
||||
#' @param x vector of values (for class [`mic`]: an MIC value in mg/L, for class [`disk`]: a disk diffusion radius in millimetres)
|
||||
#' @param mo any (vector of) text that can be coerced to a valid microorganism code with [as.mo()], will be determined automatically if the `dplyr` package is installed
|
||||
#' @param ab any (vector of) text that can be coerced to a valid antimicrobial code with [as.ab()]
|
||||
#' @param uti (Urinary Tract Infection) A vector with [logical]s (`TRUE` or `FALSE`) to specify whether a UTI specific interpretation from the guideline should be chosen. For using [as.rsi()] on a [data.frame], this can also be a column containing [logical]s or when left blank, the data set will be search for a 'specimen' and rows containing 'urin' in that column will be regarded isolates from a UTI. See *Examples*.
|
||||
#' @param uti (Urinary Tract Infection) A vector with [logical]s (`TRUE` or `FALSE`) to specify whether a UTI specific interpretation from the guideline should be chosen. For using [as.rsi()] on a [data.frame], this can also be a column containing [logical]s or when left blank, the data set will be searched for a 'specimen' and rows containing 'urin' (such as 'urine', 'urina') in that column will be regarded isolates from a UTI. See *Examples*.
|
||||
#' @inheritParams first_isolate
|
||||
#' @param guideline defaults to the latest included EUCAST guideline, see Details for all options
|
||||
#' @param conserve_capped_values a logical to indicate that MIC values starting with `">"` (but not `">="`) must always return "R" , and that MIC values starting with `"<"` (but not `"<="`) must always return "S"
|
||||
@ -193,6 +193,8 @@ is.rsi <- function(x) {
|
||||
#' @rdname as.rsi
|
||||
#' @export
|
||||
is.rsi.eligible <- function(x, threshold = 0.05) {
|
||||
meet_criteria(threshold, allow_class = "numeric", has_length = 1)
|
||||
|
||||
stop_if(NCOL(x) > 1, "`x` must be a one-dimensional vector.")
|
||||
if (any(c("logical",
|
||||
"numeric",
|
||||
@ -293,6 +295,13 @@ as.rsi.mic <- function(x,
|
||||
conserve_capped_values = FALSE,
|
||||
add_intrinsic_resistance = FALSE,
|
||||
...) {
|
||||
meet_criteria(x)
|
||||
meet_criteria(mo, allow_class = c("mo", "character"), allow_NULL = TRUE)
|
||||
meet_criteria(ab, allow_class = c("ab", "character"))
|
||||
meet_criteria(guideline, allow_class = "character", has_length = 1)
|
||||
meet_criteria(uti, allow_class = "logical", has_length = c(1, length(x)))
|
||||
meet_criteria(conserve_capped_values, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(add_intrinsic_resistance, allow_class = "logical", has_length = 1)
|
||||
|
||||
# for dplyr's across()
|
||||
cur_column_dplyr <- import_fn("cur_column", "dplyr", error_on_fail = FALSE)
|
||||
@ -323,6 +332,9 @@ as.rsi.mic <- function(x,
|
||||
"`data %>% mutate_at(vars(...), as.rsi, mo = .$x)`, where x is your column with microorganisms.\n\n",
|
||||
"To tranform all MIC values in a data set, use `data %>% as.rsi()` or data %>% mutate_if(is.mic, as.rsi).", call = FALSE)
|
||||
}
|
||||
if (length(ab) == 1 && ab %like% "as.mic") {
|
||||
stop_('No unambiguous name was supplied about the antibiotic (parameter "ab"). See ?as.rsi.', call = FALSE)
|
||||
}
|
||||
|
||||
ab_coerced <- suppressWarnings(as.ab(ab))
|
||||
mo_coerced <- suppressWarnings(as.mo(mo))
|
||||
@ -364,6 +376,12 @@ as.rsi.disk <- function(x,
|
||||
uti = FALSE,
|
||||
add_intrinsic_resistance = FALSE,
|
||||
...) {
|
||||
meet_criteria(x)
|
||||
meet_criteria(mo, allow_class = c("mo", "character"), allow_NULL = TRUE)
|
||||
meet_criteria(ab, allow_class = c("ab", "character"))
|
||||
meet_criteria(guideline, allow_class = "character", has_length = 1)
|
||||
meet_criteria(uti, allow_class = "logical", has_length = c(1, length(x)))
|
||||
meet_criteria(add_intrinsic_resistance, allow_class = "logical", has_length = 1)
|
||||
|
||||
# for dplyr's across()
|
||||
cur_column_dplyr <- import_fn("cur_column", "dplyr", error_on_fail = FALSE)
|
||||
@ -394,6 +412,9 @@ as.rsi.disk <- function(x,
|
||||
"`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 `data %>% as.rsi()` or data %>% mutate_if(is.disk, as.rsi).", call = FALSE)
|
||||
}
|
||||
if (length(ab) == 1 && ab %like% "as.disk") {
|
||||
stop_('No unambiguous name was supplied about the antibiotic (parameter "ab"). See ?as.rsi.', call = FALSE)
|
||||
}
|
||||
|
||||
ab_coerced <- suppressWarnings(as.ab(ab))
|
||||
mo_coerced <- suppressWarnings(as.mo(mo))
|
||||
@ -433,6 +454,12 @@ as.rsi.data.frame <- function(x,
|
||||
uti = NULL,
|
||||
conserve_capped_values = FALSE,
|
||||
add_intrinsic_resistance = FALSE) {
|
||||
meet_criteria(x, allow_class = "data.frame") # will also check for dimensions > 0
|
||||
meet_criteria(col_mo, allow_class = "character", is_in = colnames(x), allow_NULL = TRUE)
|
||||
meet_criteria(guideline, allow_class = "character", has_length = 1)
|
||||
meet_criteria(uti, allow_class = "logical", has_length = c(1, nrow(x)), allow_NULL = TRUE)
|
||||
meet_criteria(conserve_capped_values, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(add_intrinsic_resistance, allow_class = "logical", has_length = 1)
|
||||
|
||||
# -- UTIs
|
||||
col_uti <- uti
|
||||
@ -731,6 +758,14 @@ type_sum.rsi <- function(x, ...) {
|
||||
freq.rsi <- function(x, ...) {
|
||||
x_name <- deparse(substitute(x))
|
||||
x_name <- gsub(".*[$]", "", x_name)
|
||||
if (x_name %in% c("x", ".")) {
|
||||
# try again going through system calls
|
||||
x_name <- na.omit(sapply(sys.calls(),
|
||||
function(call) {
|
||||
call_txt <- as.character(call)
|
||||
ifelse(call_txt[1] %like% "freq$", call_txt[length(call_txt)], character(0))
|
||||
}))[1L]
|
||||
}
|
||||
ab <- suppressMessages(suppressWarnings(as.ab(x_name)))
|
||||
freq.default <- import_fn("freq.default", "cleaner", error_on_fail = FALSE)
|
||||
digits <- list(...)$digits
|
||||
@ -850,6 +885,13 @@ plot.rsi <- function(x,
|
||||
main = paste("Resistance Overview of", deparse(substitute(x))),
|
||||
axes = FALSE,
|
||||
...) {
|
||||
meet_criteria(lwd, allow_class = c("numeric", "integer"), has_length = 1)
|
||||
meet_criteria(ylim, allow_class = c("numeric", "integer"), allow_NULL = TRUE)
|
||||
meet_criteria(ylab, allow_class = "character", has_length = 1)
|
||||
meet_criteria(xlab, allow_class = "character", has_length = 1)
|
||||
meet_criteria(main, allow_class = "character", has_length = 1)
|
||||
meet_criteria(axes, allow_class = "logical", has_length = 1)
|
||||
|
||||
data <- as.data.frame(table(x), stringsAsFactors = FALSE)
|
||||
colnames(data) <- c("x", "n")
|
||||
data$s <- round((data$n / sum(data$n)) * 100, 1)
|
||||
@ -901,6 +943,12 @@ barplot.rsi <- function(height,
|
||||
beside = TRUE,
|
||||
axes = beside,
|
||||
...) {
|
||||
meet_criteria(col, allow_class = "character", has_length = 3)
|
||||
meet_criteria(xlab, allow_class = "character", has_length = 1)
|
||||
meet_criteria(main, allow_class = "character", has_length = 1)
|
||||
meet_criteria(ylab, allow_class = "character", has_length = 1)
|
||||
meet_criteria(beside, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(axes, allow_class = "logical", has_length = 1)
|
||||
|
||||
if (axes == TRUE) {
|
||||
par(mar = c(5, 4, 4, 2) + 0.1)
|
||||
|
23
R/rsi_calc.R
23
R/rsi_calc.R
@ -36,10 +36,11 @@ rsi_calc <- function(...,
|
||||
as_percent = FALSE,
|
||||
only_all_tested = 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)
|
||||
meet_criteria(ab_result, allow_class = c("character", "numeric", "integer"), has_length = c(1, 2, 3), .call_depth = 1)
|
||||
meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1, .call_depth = 1)
|
||||
meet_criteria(as_percent, allow_class = "logical", has_length = 1, .call_depth = 1)
|
||||
meet_criteria(only_all_tested, allow_class = "logical", has_length = 1, .call_depth = 1)
|
||||
meet_criteria(only_count, allow_class = "logical", has_length = 1, .call_depth = 1)
|
||||
|
||||
data_vars <- dots2vars(...)
|
||||
|
||||
@ -177,17 +178,21 @@ rsi_calc_df <- function(type, # "proportion", "count" or "both"
|
||||
combine_SI = TRUE,
|
||||
combine_IR = FALSE,
|
||||
combine_SI_missing = FALSE) {
|
||||
meet_criteria(type, is_in = c("proportion", "count", "both"), has_length = 1, .call_depth = 1)
|
||||
meet_criteria(data, allow_class = "data.frame", contains_column_class = "rsi", .call_depth = 1)
|
||||
meet_criteria(translate_ab, allow_class = c("character", "logical"), has_length = 1, allow_NA = TRUE, .call_depth = 1)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE, .call_depth = 1)
|
||||
meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1, .call_depth = 1)
|
||||
meet_criteria(as_percent, allow_class = "logical", has_length = 1, .call_depth = 1)
|
||||
meet_criteria(combine_SI, allow_class = "logical", has_length = 1, .call_depth = 1)
|
||||
meet_criteria(combine_SI_missing, allow_class = "logical", has_length = 1, .call_depth = 1)
|
||||
|
||||
check_dataset_integrity()
|
||||
stop_ifnot(is.data.frame(data), "`data` must be a data.frame", call = -2)
|
||||
stop_if(any(dim(data) == 0), "`data` must contain rows and columns", call = -2)
|
||||
stop_ifnot(any(sapply(data, is.rsi), na.rm = TRUE), "no columns with class <rsi> found. See ?as.rsi.", call = -2)
|
||||
|
||||
if (isTRUE(combine_IR) & isTRUE(combine_SI_missing)) {
|
||||
combine_SI <- FALSE
|
||||
}
|
||||
stop_if(isTRUE(combine_SI) & isTRUE(combine_IR), "either `combine_SI` or `combine_IR` can be TRUE, not both", call = -2)
|
||||
stop_ifnot(is.numeric(minimum), "`minimum` must be numeric", call = -2)
|
||||
stop_ifnot(is.logical(as_percent), "`as_percent` must be logical", call = -2)
|
||||
|
||||
translate_ab <- get_translate_ab(translate_ab)
|
||||
|
||||
|
@ -32,7 +32,6 @@ rsi_df <- function(data,
|
||||
as_percent = FALSE,
|
||||
combine_SI = TRUE,
|
||||
combine_IR = FALSE) {
|
||||
|
||||
rsi_calc_df(type = "both",
|
||||
data = data,
|
||||
translate_ab = translate_ab,
|
||||
|
@ -36,6 +36,7 @@
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @export
|
||||
skewness <- function(x, na.rm = FALSE) {
|
||||
meet_criteria(na.rm, allow_class = "logical", has_length = 1)
|
||||
UseMethod("skewness")
|
||||
}
|
||||
|
||||
@ -43,6 +44,7 @@ skewness <- function(x, na.rm = FALSE) {
|
||||
#' @rdname skewness
|
||||
#' @export
|
||||
skewness.default <- function(x, na.rm = FALSE) {
|
||||
meet_criteria(na.rm, allow_class = "logical", has_length = 1)
|
||||
x <- as.vector(x)
|
||||
if (na.rm == TRUE) {
|
||||
x <- x[!is.na(x)]
|
||||
@ -55,6 +57,7 @@ skewness.default <- function(x, na.rm = FALSE) {
|
||||
#' @rdname skewness
|
||||
#' @export
|
||||
skewness.matrix <- function(x, na.rm = FALSE) {
|
||||
meet_criteria(na.rm, allow_class = "logical", has_length = 1)
|
||||
apply(x, 2, skewness.default, na.rm = na.rm)
|
||||
}
|
||||
|
||||
@ -62,5 +65,6 @@ skewness.matrix <- function(x, na.rm = FALSE) {
|
||||
#' @rdname skewness
|
||||
#' @export
|
||||
skewness.data.frame <- function(x, na.rm = FALSE) {
|
||||
meet_criteria(na.rm, allow_class = "logical", has_length = 1)
|
||||
sapply(x, skewness.default, na.rm = na.rm)
|
||||
}
|
||||
|
@ -73,7 +73,7 @@
|
||||
#' mo_name("CoNS", language = "pt")
|
||||
#' #> "Staphylococcus coagulase negativo (CoNS)"
|
||||
get_locale <- function() {
|
||||
# AMR versions prior to 1.3.0 used the environmental variable:
|
||||
# AMR versions 1.3.0 and prior used the environmental variable:
|
||||
if (!identical("", Sys.getenv("AMR_locale"))) {
|
||||
options(AMR_locale = Sys.getenv("AMR_locale"))
|
||||
}
|
||||
@ -101,20 +101,20 @@ get_locale <- function() {
|
||||
|
||||
coerce_language_setting <- function(lang) {
|
||||
# grepl() with ignore.case = FALSE is faster than %like%
|
||||
if (grepl("^(English|en_|EN_)", lang, ignore.case = FALSE)) {
|
||||
if (grepl("^(English|en_|EN_)", lang, ignore.case = FALSE, perl = TRUE)) {
|
||||
# as first option to optimise speed
|
||||
"en"
|
||||
} else if (grepl("^(German|Deutsch|de_|DE_)", lang, ignore.case = FALSE)) {
|
||||
} else if (grepl("^(German|Deutsch|de_|DE_)", lang, ignore.case = FALSE, perl = TRUE)) {
|
||||
"de"
|
||||
} else if (grepl("^(Dutch|Nederlands|nl_|NL_)", lang, ignore.case = FALSE)) {
|
||||
} else if (grepl("^(Dutch|Nederlands|nl_|NL_)", lang, ignore.case = FALSE, perl = TRUE)) {
|
||||
"nl"
|
||||
} else if (grepl("^(Spanish|Espa.+ol|es_|ES_)", lang, ignore.case = FALSE)) {
|
||||
} else if (grepl("^(Spanish|Espa.+ol|es_|ES_)", lang, ignore.case = FALSE, perl = TRUE)) {
|
||||
"es"
|
||||
} else if (grepl("^(Italian|Italiano|it_|IT_)", lang, ignore.case = FALSE)) {
|
||||
} else if (grepl("^(Italian|Italiano|it_|IT_)", lang, ignore.case = FALSE, perl = TRUE)) {
|
||||
"it"
|
||||
} else if (grepl("^(French|Fran.+ais|fr_|FR_)", lang, ignore.case = FALSE)) {
|
||||
} else if (grepl("^(French|Fran.+ais|fr_|FR_)", lang, ignore.case = FALSE, perl = TRUE)) {
|
||||
"fr"
|
||||
} else if (grepl("^(Portuguese|Portugu.+s|pt_|PT_)", lang, ignore.case = FALSE)) {
|
||||
} else if (grepl("^(Portuguese|Portugu.+s|pt_|PT_)", lang, ignore.case = FALSE, perl = TRUE)) {
|
||||
"pt"
|
||||
} else {
|
||||
# other language -> set to English
|
||||
|
Reference in New Issue
Block a user