2018-02-21 11:52:31 +01:00
|
|
|
# ==================================================================== #
|
|
|
|
# TITLE #
|
2022-10-05 09:12:22 +02:00
|
|
|
# AMR: An R Package for Working with Antimicrobial Resistance Data #
|
2018-02-21 11:52:31 +01:00
|
|
|
# #
|
2019-01-02 23:24:07 +01:00
|
|
|
# SOURCE #
|
2020-07-08 14:48:06 +02:00
|
|
|
# https://github.com/msberends/AMR #
|
2018-02-21 11:52:31 +01:00
|
|
|
# #
|
2022-10-05 09:12:22 +02:00
|
|
|
# CITE AS #
|
|
|
|
# Berends MS, Luz CF, Friedrich AW, Sinha BNM, Albers CJ, Glasner C #
|
|
|
|
# (2022). AMR: An R Package for Working with Antimicrobial Resistance #
|
|
|
|
# Data. Journal of Statistical Software, 104(3), 1-31. #
|
|
|
|
# doi:10.18637/jss.v104.i03 #
|
|
|
|
# #
|
2022-12-27 15:16:15 +01:00
|
|
|
# Developed at the University of Groningen and the University Medical #
|
|
|
|
# Center Groningen in The Netherlands, in collaboration with many #
|
|
|
|
# colleagues from around the world, see our website. #
|
2018-02-21 11:52:31 +01:00
|
|
|
# #
|
2019-01-02 23:24:07 +01:00
|
|
|
# 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. #
|
2020-01-05 17:22:09 +01:00
|
|
|
# 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. #
|
2020-10-08 11:16:03 +02:00
|
|
|
# #
|
|
|
|
# Visit our website for the full manual and a complete tutorial about #
|
2021-02-02 23:57:35 +01:00
|
|
|
# how to conduct AMR data analysis: https://msberends.github.io/AMR/ #
|
2018-02-21 11:52:31 +01:00
|
|
|
# ==================================================================== #
|
|
|
|
|
2020-09-03 12:31:48 +02:00
|
|
|
# faster implementation of left_join than using merge() by poorman - we use match():
|
2020-09-18 16:05:53 +02:00
|
|
|
pm_left_join <- function(x, y, by = NULL, suffix = c(".x", ".y")) {
|
2020-08-14 13:36:10 +02:00
|
|
|
if (is.null(by)) {
|
|
|
|
by <- intersect(names(x), names(y))[1L]
|
|
|
|
if (is.na(by)) {
|
2020-09-18 16:05:53 +02:00
|
|
|
stop_("no common column found for pm_left_join()")
|
2020-08-14 13:36:10 +02:00
|
|
|
}
|
2020-09-19 11:54:01 +02:00
|
|
|
pm_join_message(by)
|
2020-08-14 13:36:10 +02:00
|
|
|
} else if (!is.null(names(by))) {
|
|
|
|
by <- unname(c(names(by), by))
|
|
|
|
}
|
|
|
|
if (length(by) == 1) {
|
|
|
|
by <- rep(by, 2)
|
|
|
|
}
|
2020-10-26 12:23:03 +01:00
|
|
|
|
2020-08-15 12:54:47 +02:00
|
|
|
int_x <- colnames(x) %in% colnames(y) & colnames(x) != by[1]
|
|
|
|
int_y <- colnames(y) %in% colnames(x) & colnames(y) != by[2]
|
|
|
|
colnames(x)[int_x] <- paste0(colnames(x)[int_x], suffix[1L])
|
|
|
|
colnames(y)[int_y] <- paste0(colnames(y)[int_y], suffix[2L])
|
2020-10-26 12:23:03 +01:00
|
|
|
|
2022-08-28 10:31:50 +02:00
|
|
|
merged <- cbind(
|
|
|
|
x,
|
|
|
|
y[match(
|
|
|
|
x[, by[1], drop = TRUE],
|
|
|
|
y[, by[2], drop = TRUE]
|
|
|
|
),
|
|
|
|
colnames(y)[!colnames(y) %in% colnames(x) & !colnames(y) == by[2]],
|
|
|
|
drop = FALSE
|
|
|
|
]
|
|
|
|
)
|
2020-10-26 12:23:03 +01:00
|
|
|
|
2020-08-14 13:36:10 +02:00
|
|
|
rownames(merged) <- NULL
|
|
|
|
merged
|
|
|
|
}
|
2020-09-18 16:05:53 +02:00
|
|
|
|
2021-12-05 22:06:45 +01:00
|
|
|
# support where() like tidyverse:
|
|
|
|
# adapted from https://github.com/nathaneastwood/poorman/blob/52eb6947e0b4430cd588976ed8820013eddf955f/R/where.R#L17-L32
|
|
|
|
where <- function(fn) {
|
|
|
|
if (!is.function(fn)) {
|
2021-12-05 23:11:10 +01:00
|
|
|
stop(pm_deparse_var(fn), " is not a valid predicate function.")
|
2021-12-05 22:06:45 +01:00
|
|
|
}
|
|
|
|
preds <- unlist(lapply(
|
|
|
|
pm_select_env$.data,
|
|
|
|
function(x, fn) {
|
|
|
|
do.call("fn", list(x))
|
|
|
|
},
|
|
|
|
fn
|
|
|
|
))
|
|
|
|
if (!is.logical(preds)) stop("`where()` must be used with functions that return `TRUE` or `FALSE`.")
|
|
|
|
data_cols <- pm_select_env$get_colnames()
|
|
|
|
cols <- data_cols[preds]
|
|
|
|
which(data_cols %in% cols)
|
|
|
|
}
|
|
|
|
|
2021-11-01 13:51:13 +01:00
|
|
|
# copied and slightly rewritten from poorman under same license (2021-10-15)
|
2022-08-28 10:31:50 +02:00
|
|
|
quick_case_when <- function(...) {
|
2021-11-01 13:51:13 +01:00
|
|
|
fs <- list(...)
|
2022-08-28 10:31:50 +02:00
|
|
|
lapply(fs, function(x) {
|
2022-10-05 09:12:22 +02:00
|
|
|
if (!inherits(x, "formula")) {
|
2022-08-28 10:31:50 +02:00
|
|
|
stop("`case_when()` requires formula inputs.")
|
|
|
|
}
|
|
|
|
})
|
2021-11-01 13:51:13 +01:00
|
|
|
n <- length(fs)
|
2022-08-28 10:31:50 +02:00
|
|
|
if (n == 0L) {
|
2021-11-01 13:51:13 +01:00
|
|
|
stop("No cases provided.")
|
2022-08-28 10:31:50 +02:00
|
|
|
}
|
|
|
|
|
|
|
|
validate_case_when_length <- function(query, value, fs) {
|
2021-11-01 13:51:13 +01:00
|
|
|
lhs_lengths <- lengths(query)
|
|
|
|
rhs_lengths <- lengths(value)
|
|
|
|
all_lengths <- unique(c(lhs_lengths, rhs_lengths))
|
2022-08-28 10:31:50 +02:00
|
|
|
if (length(all_lengths) <= 1L) {
|
2021-11-01 13:51:13 +01:00
|
|
|
return(all_lengths[[1L]])
|
2022-08-28 10:31:50 +02:00
|
|
|
}
|
2021-11-01 13:51:13 +01:00
|
|
|
non_atomic_lengths <- all_lengths[all_lengths != 1L]
|
|
|
|
len <- non_atomic_lengths[[1L]]
|
2022-08-28 10:31:50 +02:00
|
|
|
if (length(non_atomic_lengths) == 1L) {
|
2021-11-01 13:51:13 +01:00
|
|
|
return(len)
|
2022-08-28 10:31:50 +02:00
|
|
|
}
|
2021-11-01 13:51:13 +01:00
|
|
|
inconsistent_lengths <- non_atomic_lengths[-1L]
|
|
|
|
lhs_problems <- lhs_lengths %in% inconsistent_lengths
|
|
|
|
rhs_problems <- rhs_lengths %in% inconsistent_lengths
|
|
|
|
problems <- lhs_problems | rhs_problems
|
|
|
|
if (any(problems)) {
|
2022-08-28 10:31:50 +02:00
|
|
|
stop("The following formulas must be length ", len, " or 1, not ",
|
|
|
|
paste(inconsistent_lengths, collapse = ", "), ".\n ",
|
|
|
|
paste(fs[problems], collapse = "\n "),
|
|
|
|
call. = FALSE
|
|
|
|
)
|
2021-11-01 13:51:13 +01:00
|
|
|
}
|
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
|
|
|
|
replace_with <- function(x, i, val, arg_name) {
|
|
|
|
if (is.null(val)) {
|
2021-11-01 13:51:13 +01:00
|
|
|
return(x)
|
2022-08-28 10:31:50 +02:00
|
|
|
}
|
2021-11-01 13:51:13 +01:00
|
|
|
i[is.na(i)] <- FALSE
|
|
|
|
if (length(val) == 1L) {
|
|
|
|
x[i] <- val
|
2022-08-28 10:31:50 +02:00
|
|
|
} else {
|
2021-11-01 13:51:13 +01:00
|
|
|
x[i] <- val[i]
|
|
|
|
}
|
|
|
|
x
|
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2021-11-01 13:51:13 +01:00
|
|
|
query <- vector("list", n)
|
|
|
|
value <- vector("list", n)
|
|
|
|
default_env <- parent.frame()
|
|
|
|
for (i in seq_len(n)) {
|
|
|
|
query[[i]] <- eval(fs[[i]][[2]], envir = default_env)
|
|
|
|
value[[i]] <- eval(fs[[i]][[3]], envir = default_env)
|
2022-08-28 10:31:50 +02:00
|
|
|
if (!is.logical(query[[i]])) {
|
2021-11-01 13:51:13 +01:00
|
|
|
stop(fs[[i]][[2]], " does not return a `logical` vector.")
|
2022-08-28 10:31:50 +02:00
|
|
|
}
|
2021-11-01 13:51:13 +01:00
|
|
|
}
|
|
|
|
m <- validate_case_when_length(query, value, fs)
|
|
|
|
out <- value[[1]][rep(NA_integer_, m)]
|
|
|
|
replaced <- rep(FALSE, m)
|
|
|
|
for (i in seq_len(n)) {
|
2022-08-28 10:31:50 +02:00
|
|
|
out <- replace_with(
|
|
|
|
out, query[[i]] & !replaced, value[[i]],
|
|
|
|
NULL
|
|
|
|
)
|
2021-11-01 13:51:13 +01:00
|
|
|
replaced <- replaced | (query[[i]] & !is.na(query[[i]]))
|
2020-05-16 13:05:47 +02:00
|
|
|
}
|
2021-11-01 13:51:13 +01:00
|
|
|
out
|
2020-05-16 13:05:47 +02:00
|
|
|
}
|
|
|
|
|
2018-07-04 17:20:03 +02:00
|
|
|
# No export, no Rd
|
|
|
|
addin_insert_in <- function() {
|
2020-06-17 15:14:37 +02:00
|
|
|
import_fn("insertText", "rstudioapi")(" %in% ")
|
2018-07-04 17:20:03 +02:00
|
|
|
}
|
|
|
|
|
|
|
|
# No export, no Rd
|
|
|
|
addin_insert_like <- function() {
|
2021-04-23 09:59:36 +02:00
|
|
|
# we want Shift + Ctrl/Cmd + L to iterate over %like%, %unlike%, %like_case%, and %unlike_case%
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2021-04-23 09:59:36 +02:00
|
|
|
getActiveDocumentContext <- import_fn("getActiveDocumentContext", "rstudioapi")
|
|
|
|
insertText <- import_fn("insertText", "rstudioapi")
|
|
|
|
modifyRange <- import_fn("modifyRange", "rstudioapi")
|
|
|
|
document_range <- import_fn("document_range", "rstudioapi")
|
|
|
|
document_position <- import_fn("document_position", "rstudioapi")
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2021-04-23 09:59:36 +02:00
|
|
|
context <- getActiveDocumentContext()
|
|
|
|
current_row <- context$selection[[1]]$range$end[1]
|
|
|
|
current_col <- context$selection[[1]]$range$end[2]
|
|
|
|
current_row_txt <- context$contents[current_row]
|
|
|
|
if (is.null(current_row) || current_row_txt %unlike% "%(un)?like") {
|
|
|
|
insertText(" %like% ")
|
|
|
|
return(invisible())
|
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2021-04-23 09:59:36 +02:00
|
|
|
pos_preceded_by <- function(txt) {
|
|
|
|
if (tryCatch(substr(current_row_txt, current_col - nchar(trimws(txt, which = "right")), current_col) == trimws(txt, which = "right"),
|
2022-08-28 10:31:50 +02:00
|
|
|
error = function(e) FALSE
|
|
|
|
)) {
|
2021-04-23 09:59:36 +02:00
|
|
|
return(TRUE)
|
|
|
|
}
|
|
|
|
tryCatch(substr(current_row_txt, current_col - nchar(txt), current_col) %like% paste0("^", txt),
|
2022-08-28 10:31:50 +02:00
|
|
|
error = function(e) FALSE
|
|
|
|
)
|
2021-04-23 09:59:36 +02:00
|
|
|
}
|
|
|
|
replace_pos <- function(old, with) {
|
2022-08-28 10:31:50 +02:00
|
|
|
modifyRange(document_range(
|
|
|
|
document_position(current_row, current_col - nchar(old)),
|
|
|
|
document_position(current_row, current_col)
|
|
|
|
),
|
|
|
|
text = with,
|
|
|
|
id = context$id
|
|
|
|
)
|
2021-04-23 09:59:36 +02:00
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2021-04-23 09:59:36 +02:00
|
|
|
if (pos_preceded_by(" %like% ")) {
|
|
|
|
replace_pos(" %like% ", with = " %unlike% ")
|
|
|
|
} else if (pos_preceded_by(" %unlike% ")) {
|
|
|
|
replace_pos(" %unlike% ", with = " %like_case% ")
|
|
|
|
} else if (pos_preceded_by(" %like_case% ")) {
|
|
|
|
replace_pos(" %like_case% ", with = " %unlike_case% ")
|
|
|
|
} else if (pos_preceded_by(" %unlike_case% ")) {
|
|
|
|
replace_pos(" %unlike_case% ", with = " %like% ")
|
|
|
|
} else {
|
|
|
|
insertText(" %like% ")
|
|
|
|
}
|
2018-07-04 17:20:03 +02:00
|
|
|
}
|
|
|
|
|
2020-09-24 00:30:11 +02:00
|
|
|
search_type_in_df <- function(x, type, info = TRUE) {
|
2020-11-17 16:57:41 +01:00
|
|
|
meet_criteria(x, allow_class = "data.frame")
|
|
|
|
meet_criteria(type, allow_class = "character", has_length = 1)
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2019-01-15 12:45:24 +01:00
|
|
|
# try to find columns based on type
|
|
|
|
found <- NULL
|
2020-10-26 12:23:03 +01:00
|
|
|
|
2020-11-17 16:57:41 +01:00
|
|
|
# remove attributes from other packages
|
2020-05-16 13:05:47 +02:00
|
|
|
x <- as.data.frame(x, stringsAsFactors = FALSE)
|
2021-06-22 12:16:42 +02:00
|
|
|
colnames_formatted <- tolower(generalise_antibiotic_name(colnames(x)))
|
2020-10-26 12:23:03 +01:00
|
|
|
|
2019-01-15 12:45:24 +01:00
|
|
|
# -- mo
|
|
|
|
if (type == "mo") {
|
2020-12-28 22:24:33 +01:00
|
|
|
if (any(vapply(FUN.VALUE = logical(1), x, is.mo))) {
|
2022-10-19 11:47:57 +02:00
|
|
|
# take first 'mo' column
|
2021-06-22 12:16:42 +02:00
|
|
|
found <- colnames(x)[vapply(FUN.VALUE = logical(1), x, is.mo)]
|
2022-10-05 09:12:22 +02:00
|
|
|
} else if ("mo" %in% colnames_formatted &&
|
|
|
|
suppressWarnings(all(x$mo %in% c(NA, AMR::microorganisms$mo)))) {
|
2019-11-04 12:08:08 +01:00
|
|
|
found <- "mo"
|
2021-06-22 12:16:42 +02:00
|
|
|
} else if (any(colnames_formatted %like_case% "^(mo|microorganism|organism|bacteria|ba[ck]terie)s?$")) {
|
|
|
|
found <- sort(colnames(x)[colnames_formatted %like_case% "^(mo|microorganism|organism|bacteria|ba[ck]terie)s?$"])
|
|
|
|
} else if (any(colnames_formatted %like_case% "^(microorganism|organism|bacteria|ba[ck]terie)")) {
|
|
|
|
found <- sort(colnames(x)[colnames_formatted %like_case% "^(microorganism|organism|bacteria|ba[ck]terie)"])
|
|
|
|
} else if (any(colnames_formatted %like_case% "species")) {
|
|
|
|
found <- sort(colnames(x)[colnames_formatted %like_case% "species"])
|
2019-01-15 12:45:24 +01:00
|
|
|
}
|
|
|
|
}
|
|
|
|
# -- key antibiotics
|
2021-05-24 15:29:17 +02:00
|
|
|
if (type %in% c("keyantibiotics", "keyantimicrobials")) {
|
2021-06-22 12:16:42 +02:00
|
|
|
if (any(colnames_formatted %like_case% "^key.*(ab|antibiotics|antimicrobials)")) {
|
|
|
|
found <- sort(colnames(x)[colnames_formatted %like_case% "^key.*(ab|antibiotics|antimicrobials)"])
|
2019-01-15 12:45:24 +01:00
|
|
|
}
|
|
|
|
}
|
|
|
|
# -- date
|
|
|
|
if (type == "date") {
|
2021-06-22 12:16:42 +02:00
|
|
|
if (any(colnames_formatted %like_case% "^(specimen date|specimen_date|spec_date)")) {
|
2019-03-15 13:57:25 +01:00
|
|
|
# WHONET support
|
2021-06-22 12:16:42 +02:00
|
|
|
found <- sort(colnames(x)[colnames_formatted %like_case% "^(specimen date|specimen_date|spec_date)"])
|
2022-10-05 09:12:22 +02:00
|
|
|
if (!inherits(pm_pull(x, found), c("Date", "POSIXct"))) {
|
2022-08-28 10:31:50 +02:00
|
|
|
stop(font_red(paste0(
|
|
|
|
"Found column '", font_bold(found), "' to be used as input for `col_", type,
|
|
|
|
"`, but this column contains no valid dates. Transform its values to valid dates first."
|
|
|
|
)),
|
|
|
|
call. = FALSE
|
|
|
|
)
|
2019-03-15 13:57:25 +01:00
|
|
|
}
|
2020-12-28 22:24:33 +01:00
|
|
|
} else if (any(vapply(FUN.VALUE = logical(1), x, function(x) inherits(x, c("Date", "POSIXct"))))) {
|
2021-06-22 12:16:42 +02:00
|
|
|
# take first <Date> column
|
|
|
|
found <- colnames(x)[vapply(FUN.VALUE = logical(1), x, function(x) inherits(x, c("Date", "POSIXct")))]
|
2019-01-15 12:45:24 +01:00
|
|
|
}
|
|
|
|
}
|
|
|
|
# -- patient id
|
|
|
|
if (type == "patient_id") {
|
2021-06-22 12:16:42 +02:00
|
|
|
crit1 <- colnames_formatted %like_case% "^(patient|patid)"
|
|
|
|
if (any(crit1)) {
|
|
|
|
found <- colnames(x)[crit1]
|
|
|
|
} else {
|
|
|
|
crit2 <- colnames_formatted %like_case% "(identification |patient|pat.*id)"
|
|
|
|
if (any(crit2)) {
|
|
|
|
found <- colnames(x)[crit2]
|
|
|
|
}
|
2019-01-29 00:06:50 +01:00
|
|
|
}
|
|
|
|
}
|
|
|
|
# -- specimen
|
|
|
|
if (type == "specimen") {
|
2021-06-22 12:16:42 +02:00
|
|
|
if (any(colnames_formatted %like_case% "(specimen type|spec_type)")) {
|
|
|
|
found <- sort(colnames(x)[colnames_formatted %like_case% "(specimen type|spec_type)"])
|
|
|
|
} else if (any(colnames_formatted %like_case% "^(specimen)")) {
|
|
|
|
found <- sort(colnames(x)[colnames_formatted %like_case% "^(specimen)"])
|
2019-01-15 12:45:24 +01:00
|
|
|
}
|
|
|
|
}
|
2020-02-20 13:19:23 +01:00
|
|
|
# -- UTI (urinary tract infection)
|
|
|
|
if (type == "uti") {
|
2021-06-22 12:16:42 +02:00
|
|
|
if (any(colnames_formatted == "uti")) {
|
|
|
|
found <- colnames(x)[colnames_formatted == "uti"]
|
|
|
|
} else if (any(colnames_formatted %like_case% "(urine|urinary)")) {
|
|
|
|
found <- sort(colnames(x)[colnames_formatted %like_case% "(urine|urinary)"])
|
2020-02-20 13:19:23 +01:00
|
|
|
}
|
|
|
|
if (!is.null(found)) {
|
2020-02-21 21:13:38 +01:00
|
|
|
# this column should contain logicals
|
2020-02-20 13:19:23 +01:00
|
|
|
if (!is.logical(x[, found, drop = TRUE])) {
|
2020-12-03 16:59:04 +01:00
|
|
|
message_("Column '", font_bold(found), "' found as input for `col_", type,
|
2022-08-28 10:31:50 +02:00
|
|
|
"`, but this column does not contain 'logical' values (TRUE/FALSE) and was ignored.",
|
|
|
|
add_fn = font_red
|
|
|
|
)
|
2020-02-20 13:19:23 +01:00
|
|
|
found <- NULL
|
|
|
|
}
|
|
|
|
}
|
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2021-06-22 12:16:42 +02:00
|
|
|
found <- found[1]
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2022-11-14 15:20:39 +01:00
|
|
|
if (!is.null(found) && isTRUE(info)) {
|
2021-12-11 13:41:31 +01:00
|
|
|
if (message_not_thrown_before("search_in_type", type)) {
|
2020-12-24 23:29:10 +01:00
|
|
|
msg <- paste0("Using column '", font_bold(found), "' as input for `col_", type, "`.")
|
2021-06-22 12:16:42 +02:00
|
|
|
if (type %in% c("keyantibiotics", "keyantimicrobials", "specimen")) {
|
2020-12-24 23:29:10 +01:00
|
|
|
msg <- paste(msg, "Use", font_bold(paste0("col_", type), "= FALSE"), "to prevent this.")
|
|
|
|
}
|
|
|
|
message_(msg)
|
2019-01-15 12:45:24 +01:00
|
|
|
}
|
|
|
|
}
|
|
|
|
found
|
|
|
|
}
|
2019-03-26 14:24:03 +01:00
|
|
|
|
2021-04-16 11:41:05 +02:00
|
|
|
is_valid_regex <- function(x) {
|
2022-08-28 10:31:50 +02:00
|
|
|
regex_at_all <- tryCatch(vapply(
|
|
|
|
FUN.VALUE = logical(1),
|
2022-10-05 09:12:22 +02:00
|
|
|
X = strsplit(x, "", fixed = TRUE),
|
2022-08-28 10:31:50 +02:00
|
|
|
FUN = function(y) {
|
|
|
|
any(y %in% c(
|
|
|
|
"$", "(", ")", "*", "+", "-",
|
|
|
|
".", "?", "[", "]", "^", "{",
|
|
|
|
"|", "}", "\\"
|
|
|
|
),
|
|
|
|
na.rm = TRUE
|
|
|
|
)
|
|
|
|
},
|
|
|
|
USE.NAMES = FALSE
|
|
|
|
),
|
|
|
|
error = function(e) rep(TRUE, length(x))
|
|
|
|
)
|
|
|
|
regex_valid <- vapply(
|
|
|
|
FUN.VALUE = logical(1),
|
|
|
|
X = x,
|
|
|
|
FUN = function(y) {
|
2022-10-05 09:12:22 +02:00
|
|
|
!inherits(try(grepl(y, "", perl = TRUE), silent = TRUE), "try-error")
|
2022-08-28 10:31:50 +02:00
|
|
|
},
|
|
|
|
USE.NAMES = FALSE
|
|
|
|
)
|
2021-04-16 11:41:05 +02:00
|
|
|
regex_at_all & regex_valid
|
2020-09-24 00:30:11 +02:00
|
|
|
}
|
|
|
|
|
2020-06-22 11:18:40 +02:00
|
|
|
stop_ifnot_installed <- function(package) {
|
2022-10-14 15:45:20 +02:00
|
|
|
installed <- vapply(FUN.VALUE = logical(1), package, requireNamespace, quietly = TRUE)
|
|
|
|
if (any(!installed) && any(package == "rstudioapi")) {
|
|
|
|
stop("This function only works in RStudio when using R >= 3.2.", call. = FALSE)
|
|
|
|
} else if (any(!installed)) {
|
|
|
|
stop("This requires the ", vector_and(package[!installed]), " package.",
|
2022-10-30 14:31:45 +01:00
|
|
|
"\nTry to install with install.packages().",
|
|
|
|
call. = FALSE
|
|
|
|
)
|
2022-10-14 15:45:20 +02:00
|
|
|
} else {
|
|
|
|
return(invisible())
|
|
|
|
}
|
2019-03-26 14:24:03 +01:00
|
|
|
}
|
2019-05-10 16:44:59 +02:00
|
|
|
|
2021-10-05 09:58:08 +02:00
|
|
|
pkg_is_available <- function(pkg, also_load = TRUE, min_version = NULL) {
|
2021-05-21 20:20:51 +02:00
|
|
|
if (also_load == TRUE) {
|
2021-08-30 15:43:12 +02:00
|
|
|
out <- suppressWarnings(require(pkg, character.only = TRUE, warn.conflicts = FALSE))
|
2021-05-21 20:20:51 +02:00
|
|
|
} else {
|
|
|
|
out <- requireNamespace(pkg, quietly = TRUE)
|
|
|
|
}
|
2021-10-05 09:58:08 +02:00
|
|
|
if (!is.null(min_version)) {
|
2021-10-06 16:22:36 +02:00
|
|
|
out <- out && utils::packageVersion(pkg) >= min_version
|
2021-10-05 09:58:08 +02:00
|
|
|
}
|
2021-05-21 20:20:51 +02:00
|
|
|
isTRUE(out)
|
|
|
|
}
|
|
|
|
|
2020-08-10 11:44:58 +02:00
|
|
|
import_fn <- function(name, pkg, error_on_fail = TRUE) {
|
|
|
|
if (isTRUE(error_on_fail)) {
|
|
|
|
stop_ifnot_installed(pkg)
|
|
|
|
}
|
2020-07-08 14:48:06 +02:00
|
|
|
tryCatch(
|
2022-08-28 10:31:50 +02:00
|
|
|
# don't use get() to avoid fetching non-API functions
|
2020-12-17 16:22:25 +01:00
|
|
|
getExportedValue(name = name, ns = asNamespace(pkg)),
|
2020-08-10 11:44:58 +02:00
|
|
|
error = function(e) {
|
|
|
|
if (isTRUE(error_on_fail)) {
|
2020-12-17 16:22:25 +01:00
|
|
|
stop_("function ", name, "() is not an exported object from package '", pkg,
|
2022-12-30 12:57:27 +01:00
|
|
|
"'. Please create an issue at ", font_url("https://github.com/msberends/AMR/issues"), ". Many thanks!",
|
2022-08-28 10:31:50 +02:00
|
|
|
call = FALSE
|
|
|
|
)
|
2020-08-10 11:44:58 +02:00
|
|
|
} else {
|
|
|
|
return(NULL)
|
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
}
|
|
|
|
)
|
2020-06-17 15:14:37 +02:00
|
|
|
}
|
|
|
|
|
2020-11-10 16:35:56 +01:00
|
|
|
# this alternative wrapper to the message(), warning() and stop() functions:
|
2020-10-26 12:23:03 +01:00
|
|
|
# - wraps text to never break lines within words
|
|
|
|
# - ignores formatted text while wrapping
|
2020-12-17 16:22:25 +01:00
|
|
|
# - adds indentation dependent on the type of message (such as NOTE)
|
2020-11-10 16:35:56 +01:00
|
|
|
# - can add additional formatting functions like blue or bold text
|
|
|
|
word_wrap <- function(...,
|
2022-08-28 10:31:50 +02:00
|
|
|
add_fn = list(),
|
2020-11-10 16:35:56 +01:00
|
|
|
as_note = FALSE,
|
|
|
|
width = 0.95 * getOption("width"),
|
|
|
|
extra_indent = 0) {
|
2020-10-26 12:23:03 +01:00
|
|
|
msg <- paste0(c(...), collapse = "")
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2020-10-26 15:53:31 +01:00
|
|
|
if (isTRUE(as_note)) {
|
2022-10-05 09:12:22 +02:00
|
|
|
msg <- paste0(AMR_env$info_icon, " ", gsub("^note:? ?", "", msg, ignore.case = TRUE))
|
2020-10-26 15:53:31 +01:00
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2020-12-22 00:51:17 +01:00
|
|
|
if (msg %like% "\n") {
|
|
|
|
# run word_wraps() over every line here, bind them and return again
|
2022-08-28 10:31:50 +02:00
|
|
|
return(paste0(vapply(
|
|
|
|
FUN.VALUE = character(1),
|
2022-10-05 09:12:22 +02:00
|
|
|
trimws(unlist(strsplit(msg, "\n", fixed = TRUE)), which = "right"),
|
2022-08-28 10:31:50 +02:00
|
|
|
word_wrap,
|
|
|
|
add_fn = add_fn,
|
|
|
|
as_note = FALSE,
|
|
|
|
width = width,
|
|
|
|
extra_indent = extra_indent
|
|
|
|
),
|
|
|
|
collapse = "\n"
|
|
|
|
))
|
|
|
|
}
|
|
|
|
|
2021-05-19 22:55:42 +02:00
|
|
|
# correct for operators (will add the space later on)
|
|
|
|
ops <- "([,./><\\]\\[])"
|
|
|
|
msg <- gsub(paste0(ops, " ", ops), "\\1\\2", msg, perl = TRUE)
|
2020-10-26 12:23:03 +01:00
|
|
|
# we need to correct for already applied style, that adds text like "\033[31m\"
|
|
|
|
msg_stripped <- font_stripstyle(msg)
|
|
|
|
# where are the spaces now?
|
|
|
|
msg_stripped_wrapped <- paste0(strwrap(msg_stripped,
|
2022-08-28 10:31:50 +02:00
|
|
|
simplify = TRUE,
|
|
|
|
width = width
|
|
|
|
),
|
|
|
|
collapse = "\n"
|
|
|
|
)
|
2020-11-10 16:35:56 +01:00
|
|
|
msg_stripped_wrapped <- paste0(unlist(strsplit(msg_stripped_wrapped, "(\n|\\*\\|\\*)")),
|
2022-08-28 10:31:50 +02:00
|
|
|
collapse = "\n"
|
|
|
|
)
|
2022-10-05 09:12:22 +02:00
|
|
|
msg_stripped_spaces <- which(unlist(strsplit(msg_stripped, "", fixed = TRUE)) == " ")
|
|
|
|
msg_stripped_wrapped_spaces <- which(unlist(strsplit(msg_stripped_wrapped, "", fixed = TRUE)) != "\n")
|
2020-10-26 12:23:03 +01:00
|
|
|
# so these are the indices of spaces that need to be replaced
|
|
|
|
replace_spaces <- which(!msg_stripped_spaces %in% msg_stripped_wrapped_spaces)
|
|
|
|
# put it together
|
2022-10-05 09:12:22 +02:00
|
|
|
msg <- unlist(strsplit(msg, " ", fixed = TRUE))
|
2020-10-26 12:23:03 +01:00
|
|
|
msg[replace_spaces] <- paste0(msg[replace_spaces], "\n")
|
2021-05-19 22:55:42 +02:00
|
|
|
# add space around operators again
|
|
|
|
msg <- gsub(paste0(ops, ops), "\\1 \\2", msg, perl = TRUE)
|
2020-10-26 12:23:03 +01:00
|
|
|
msg <- paste0(msg, collapse = " ")
|
|
|
|
msg <- gsub("\n ", "\n", msg, fixed = TRUE)
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2021-04-26 23:57:37 +02:00
|
|
|
if (msg_stripped %like% "\u2139 ") {
|
|
|
|
indentation <- 2 + extra_indent
|
2020-10-27 15:56:51 +01:00
|
|
|
} else if (msg_stripped %like% "^=> ") {
|
2020-11-10 16:35:56 +01:00
|
|
|
indentation <- 3 + extra_indent
|
2020-10-26 12:23:03 +01:00
|
|
|
} else {
|
2020-11-10 16:35:56 +01:00
|
|
|
indentation <- 0 + extra_indent
|
2020-10-26 12:23:03 +01:00
|
|
|
}
|
|
|
|
msg <- gsub("\n", paste0("\n", strrep(" ", indentation)), msg, fixed = TRUE)
|
2020-11-10 19:59:14 +01:00
|
|
|
# remove trailing empty characters
|
|
|
|
msg <- gsub("(\n| )+$", "", msg)
|
2021-05-19 22:55:42 +02:00
|
|
|
|
2020-10-26 12:23:03 +01:00
|
|
|
if (length(add_fn) > 0) {
|
|
|
|
if (!is.list(add_fn)) {
|
|
|
|
add_fn <- list(add_fn)
|
|
|
|
}
|
|
|
|
for (i in seq_len(length(add_fn))) {
|
|
|
|
msg <- add_fn[[i]](msg)
|
|
|
|
}
|
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2020-12-01 16:59:57 +01:00
|
|
|
# format backticks
|
2022-11-24 20:29:00 +01:00
|
|
|
msg <- gsub("`(.+?)`", font_grey_bg("\\1"), msg)
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2021-07-12 12:28:41 +02:00
|
|
|
# clean introduced whitespace between fullstops
|
|
|
|
msg <- gsub("[.] +[.]", "..", msg)
|
2022-10-20 16:08:01 +02:00
|
|
|
# remove extra space that was introduced (e.g. "Smith et al., 2022")
|
2022-10-05 09:12:22 +02:00
|
|
|
msg <- gsub(". ,", ".,", msg, fixed = TRUE)
|
2022-10-20 16:08:01 +02:00
|
|
|
msg <- gsub("[ ,", "[,", msg, fixed = TRUE)
|
2022-12-30 12:57:27 +01:00
|
|
|
msg <- gsub("/ /", "//", msg, fixed = TRUE)
|
2022-10-30 14:31:45 +01:00
|
|
|
|
2020-11-10 16:35:56 +01:00
|
|
|
msg
|
|
|
|
}
|
|
|
|
|
|
|
|
message_ <- function(...,
|
|
|
|
appendLF = TRUE,
|
|
|
|
add_fn = list(font_blue),
|
|
|
|
as_note = TRUE) {
|
2022-08-28 10:31:50 +02:00
|
|
|
message(word_wrap(...,
|
|
|
|
add_fn = add_fn,
|
|
|
|
as_note = as_note
|
|
|
|
),
|
|
|
|
appendLF = appendLF
|
|
|
|
)
|
2020-11-10 16:35:56 +01:00
|
|
|
}
|
|
|
|
|
|
|
|
warning_ <- function(...,
|
|
|
|
add_fn = list(),
|
|
|
|
immediate = FALSE,
|
2022-03-02 15:38:55 +01:00
|
|
|
call = FALSE) {
|
2022-08-28 10:31:50 +02:00
|
|
|
warning(word_wrap(...,
|
|
|
|
add_fn = add_fn,
|
|
|
|
as_note = FALSE
|
|
|
|
),
|
|
|
|
immediate. = immediate,
|
|
|
|
call. = call
|
|
|
|
)
|
2020-10-26 12:23:03 +01:00
|
|
|
}
|
|
|
|
|
|
|
|
# this alternative to the stop() function:
|
|
|
|
# - adds the function name where the error was thrown
|
|
|
|
# - wraps text to never break lines within words
|
2020-07-01 11:07:01 +02:00
|
|
|
stop_ <- function(..., call = TRUE) {
|
2020-11-28 22:15:44 +01:00
|
|
|
msg <- paste0(c(...), collapse = "")
|
2020-07-01 11:07:01 +02:00
|
|
|
if (!isFALSE(call)) {
|
|
|
|
if (isTRUE(call)) {
|
|
|
|
call <- as.character(sys.call(-1)[1])
|
|
|
|
} else {
|
|
|
|
# so you can go back more than 1 call, as used in rsi_calc(), that now throws a reference to e.g. n_rsi()
|
|
|
|
call <- as.character(sys.call(call)[1])
|
|
|
|
}
|
|
|
|
msg <- paste0("in ", call, "(): ", msg)
|
|
|
|
}
|
2020-11-28 22:15:44 +01:00
|
|
|
msg <- word_wrap(msg, add_fn = list(), as_note = FALSE)
|
2020-07-01 11:07:01 +02:00
|
|
|
stop(msg, call. = FALSE)
|
|
|
|
}
|
|
|
|
|
2020-06-22 11:18:40 +02:00
|
|
|
stop_if <- function(expr, ..., call = TRUE) {
|
|
|
|
if (isTRUE(expr)) {
|
2020-07-01 11:07:01 +02:00
|
|
|
if (isTRUE(call)) {
|
|
|
|
call <- -1
|
|
|
|
}
|
2020-06-26 10:21:22 +02:00
|
|
|
if (!isFALSE(call)) {
|
2020-07-01 11:07:01 +02:00
|
|
|
# since we're calling stop_(), which is another call
|
|
|
|
call <- call - 1
|
2020-06-26 10:21:22 +02:00
|
|
|
}
|
2020-07-01 11:07:01 +02:00
|
|
|
stop_(..., call = call)
|
2020-03-08 11:18:59 +01:00
|
|
|
}
|
|
|
|
}
|
|
|
|
|
2020-06-22 11:18:40 +02:00
|
|
|
stop_ifnot <- function(expr, ..., call = TRUE) {
|
2020-09-24 00:30:11 +02:00
|
|
|
if (isFALSE(expr)) {
|
2020-07-01 11:07:01 +02:00
|
|
|
if (isTRUE(call)) {
|
|
|
|
call <- -1
|
|
|
|
}
|
2020-06-26 10:21:22 +02:00
|
|
|
if (!isFALSE(call)) {
|
2020-07-01 11:07:01 +02:00
|
|
|
# since we're calling stop_(), which is another call
|
|
|
|
call <- call - 1
|
2020-06-26 10:21:22 +02:00
|
|
|
}
|
2020-07-01 11:07:01 +02:00
|
|
|
stop_(..., call = call)
|
2020-06-22 11:18:40 +02:00
|
|
|
}
|
|
|
|
}
|
2020-03-08 11:18:59 +01:00
|
|
|
|
2019-05-20 19:12:41 +02:00
|
|
|
"%or%" <- function(x, y) {
|
2022-10-05 09:12:22 +02:00
|
|
|
if (is.null(x) || is.null(y)) {
|
2019-06-16 21:42:40 +02:00
|
|
|
if (is.null(x)) {
|
|
|
|
return(y)
|
|
|
|
} else {
|
|
|
|
return(x)
|
|
|
|
}
|
|
|
|
}
|
2022-10-05 09:12:22 +02:00
|
|
|
ifelse(is.na(x), y, x)
|
2019-05-20 19:12:41 +02:00
|
|
|
}
|
2019-08-26 16:02:03 +02:00
|
|
|
|
2021-05-03 13:06:43 +02:00
|
|
|
return_after_integrity_check <- function(value, type, check_vector) {
|
2019-08-26 16:02:03 +02:00
|
|
|
if (!all(value[!is.na(value)] %in% check_vector)) {
|
2022-03-02 15:38:55 +01:00
|
|
|
warning_(paste0("invalid ", type, ", NA generated"))
|
2019-08-26 16:02:03 +02:00
|
|
|
value[!value %in% check_vector] <- NA
|
|
|
|
}
|
|
|
|
value
|
|
|
|
}
|
2020-01-27 19:14:23 +01:00
|
|
|
|
2022-08-27 20:49:37 +02:00
|
|
|
# transforms data set to a tibble with only ASCII values, to comply with CRAN policies
|
2020-01-27 19:14:23 +01:00
|
|
|
dataset_UTF8_to_ASCII <- function(df) {
|
|
|
|
trans <- function(vect) {
|
|
|
|
iconv(vect, from = "UTF-8", to = "ASCII//TRANSLIT")
|
|
|
|
}
|
|
|
|
df <- as.data.frame(df, stringsAsFactors = FALSE)
|
|
|
|
for (i in seq_len(NCOL(df))) {
|
|
|
|
col <- df[, i]
|
|
|
|
if (is.list(col)) {
|
|
|
|
col <- lapply(col, function(j) trans(j))
|
|
|
|
df[, i] <- list(col)
|
|
|
|
} else {
|
|
|
|
if (is.factor(col)) {
|
|
|
|
levels(col) <- trans(levels(col))
|
|
|
|
} else if (is.character(col)) {
|
|
|
|
col <- trans(col)
|
|
|
|
} else {
|
|
|
|
col
|
|
|
|
}
|
|
|
|
df[, i] <- col
|
|
|
|
}
|
|
|
|
}
|
2022-08-28 19:34:04 +02:00
|
|
|
import_fn("as_tibble", "tibble")(df)
|
2020-01-27 19:14:23 +01:00
|
|
|
}
|
2020-05-16 13:05:47 +02:00
|
|
|
|
2022-10-05 09:12:22 +02:00
|
|
|
documentation_date <- function(d) {
|
|
|
|
paste0(trimws(format(d, "%e")), " ", month.name[as.integer(format(d, "%m"))], ", ", format(d, "%Y"))
|
|
|
|
}
|
|
|
|
|
|
|
|
format_included_data_number <- function(data) {
|
|
|
|
if (is.data.frame(data)) {
|
|
|
|
n <- nrow(data)
|
|
|
|
} else {
|
|
|
|
n <- length(unique(data))
|
|
|
|
}
|
|
|
|
if (n > 10000) {
|
|
|
|
rounder <- -3 # round on thousands
|
|
|
|
} else if (n > 1000) {
|
|
|
|
rounder <- -2 # round on hundreds
|
|
|
|
} else {
|
|
|
|
rounder <- -1 # round on tens
|
|
|
|
}
|
|
|
|
paste0("~", format(round(n, rounder), decimal.mark = ".", big.mark = ","))
|
|
|
|
}
|
|
|
|
|
2020-11-28 22:15:44 +01:00
|
|
|
# for eucast_rules() and mdro(), creates markdown output with URLs and names
|
2021-05-18 11:29:31 +02:00
|
|
|
create_eucast_ab_documentation <- function() {
|
2022-10-05 09:12:22 +02:00
|
|
|
x <- trimws(unique(toupper(unlist(strsplit(EUCAST_RULES_DF$then_change_these_antibiotics, ",", fixed = TRUE)))))
|
2021-05-18 11:29:31 +02:00
|
|
|
ab <- character()
|
|
|
|
for (val in x) {
|
2021-08-17 14:34:11 +02:00
|
|
|
if (paste0("AB_", val) %in% ls(envir = asNamespace("AMR"))) {
|
2022-08-28 10:31:50 +02:00
|
|
|
# antibiotic group names, as defined in data-raw/_pre_commit_hook.R, such as `CARBAPENEMS`
|
2021-08-17 14:34:11 +02:00
|
|
|
val <- eval(parse(text = paste0("AB_", val)), envir = asNamespace("AMR"))
|
2022-10-14 13:02:50 +02:00
|
|
|
} else if (val %in% AMR_env$AB_lookup$ab) {
|
2021-05-18 11:29:31 +02:00
|
|
|
# separate drugs, such as `AMX`
|
|
|
|
val <- as.ab(val)
|
|
|
|
} else {
|
2021-05-20 00:07:27 +02:00
|
|
|
val <- as.rsi(NA)
|
2021-05-18 11:29:31 +02:00
|
|
|
}
|
|
|
|
ab <- c(ab, val)
|
|
|
|
}
|
|
|
|
ab <- unique(ab)
|
2021-08-17 14:34:11 +02:00
|
|
|
atcs <- ab_atc(ab, only_first = TRUE)
|
2021-05-18 11:29:31 +02:00
|
|
|
# only keep ABx with an ATC code:
|
|
|
|
ab <- ab[!is.na(atcs)]
|
2020-09-24 00:30:11 +02:00
|
|
|
ab_names <- ab_name(ab, language = NULL, tolower = TRUE)
|
|
|
|
ab <- ab[order(ab_names)]
|
|
|
|
ab_names <- ab_names[order(ab_names)]
|
2021-05-18 11:29:31 +02:00
|
|
|
atc_txt <- paste0("[", atcs[!is.na(atcs)], "](", ab_url(ab), ")")
|
|
|
|
out <- paste0(ab_names, " (`", ab, "`, ", atc_txt, ")", collapse = ", ")
|
2020-09-24 00:30:11 +02:00
|
|
|
substr(out, 1, 1) <- toupper(substr(out, 1, 1))
|
|
|
|
out
|
|
|
|
}
|
|
|
|
|
2021-08-16 21:54:34 +02:00
|
|
|
vector_or <- function(v, quotes = TRUE, reverse = FALSE, sort = TRUE, initial_captital = FALSE, last_sep = " or ") {
|
2021-01-12 22:08:04 +01:00
|
|
|
# makes unique and sorts, and this also removed NAs
|
2021-02-04 16:48:16 +01:00
|
|
|
v <- unique(v)
|
|
|
|
if (isTRUE(sort)) {
|
|
|
|
v <- sort(v)
|
2021-01-12 22:08:04 +01:00
|
|
|
}
|
2021-02-04 16:48:16 +01:00
|
|
|
if (isTRUE(reverse)) {
|
2021-01-12 22:08:04 +01:00
|
|
|
v <- rev(v)
|
|
|
|
}
|
2021-01-25 21:58:00 +01:00
|
|
|
if (isTRUE(quotes)) {
|
|
|
|
quotes <- '"'
|
|
|
|
} else if (isFALSE(quotes)) {
|
|
|
|
quotes <- ""
|
2021-02-04 16:48:16 +01:00
|
|
|
} else {
|
|
|
|
quotes <- quotes[1L]
|
|
|
|
}
|
2021-08-16 21:54:34 +02:00
|
|
|
if (isTRUE(initial_captital)) {
|
|
|
|
v[1] <- gsub("^([a-z])", "\\U\\1", v[1], perl = TRUE)
|
|
|
|
}
|
2022-04-08 11:02:45 +02:00
|
|
|
if (length(v) <= 1) {
|
2021-02-04 16:48:16 +01:00
|
|
|
return(paste0(quotes, v, quotes))
|
|
|
|
}
|
|
|
|
if (identical(v, c("I", "R", "S"))) {
|
2022-10-19 11:47:57 +02:00
|
|
|
# class 'rsi' should be sorted like this
|
2021-02-04 16:48:16 +01:00
|
|
|
v <- c("R", "S", "I")
|
2021-01-25 21:58:00 +01:00
|
|
|
}
|
2021-01-12 22:08:04 +01:00
|
|
|
# all commas except for last item, so will become '"val1", "val2", "val3" or "val4"'
|
2022-08-28 10:31:50 +02:00
|
|
|
paste0(
|
|
|
|
paste0(quotes, v[seq_len(length(v) - 1)], quotes, collapse = ", "),
|
|
|
|
last_sep, paste0(quotes, v[length(v)], quotes)
|
|
|
|
)
|
2021-01-12 22:08:04 +01:00
|
|
|
}
|
|
|
|
|
2021-08-16 21:54:34 +02:00
|
|
|
vector_and <- function(v, quotes = TRUE, reverse = FALSE, sort = TRUE, initial_captital = FALSE) {
|
2022-08-28 10:31:50 +02:00
|
|
|
vector_or(
|
|
|
|
v = v, quotes = quotes, reverse = reverse, sort = sort,
|
|
|
|
initial_captital = initial_captital, last_sep = " and "
|
|
|
|
)
|
2021-02-04 16:48:16 +01:00
|
|
|
}
|
|
|
|
|
2021-05-12 18:15:03 +02:00
|
|
|
format_class <- function(class, plural = FALSE) {
|
2021-01-18 16:57:56 +01:00
|
|
|
class.bak <- class
|
2021-01-24 14:48:56 +01:00
|
|
|
class[class == "numeric"] <- "number"
|
2021-01-18 16:57:56 +01:00
|
|
|
class[class == "integer"] <- "whole number"
|
2021-01-24 14:48:56 +01:00
|
|
|
if (all(c("numeric", "integer") %in% class.bak, na.rm = TRUE)) {
|
2021-01-18 16:57:56 +01:00
|
|
|
class[class %in% c("number", "whole number")] <- "(whole) number"
|
|
|
|
}
|
|
|
|
class[class == "character"] <- "text string"
|
2022-10-05 09:12:22 +02:00
|
|
|
class[class == "Date"] <- "date"
|
|
|
|
class[class %in% c("POSIXt", "POSIXct", "POSIXlt")] <- "date/time"
|
2022-08-28 10:31:50 +02:00
|
|
|
class[class != class.bak] <- paste0(
|
|
|
|
ifelse(plural, "", "a "),
|
|
|
|
class[class != class.bak],
|
|
|
|
ifelse(plural, "s", "")
|
|
|
|
)
|
2021-01-18 16:57:56 +01:00
|
|
|
# exceptions
|
|
|
|
class[class == "logical"] <- ifelse(plural, "a vector of `TRUE`/`FALSE`", "`TRUE` or `FALSE`")
|
2021-05-12 18:15:03 +02:00
|
|
|
class[class == "data.frame"] <- "a data set"
|
2021-01-18 16:57:56 +01:00
|
|
|
if ("list" %in% class) {
|
|
|
|
class <- "a list"
|
|
|
|
}
|
|
|
|
if ("matrix" %in% class) {
|
|
|
|
class <- "a matrix"
|
|
|
|
}
|
2021-04-07 08:37:42 +02:00
|
|
|
if ("custom_eucast_rules" %in% class) {
|
|
|
|
class <- "input created with `custom_eucast_rules()`"
|
2021-01-22 10:55:07 +01:00
|
|
|
}
|
2021-03-08 09:44:17 +01:00
|
|
|
if (any(c("mo", "ab", "rsi") %in% class)) {
|
2021-01-22 10:55:07 +01:00
|
|
|
class <- paste0("of class <", class[1L], ">")
|
2021-01-18 16:57:56 +01:00
|
|
|
}
|
2021-01-22 10:55:07 +01:00
|
|
|
class[class == class.bak] <- paste0("of class <", class[class == class.bak], ">")
|
2021-01-18 16:57:56 +01:00
|
|
|
# output
|
2021-03-08 09:44:17 +01:00
|
|
|
vector_or(class, quotes = FALSE, sort = FALSE)
|
2021-01-18 16:57:56 +01:00
|
|
|
}
|
|
|
|
|
2020-10-19 17:09:19 +02:00
|
|
|
# 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,
|
2021-01-24 14:48:56 +01:00
|
|
|
is_positive = NULL,
|
2021-04-07 08:37:42 +02:00
|
|
|
is_positive_or_zero = NULL,
|
2021-01-24 14:48:56 +01:00
|
|
|
is_finite = NULL,
|
2020-10-19 17:09:19 +02:00
|
|
|
contains_column_class = NULL,
|
|
|
|
allow_NULL = FALSE,
|
|
|
|
allow_NA = FALSE,
|
|
|
|
ignore.case = FALSE,
|
|
|
|
.call_depth = 0) { # depth in calling
|
2020-10-26 12:23:03 +01:00
|
|
|
|
2020-10-19 17:09:19 +02:00
|
|
|
obj_name <- deparse(substitute(object))
|
|
|
|
call_depth <- -2 - abs(.call_depth)
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2021-01-24 14:48:56 +01:00
|
|
|
# if object is missing, or another error:
|
|
|
|
tryCatch(invisible(object),
|
2022-10-05 09:12:22 +02:00
|
|
|
error = function(e) AMR_env$meet_criteria_error_txt <- e$message
|
2022-08-28 10:31:50 +02:00
|
|
|
)
|
2022-10-05 09:12:22 +02:00
|
|
|
if (!is.null(AMR_env$meet_criteria_error_txt)) {
|
|
|
|
error_txt <- AMR_env$meet_criteria_error_txt
|
|
|
|
AMR_env$meet_criteria_error_txt <- NULL
|
2022-08-27 20:49:37 +02:00
|
|
|
stop(error_txt, call. = FALSE) # don't use stop_() here, our pkg may not be loaded yet
|
2021-01-24 14:48:56 +01:00
|
|
|
}
|
2022-10-05 09:12:22 +02:00
|
|
|
AMR_env$meet_criteria_error_txt <- NULL
|
2020-10-26 12:23:03 +01:00
|
|
|
|
2020-10-19 17:09:19 +02:00
|
|
|
if (is.null(object)) {
|
|
|
|
stop_if(allow_NULL == FALSE, "argument `", obj_name, "` must not be NULL", call = call_depth)
|
|
|
|
return(invisible())
|
|
|
|
}
|
2021-01-04 12:29:25 +01:00
|
|
|
if (is.null(dim(object)) && length(object) == 1 && suppressWarnings(is.na(object))) { # suppressWarnings for functions
|
2020-10-19 17:09:19 +02:00
|
|
|
stop_if(allow_NA == FALSE, "argument `", obj_name, "` must not be NA", call = call_depth)
|
|
|
|
return(invisible())
|
|
|
|
}
|
2020-10-26 12:23:03 +01:00
|
|
|
|
2020-10-19 17:09:19 +02:00
|
|
|
if (!is.null(allow_class)) {
|
2020-10-26 12:23:03 +01:00
|
|
|
stop_ifnot(inherits(object, allow_class), "argument `", obj_name,
|
2022-08-28 10:31:50 +02:00
|
|
|
"` must be ", format_class(allow_class, plural = isTRUE(has_length > 1)),
|
|
|
|
", i.e. not be ", format_class(class(object), plural = isTRUE(has_length > 1)),
|
|
|
|
call = call_depth
|
|
|
|
)
|
2020-10-19 17:09:19 +02:00
|
|
|
# check data.frames for data
|
|
|
|
if (inherits(object, "data.frame")) {
|
2020-10-26 12:23:03 +01:00
|
|
|
stop_if(any(dim(object) == 0),
|
2022-08-28 10:31:50 +02:00
|
|
|
"the data provided in argument `", obj_name,
|
|
|
|
"` must contain rows and columns (current dimensions: ",
|
|
|
|
paste(dim(object), collapse = "x"), ")",
|
|
|
|
call = call_depth
|
|
|
|
)
|
2020-10-19 17:09:19 +02:00
|
|
|
}
|
|
|
|
}
|
|
|
|
if (!is.null(has_length)) {
|
2020-10-26 12:23:03 +01:00
|
|
|
stop_ifnot(length(object) %in% has_length, "argument `", obj_name,
|
2022-08-28 10:31:50 +02:00
|
|
|
"` must ", # ifelse(allow_NULL, "be NULL or must ", ""),
|
|
|
|
"be of length ", vector_or(has_length, quotes = FALSE),
|
|
|
|
", not ", length(object),
|
|
|
|
call = call_depth
|
|
|
|
)
|
2020-10-19 17:09:19 +02:00
|
|
|
}
|
|
|
|
if (!is.null(looks_like)) {
|
2020-10-26 12:23:03 +01:00
|
|
|
stop_ifnot(object %like% looks_like, "argument `", obj_name,
|
2022-08-28 10:31:50 +02:00
|
|
|
"` must ", # ifelse(allow_NULL, "be NULL or must ", ""),
|
|
|
|
"resemble the regular expression \"", looks_like, "\"",
|
|
|
|
call = call_depth
|
|
|
|
)
|
2020-10-19 17:09:19 +02:00
|
|
|
}
|
|
|
|
if (!is.null(is_in)) {
|
|
|
|
if (ignore.case == TRUE) {
|
|
|
|
object <- tolower(object)
|
|
|
|
is_in <- tolower(is_in)
|
|
|
|
}
|
2021-05-18 11:29:31 +02:00
|
|
|
stop_ifnot(all(object %in% is_in, na.rm = TRUE), "argument `", obj_name, "` ",
|
2022-08-28 10:31:50 +02:00
|
|
|
ifelse(!is.null(has_length) && length(has_length) == 1 && has_length == 1,
|
|
|
|
"must be either ",
|
|
|
|
"must only contain values "
|
|
|
|
),
|
|
|
|
vector_or(is_in, quotes = !isTRUE(any(c("double", "numeric", "integer") %in% allow_class))),
|
|
|
|
ifelse(allow_NA == TRUE, ", or NA", ""),
|
|
|
|
call = call_depth
|
|
|
|
)
|
2020-10-19 17:09:19 +02:00
|
|
|
}
|
2021-04-12 12:35:13 +02:00
|
|
|
if (isTRUE(is_positive)) {
|
2021-01-24 14:48:56 +01:00
|
|
|
stop_if(is.numeric(object) && !all(object > 0, na.rm = TRUE), "argument `", obj_name,
|
2022-08-28 10:31:50 +02:00
|
|
|
"` must ",
|
|
|
|
ifelse(!is.null(has_length) && length(has_length) == 1 && has_length == 1,
|
|
|
|
"be a number higher than zero",
|
|
|
|
"all be numbers higher than zero"
|
|
|
|
),
|
|
|
|
call = call_depth
|
|
|
|
)
|
2021-04-07 08:37:42 +02:00
|
|
|
}
|
2021-04-12 12:35:13 +02:00
|
|
|
if (isTRUE(is_positive_or_zero)) {
|
2021-04-07 08:37:42 +02:00
|
|
|
stop_if(is.numeric(object) && !all(object >= 0, na.rm = TRUE), "argument `", obj_name,
|
2022-08-28 10:31:50 +02:00
|
|
|
"` must ",
|
|
|
|
ifelse(!is.null(has_length) && length(has_length) == 1 && has_length == 1,
|
|
|
|
"be zero or a positive number",
|
|
|
|
"all be zero or numbers higher than zero"
|
|
|
|
),
|
|
|
|
call = call_depth
|
|
|
|
)
|
2021-01-24 14:48:56 +01:00
|
|
|
}
|
2021-04-12 12:35:13 +02:00
|
|
|
if (isTRUE(is_finite)) {
|
2021-01-24 14:48:56 +01:00
|
|
|
stop_if(is.numeric(object) && !all(is.finite(object[!is.na(object)]), na.rm = TRUE), "argument `", obj_name,
|
2022-08-28 10:31:50 +02:00
|
|
|
"` must ",
|
|
|
|
ifelse(!is.null(has_length) && length(has_length) == 1 && has_length == 1,
|
|
|
|
"be a finite number",
|
|
|
|
"all be finite numbers"
|
|
|
|
),
|
|
|
|
" (i.e. not be infinite)",
|
|
|
|
call = call_depth
|
|
|
|
)
|
2021-01-24 14:48:56 +01:00
|
|
|
}
|
2020-10-19 17:09:19 +02:00
|
|
|
if (!is.null(contains_column_class)) {
|
2022-08-28 10:31:50 +02:00
|
|
|
stop_ifnot(any(vapply(
|
|
|
|
FUN.VALUE = logical(1),
|
|
|
|
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
|
|
|
|
)
|
2020-10-19 17:09:19 +02:00
|
|
|
}
|
|
|
|
return(invisible())
|
|
|
|
}
|
|
|
|
|
2021-08-31 17:06:44 +02:00
|
|
|
get_current_data <- function(arg_name, call) {
|
2021-12-11 13:41:31 +01:00
|
|
|
valid_df <- function(x) {
|
|
|
|
!is.null(x) && is.data.frame(x)
|
|
|
|
}
|
2021-01-12 22:08:04 +01:00
|
|
|
# try dplyr::cur_data_all() first to support dplyr groups
|
|
|
|
# only useful for e.g. dplyr::filter(), dplyr::mutate() and dplyr::summarise()
|
2022-10-20 16:08:01 +02:00
|
|
|
# not useful (throws error) with e.g. dplyr::select(), dplyr::across(), or dplyr::vars(),
|
|
|
|
# but that will be caught later on in this function
|
2021-01-12 22:08:04 +01:00
|
|
|
cur_data_all <- import_fn("cur_data_all", "dplyr", error_on_fail = FALSE)
|
|
|
|
if (!is.null(cur_data_all)) {
|
|
|
|
out <- tryCatch(cur_data_all(), error = function(e) NULL)
|
2021-12-11 13:41:31 +01:00
|
|
|
if (valid_df(out)) {
|
|
|
|
return(out)
|
2021-01-04 12:29:25 +01:00
|
|
|
}
|
|
|
|
}
|
2022-10-30 14:31:45 +01:00
|
|
|
|
2021-06-22 12:16:42 +02:00
|
|
|
# try a manual (base R) method, by going over all underlying environments with sys.frames()
|
2021-07-03 21:56:53 +02:00
|
|
|
for (env in sys.frames()) {
|
|
|
|
if (!is.null(env$`.Generic`)) {
|
|
|
|
# don't check `".Generic" %in% names(env)`, because in R < 3.2, `names(env)` is always NULL
|
2022-10-30 14:31:45 +01:00
|
|
|
|
2021-12-11 13:41:31 +01:00
|
|
|
if (valid_df(env$`.data`)) {
|
2021-06-22 12:16:42 +02:00
|
|
|
# an element `.data` will be in the environment when using `dplyr::select()`
|
|
|
|
# (but not when using `dplyr::filter()`, `dplyr::mutate()` or `dplyr::summarise()`)
|
2021-12-11 13:41:31 +01:00
|
|
|
return(env$`.data`)
|
|
|
|
} else if (valid_df(env$xx)) {
|
2021-06-22 12:16:42 +02:00
|
|
|
# an element `xx` will be in the environment for rows + cols, e.g. `example_isolates[c(1:3), carbapenems()]`
|
2021-12-11 13:41:31 +01:00
|
|
|
return(env$xx)
|
|
|
|
} else if (valid_df(env$x)) {
|
2021-06-22 12:16:42 +02:00
|
|
|
# an element `x` will be in the environment for only cols, e.g. `example_isolates[, carbapenems()]`
|
2021-12-11 13:41:31 +01:00
|
|
|
return(env$x)
|
2021-01-03 23:40:05 +01:00
|
|
|
}
|
2022-10-21 15:13:19 +02:00
|
|
|
} else if (!is.null(names(env)) && all(c(".tbl", ".vars", ".cols") %in% names(env), na.rm = TRUE) && valid_df(env$`.tbl`)) {
|
|
|
|
# an element `.tbl` will be in the environment when using scoped dplyr variants, with or without `dplyr::vars()`
|
|
|
|
# (e.g. `dplyr::summarise_at()` or `dplyr::mutate_at()`)
|
2022-10-20 16:08:01 +02:00
|
|
|
return(env$`.tbl`)
|
2021-01-03 23:40:05 +01:00
|
|
|
}
|
|
|
|
}
|
2022-10-30 14:31:45 +01:00
|
|
|
|
2021-06-22 12:16:42 +02:00
|
|
|
# no data.frame found, so an error must be returned:
|
2021-01-03 23:40:05 +01:00
|
|
|
if (is.na(arg_name)) {
|
2021-02-08 14:18:42 +01:00
|
|
|
if (isTRUE(is.numeric(call))) {
|
|
|
|
fn <- as.character(sys.call(call + 1)[1])
|
2022-08-28 10:31:50 +02:00
|
|
|
examples <- paste0(
|
|
|
|
", e.g.:\n",
|
|
|
|
" your_data %>% select(", fn, "())\n",
|
|
|
|
" your_data %>% select(column_a, column_b, ", fn, "())\n",
|
|
|
|
" your_data[, ", fn, "()]\n",
|
|
|
|
' your_data[, c("column_a", "column_b", ', fn, "())]"
|
|
|
|
)
|
2021-02-08 14:18:42 +01:00
|
|
|
} else {
|
|
|
|
examples <- ""
|
|
|
|
}
|
2021-07-23 21:42:11 +02:00
|
|
|
stop_("this function must be used inside a `dplyr` verb or `data.frame` call",
|
2022-08-28 10:31:50 +02:00
|
|
|
examples,
|
|
|
|
call = call
|
|
|
|
)
|
2021-01-03 23:40:05 +01:00
|
|
|
} else {
|
2021-07-23 21:42:11 +02:00
|
|
|
# mimic a base R error that the argument is missing
|
2021-01-12 22:08:04 +01:00
|
|
|
stop_("argument `", arg_name, "` is missing with no default", call = call)
|
2021-01-03 23:40:05 +01:00
|
|
|
}
|
2020-12-07 16:06:42 +01:00
|
|
|
}
|
|
|
|
|
2021-02-02 23:57:35 +01:00
|
|
|
get_current_column <- function() {
|
|
|
|
# try dplyr::cur_columns() first
|
|
|
|
cur_column <- import_fn("cur_column", "dplyr", error_on_fail = FALSE)
|
|
|
|
if (!is.null(cur_column)) {
|
|
|
|
out <- tryCatch(cur_column(), error = function(e) NULL)
|
|
|
|
if (!is.null(out)) {
|
|
|
|
return(out)
|
|
|
|
}
|
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2021-07-03 21:56:53 +02:00
|
|
|
# cur_column() doesn't always work (only allowed for certain conditions set by dplyr), but it's probably still possible:
|
|
|
|
frms <- lapply(sys.frames(), function(env) {
|
|
|
|
if (!is.null(env$i)) {
|
|
|
|
if (!is.null(env$tibble_vars)) {
|
2021-02-02 23:57:35 +01:00
|
|
|
# for mutate_if()
|
2021-07-03 21:56:53 +02:00
|
|
|
env$tibble_vars[env$i]
|
2021-02-02 23:57:35 +01:00
|
|
|
} else {
|
|
|
|
# for mutate(across())
|
|
|
|
df <- tryCatch(get_current_data(NA, 0), error = function(e) NULL)
|
|
|
|
if (is.data.frame(df)) {
|
2021-07-03 21:56:53 +02:00
|
|
|
colnames(df)[env$i]
|
2021-02-02 23:57:35 +01:00
|
|
|
} else {
|
2021-07-03 21:56:53 +02:00
|
|
|
env$i
|
2021-02-02 23:57:35 +01:00
|
|
|
}
|
|
|
|
}
|
|
|
|
} else {
|
|
|
|
NULL
|
|
|
|
}
|
|
|
|
})
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2021-02-02 23:57:35 +01:00
|
|
|
vars <- unlist(frms)
|
|
|
|
if (length(vars) > 0) {
|
|
|
|
vars[length(vars)]
|
|
|
|
} else {
|
|
|
|
# not found, so:
|
|
|
|
NULL
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
2021-02-08 14:18:42 +01:00
|
|
|
is_null_or_grouped_tbl <- function(x) {
|
2021-07-03 21:56:53 +02:00
|
|
|
# class "grouped_df" might change at one point, so only set in one place; here.
|
2021-02-08 21:09:36 +01:00
|
|
|
is.null(x) || inherits(x, "grouped_df")
|
2021-02-08 14:18:42 +01:00
|
|
|
}
|
|
|
|
|
2021-12-11 13:41:31 +01:00
|
|
|
unique_call_id <- function(entire_session = FALSE, match_fn = NULL) {
|
2021-01-03 23:40:05 +01:00
|
|
|
if (entire_session == TRUE) {
|
2021-12-11 13:41:31 +01:00
|
|
|
return(c(envir = "session", call = "session"))
|
2021-01-03 23:40:05 +01:00
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2021-12-11 13:41:31 +01:00
|
|
|
# combination of environment ID (such as "0x7fed4ee8c848")
|
|
|
|
# and relevant system call (where 'match_fn' is being called in)
|
|
|
|
calls <- sys.calls()
|
2022-10-05 09:12:22 +02:00
|
|
|
in_test <- any(as.character(calls[[1]]) %like_case% "run_test_dir|run_test_file|test_all|tinytest|test_package|testthat", na.rm = TRUE)
|
|
|
|
if (!isTRUE(in_test)) {
|
2021-12-11 15:13:44 +01:00
|
|
|
for (i in seq_len(length(calls))) {
|
|
|
|
call_clean <- gsub("[^a-zA-Z0-9_().-]", "", as.character(calls[[i]]), perl = TRUE)
|
2022-11-24 20:29:00 +01:00
|
|
|
if (match_fn %in% call_clean || any(call_clean %like% paste0(match_fn, "\\("), na.rm = TRUE)) {
|
2022-08-28 10:31:50 +02:00
|
|
|
return(c(
|
|
|
|
envir = gsub("<environment: (.*)>", "\\1", utils::capture.output(sys.frames()[[1]]), perl = TRUE),
|
|
|
|
call = paste0(deparse(calls[[i]]), collapse = "")
|
|
|
|
))
|
2021-12-11 15:13:44 +01:00
|
|
|
}
|
|
|
|
}
|
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
c(
|
2022-10-05 09:12:22 +02:00
|
|
|
envir = paste0(sample(c(0:9, letters[1:6]), size = 32, replace = TRUE), collapse = ""),
|
|
|
|
call = paste0(sample(c(0:9, letters[1:6]), size = 32, replace = TRUE), collapse = "")
|
2022-08-28 10:31:50 +02:00
|
|
|
)
|
2020-12-24 23:29:10 +01:00
|
|
|
}
|
|
|
|
|
2021-12-11 13:41:31 +01:00
|
|
|
#' @noRd
|
|
|
|
#' @param fn name of the function as a character
|
|
|
|
#' @param ... character elements to be pasted together as a 'salt'
|
|
|
|
#' @param entire_session show message once per session
|
|
|
|
message_not_thrown_before <- function(fn, ..., entire_session = FALSE) {
|
2021-08-16 21:54:34 +02:00
|
|
|
# this is to prevent that messages/notes will be printed for every dplyr group or more than once per session
|
2022-08-27 20:49:37 +02:00
|
|
|
# e.g. this would show a msg 4 times: example_isolates %>% group_by(ward) %>% filter(mo_is_gram_negative())
|
2022-10-05 09:12:22 +02:00
|
|
|
salt <- gsub("[^a-zA-Z0-9|_-]", "?", substr(paste(c(...), sep = "|", collapse = "|"), 1, 512), perl = TRUE)
|
|
|
|
not_thrown_before <- is.null(AMR_env[[paste0("thrown_msg.", fn, ".", salt)]]) ||
|
2022-08-28 10:31:50 +02:00
|
|
|
!identical(
|
2022-10-05 09:12:22 +02:00
|
|
|
AMR_env[[paste0("thrown_msg.", fn, ".", salt)]],
|
2022-08-28 10:31:50 +02:00
|
|
|
unique_call_id(
|
|
|
|
entire_session = entire_session,
|
|
|
|
match_fn = fn
|
|
|
|
)
|
|
|
|
)
|
2021-08-16 21:54:34 +02:00
|
|
|
if (isTRUE(not_thrown_before)) {
|
2021-07-23 21:42:11 +02:00
|
|
|
# message was not thrown before - remember this so on the next run it will return FALSE:
|
2022-08-28 10:31:50 +02:00
|
|
|
assign(
|
|
|
|
x = paste0("thrown_msg.", fn, ".", salt),
|
|
|
|
value = unique_call_id(entire_session = entire_session, match_fn = fn),
|
2022-10-05 09:12:22 +02:00
|
|
|
envir = AMR_env
|
2022-08-28 10:31:50 +02:00
|
|
|
)
|
2021-07-23 21:42:11 +02:00
|
|
|
}
|
2021-08-16 21:54:34 +02:00
|
|
|
not_thrown_before
|
2020-12-27 00:07:00 +01:00
|
|
|
}
|
|
|
|
|
2020-06-17 15:14:37 +02:00
|
|
|
has_colour <- function() {
|
2020-12-27 00:07:00 +01:00
|
|
|
# this is a base R version of crayon::has_color, but disables colours on emacs
|
2022-08-28 10:31:50 +02:00
|
|
|
|
2020-12-27 00:07:00 +01:00
|
|
|
if (Sys.getenv("EMACS") != "" || Sys.getenv("INSIDE_EMACS") != "") {
|
2021-01-03 23:40:05 +01:00
|
|
|
# disable on emacs, which only supports 8 colours
|
2020-12-27 00:07:00 +01:00
|
|
|
return(FALSE)
|
|
|
|
}
|
2020-06-05 13:56:05 +02:00
|
|
|
enabled <- getOption("crayon.enabled")
|
|
|
|
if (!is.null(enabled)) {
|
|
|
|
return(isTRUE(enabled))
|
|
|
|
}
|
|
|
|
rstudio_with_ansi_support <- function(x) {
|
|
|
|
if (Sys.getenv("RSTUDIO", "") == "") {
|
|
|
|
return(FALSE)
|
|
|
|
}
|
2021-05-24 00:06:28 +02:00
|
|
|
if ((cols <- Sys.getenv("RSTUDIO_CONSOLE_COLOR", "")) != "" && !is.na(as.double(cols))) {
|
2020-06-05 13:56:05 +02:00
|
|
|
return(TRUE)
|
|
|
|
}
|
2022-09-01 15:20:57 +02:00
|
|
|
tryCatch(getExportedValue("isAvailable", ns = asNamespace("rstudioapi"))(), error = function(e) {
|
2022-08-28 10:31:50 +02:00
|
|
|
return(FALSE)
|
|
|
|
}) &&
|
2022-09-01 15:20:57 +02:00
|
|
|
tryCatch(getExportedValue("hasFun", ns = asNamespace("rstudioapi"))("getConsoleHasColor"), error = function(e) {
|
2022-08-28 10:31:50 +02:00
|
|
|
return(FALSE)
|
|
|
|
})
|
2020-06-05 13:56:05 +02:00
|
|
|
}
|
|
|
|
if (rstudio_with_ansi_support() && sink.number() == 0) {
|
|
|
|
return(TRUE)
|
|
|
|
}
|
|
|
|
if (!isatty(stdout())) {
|
2020-05-16 13:05:47 +02:00
|
|
|
return(FALSE)
|
|
|
|
}
|
|
|
|
if (tolower(Sys.info()["sysname"]) == "windows") {
|
2020-06-05 13:56:05 +02:00
|
|
|
if (Sys.getenv("ConEmuANSI") == "ON") {
|
2020-05-16 13:05:47 +02:00
|
|
|
return(TRUE)
|
|
|
|
}
|
2020-06-05 13:56:05 +02:00
|
|
|
if (Sys.getenv("CMDER_ROOT") != "") {
|
|
|
|
return(TRUE)
|
|
|
|
}
|
|
|
|
return(FALSE)
|
|
|
|
}
|
|
|
|
if ("COLORTERM" %in% names(Sys.getenv())) {
|
|
|
|
return(TRUE)
|
|
|
|
}
|
|
|
|
if (Sys.getenv("TERM") == "dumb") {
|
|
|
|
return(FALSE)
|
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
grepl(
|
|
|
|
pattern = "^screen|^xterm|^vt100|color|ansi|cygwin|linux",
|
|
|
|
x = Sys.getenv("TERM"),
|
|
|
|
ignore.case = TRUE,
|
|
|
|
perl = TRUE
|
|
|
|
)
|
2020-05-16 13:05:47 +02:00
|
|
|
}
|
|
|
|
|
2020-12-07 16:06:42 +01:00
|
|
|
# set colours if console has_colour()
|
2020-05-16 13:05:47 +02:00
|
|
|
try_colour <- function(..., before, after, collapse = " ") {
|
2022-10-05 09:12:22 +02:00
|
|
|
if (length(c(...)) == 0) {
|
|
|
|
return(character(0))
|
|
|
|
}
|
|
|
|
txt <- paste0(c(...), collapse = collapse)
|
2020-05-16 13:05:47 +02:00
|
|
|
if (isTRUE(has_colour())) {
|
|
|
|
if (is.null(collapse)) {
|
|
|
|
paste0(before, txt, after, collapse = NULL)
|
|
|
|
} else {
|
|
|
|
paste0(before, txt, after, collapse = "")
|
|
|
|
}
|
|
|
|
} else {
|
|
|
|
txt
|
|
|
|
}
|
|
|
|
}
|
2022-10-30 21:05:46 +01:00
|
|
|
is_dark <- function() {
|
|
|
|
if (is.null(AMR_env$is_dark_theme)) {
|
|
|
|
AMR_env$is_dark_theme <- tryCatch(isTRUE(getExportedValue("getThemeInfo", ns = asNamespace("rstudioapi"))()$dark), error = function(e) FALSE)
|
|
|
|
}
|
|
|
|
isTRUE(AMR_env$is_dark_theme)
|
|
|
|
}
|
2020-05-16 13:05:47 +02:00
|
|
|
font_black <- function(..., collapse = " ") {
|
2022-09-01 15:20:57 +02:00
|
|
|
before <- "\033[38;5;232m"
|
|
|
|
after <- "\033[39m"
|
2022-10-30 21:05:46 +01:00
|
|
|
if (is_dark()) {
|
2022-09-01 15:20:57 +02:00
|
|
|
# white
|
|
|
|
before <- "\033[37m"
|
|
|
|
after <- "\033[39m"
|
|
|
|
}
|
|
|
|
try_colour(..., before = before, after = after, collapse = collapse)
|
|
|
|
}
|
|
|
|
font_white <- function(..., collapse = " ") {
|
|
|
|
before <- "\033[37m"
|
|
|
|
after <- "\033[39m"
|
2022-10-30 21:05:46 +01:00
|
|
|
if (is_dark()) {
|
2022-09-01 15:20:57 +02:00
|
|
|
# black
|
|
|
|
before <- "\033[38;5;232m"
|
|
|
|
after <- "\033[39m"
|
|
|
|
}
|
|
|
|
try_colour(..., before = before, after = after, collapse = collapse)
|
2020-05-16 13:05:47 +02:00
|
|
|
}
|
|
|
|
font_blue <- function(..., collapse = " ") {
|
|
|
|
try_colour(..., before = "\033[34m", after = "\033[39m", collapse = collapse)
|
|
|
|
}
|
|
|
|
font_green <- function(..., collapse = " ") {
|
|
|
|
try_colour(..., before = "\033[32m", after = "\033[39m", collapse = collapse)
|
|
|
|
}
|
|
|
|
font_magenta <- function(..., collapse = " ") {
|
|
|
|
try_colour(..., before = "\033[35m", after = "\033[39m", collapse = collapse)
|
|
|
|
}
|
|
|
|
font_red <- function(..., collapse = " ") {
|
|
|
|
try_colour(..., before = "\033[31m", after = "\033[39m", collapse = collapse)
|
|
|
|
}
|
|
|
|
font_silver <- function(..., collapse = " ") {
|
|
|
|
try_colour(..., before = "\033[90m", after = "\033[39m", collapse = collapse)
|
|
|
|
}
|
|
|
|
font_yellow <- function(..., collapse = " ") {
|
|
|
|
try_colour(..., before = "\033[33m", after = "\033[39m", collapse = collapse)
|
|
|
|
}
|
|
|
|
font_subtle <- function(..., collapse = " ") {
|
|
|
|
try_colour(..., before = "\033[38;5;246m", after = "\033[39m", collapse = collapse)
|
|
|
|
}
|
|
|
|
font_grey <- function(..., collapse = " ") {
|
|
|
|
try_colour(..., before = "\033[38;5;249m", after = "\033[39m", collapse = collapse)
|
|
|
|
}
|
2020-12-01 16:59:57 +01:00
|
|
|
font_grey_bg <- function(..., collapse = " ") {
|
2022-10-31 13:25:41 +01:00
|
|
|
if (is_dark()) {
|
2021-02-21 22:56:35 +01:00
|
|
|
# similar to HTML #444444
|
2022-08-28 10:31:50 +02:00
|
|
|
try_colour(..., before = "\033[48;5;238m", after = "\033[49m", collapse = collapse)
|
2021-02-21 22:56:35 +01:00
|
|
|
} else {
|
2021-06-22 12:16:42 +02:00
|
|
|
# similar to HTML #f0f0f0
|
|
|
|
try_colour(..., before = "\033[48;5;255m", after = "\033[49m", collapse = collapse)
|
2021-02-21 22:56:35 +01:00
|
|
|
}
|
2020-12-01 16:59:57 +01:00
|
|
|
}
|
2022-10-05 09:12:22 +02:00
|
|
|
font_red_bg <- function(..., collapse = " ") {
|
|
|
|
# this is #ed553b (picked to be colourblind-safe with other RSI colours)
|
|
|
|
try_colour(font_black(..., collapse = collapse), before = "\033[48;5;203m", after = "\033[49m", collapse = collapse)
|
2020-05-16 13:05:47 +02:00
|
|
|
}
|
2022-10-05 09:12:22 +02:00
|
|
|
font_orange_bg <- function(..., collapse = " ") {
|
|
|
|
# this is #f6d55c (picked to be colourblind-safe with other RSI colours)
|
|
|
|
try_colour(font_black(..., collapse = collapse), before = "\033[48;5;222m", after = "\033[49m", collapse = collapse)
|
2020-12-27 00:07:00 +01:00
|
|
|
}
|
2022-10-05 09:12:22 +02:00
|
|
|
font_yellow_bg <- function(..., collapse = " ") {
|
|
|
|
try_colour(font_black(..., collapse = collapse), before = "\033[48;5;228m", after = "\033[49m", collapse = collapse)
|
2020-12-27 00:07:00 +01:00
|
|
|
}
|
2022-10-05 09:12:22 +02:00
|
|
|
font_green_bg <- function(..., collapse = " ") {
|
|
|
|
# this is #3caea3 (picked to be colourblind-safe with other RSI colours)
|
|
|
|
try_colour(font_black(..., collapse = collapse), before = "\033[48;5;79m", after = "\033[49m", collapse = collapse)
|
2020-12-27 00:07:00 +01:00
|
|
|
}
|
2022-10-05 09:12:22 +02:00
|
|
|
font_purple_bg <- function(..., collapse = " ") {
|
|
|
|
try_colour(font_black(..., collapse = collapse), before = "\033[48;5;89m", after = "\033[49m", collapse = collapse)
|
2020-05-16 13:05:47 +02:00
|
|
|
}
|
2022-10-05 09:12:22 +02:00
|
|
|
font_rose_bg <- function(..., collapse = " ") {
|
|
|
|
try_colour(font_black(..., collapse = collapse), before = "\033[48;5;217m", after = "\033[49m", collapse = collapse)
|
2020-05-16 13:05:47 +02:00
|
|
|
}
|
2020-08-28 21:55:47 +02:00
|
|
|
font_na <- function(..., collapse = " ") {
|
|
|
|
font_red(..., collapse = collapse)
|
|
|
|
}
|
2020-05-16 13:05:47 +02:00
|
|
|
font_bold <- function(..., collapse = " ") {
|
|
|
|
try_colour(..., before = "\033[1m", after = "\033[22m", collapse = collapse)
|
|
|
|
}
|
|
|
|
font_italic <- function(..., collapse = " ") {
|
|
|
|
try_colour(..., before = "\033[3m", after = "\033[23m", collapse = collapse)
|
|
|
|
}
|
|
|
|
font_underline <- function(..., collapse = " ") {
|
|
|
|
try_colour(..., before = "\033[4m", after = "\033[24m", collapse = collapse)
|
|
|
|
}
|
2022-11-24 20:29:00 +01:00
|
|
|
font_url <- function(url, txt = url) {
|
|
|
|
if (tryCatch(isTRUE(getExportedValue("ansi_has_hyperlink_support", ns = asNamespace("cli"))()), error = function(e) FALSE)) {
|
|
|
|
paste0("\033]8;;", url, "\a", txt, "\033]8;;\a")
|
|
|
|
} else {
|
|
|
|
url
|
|
|
|
}
|
|
|
|
}
|
2020-05-16 13:05:47 +02:00
|
|
|
font_stripstyle <- function(x) {
|
2022-11-24 20:29:00 +01:00
|
|
|
# remove URLs
|
|
|
|
x <- gsub("\033]8;;(.*?)\a.*?\033]8;;\a", "\\1", x)
|
2020-05-16 13:05:47 +02:00
|
|
|
# from crayon:::ansi_regex
|
2022-11-24 20:29:00 +01:00
|
|
|
x <- gsub("(?:(?:\\x{001b}\\[)|\\x{009b})(?:(?:[0-9]{1,3})?(?:(?:;[0-9]{0,3})*)?[A-M|f-m])|\\x{001b}[A-M]", "", x, perl = TRUE)
|
|
|
|
x
|
2020-05-16 13:05:47 +02:00
|
|
|
}
|
|
|
|
|
2021-04-20 10:46:17 +02:00
|
|
|
progress_ticker <- function(n = 1, n_min = 0, print = TRUE, ...) {
|
|
|
|
if (print == FALSE || n < n_min) {
|
2022-10-06 11:33:30 +02:00
|
|
|
# create fake/empty object
|
2020-05-16 13:05:47 +02:00
|
|
|
pb <- list()
|
|
|
|
pb$tick <- function() {
|
|
|
|
invisible()
|
|
|
|
}
|
|
|
|
pb$kill <- function() {
|
|
|
|
invisible()
|
|
|
|
}
|
2020-11-16 16:57:55 +01:00
|
|
|
set_clean_class(pb, new_class = "txtProgressBar")
|
2020-07-29 10:33:47 +02:00
|
|
|
} else if (n >= n_min) {
|
2022-10-06 11:33:30 +02:00
|
|
|
# use `progress`, which also has a timer
|
2021-12-13 10:18:28 +01:00
|
|
|
progress_bar <- import_fn("progress_bar", "progress", error_on_fail = FALSE)
|
|
|
|
if (!is.null(progress_bar)) {
|
|
|
|
# so we use progress::progress_bar
|
|
|
|
# a close() method was also added, see below this function
|
2022-08-28 10:31:50 +02:00
|
|
|
pb <- progress_bar$new(
|
2022-10-22 22:00:15 +02:00
|
|
|
format = "[:bar] :percent (:current/:total,:eta)",
|
2022-08-28 10:31:50 +02:00
|
|
|
total = n
|
|
|
|
)
|
2021-12-13 10:18:28 +01:00
|
|
|
} else {
|
2022-10-06 11:33:30 +02:00
|
|
|
# use base R
|
2021-12-13 10:18:28 +01:00
|
|
|
pb <- utils::txtProgressBar(max = n, style = 3)
|
|
|
|
pb$tick <- function() {
|
|
|
|
pb$up(pb$getVal() + 1)
|
|
|
|
}
|
2020-07-29 10:33:47 +02:00
|
|
|
}
|
|
|
|
pb
|
2020-05-16 13:05:47 +02:00
|
|
|
}
|
|
|
|
}
|
|
|
|
|
2021-12-13 10:18:28 +01:00
|
|
|
#' @method close progress_bar
|
|
|
|
#' @export
|
|
|
|
#' @noRd
|
|
|
|
close.progress_bar <- function(con, ...) {
|
2022-10-06 11:33:30 +02:00
|
|
|
# for progress::progress_bar$new()
|
2021-12-13 10:18:28 +01:00
|
|
|
con$terminate()
|
|
|
|
}
|
|
|
|
|
2020-11-16 16:57:55 +01:00
|
|
|
set_clean_class <- function(x, new_class) {
|
2020-12-07 16:06:42 +01:00
|
|
|
# return the object with only the new class and no additional attributes where possible
|
2020-11-16 16:57:55 +01:00
|
|
|
if (is.null(x)) {
|
|
|
|
x <- NA_character_
|
|
|
|
}
|
|
|
|
if (is.factor(x)) {
|
2020-12-07 16:06:42 +01:00
|
|
|
# keep only levels and remove all other attributes
|
2020-11-16 16:57:55 +01:00
|
|
|
lvls <- levels(x)
|
|
|
|
attributes(x) <- NULL
|
|
|
|
levels(x) <- lvls
|
2020-11-16 20:02:20 +01:00
|
|
|
} else if (!is.list(x) && !is.function(x)) {
|
2020-11-16 16:57:55 +01:00
|
|
|
attributes(x) <- NULL
|
|
|
|
}
|
|
|
|
class(x) <- new_class
|
|
|
|
x
|
|
|
|
}
|
|
|
|
|
2020-12-17 16:22:25 +01:00
|
|
|
formatted_filesize <- function(...) {
|
|
|
|
size_kb <- file.size(...) / 1024
|
|
|
|
if (size_kb < 1) {
|
|
|
|
paste(round(size_kb, 1), "kB")
|
|
|
|
} else if (size_kb < 100) {
|
|
|
|
paste(round(size_kb, 0), "kB")
|
|
|
|
} else {
|
|
|
|
paste(round(size_kb / 1024, 1), "MB")
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
2020-08-28 21:55:47 +02:00
|
|
|
create_pillar_column <- function(x, ...) {
|
2021-03-07 13:52:39 +01:00
|
|
|
new_pillar_shaft_simple <- import_fn("new_pillar_shaft_simple", "pillar")
|
|
|
|
new_pillar_shaft_simple(x, ...)
|
2020-08-28 21:55:47 +02:00
|
|
|
}
|
|
|
|
|
2022-08-27 20:49:37 +02:00
|
|
|
as_original_data_class <- function(df, old_class = NULL) {
|
|
|
|
if ("tbl_df" %in% old_class && pkg_is_available("tibble", also_load = FALSE)) {
|
|
|
|
fn <- import_fn("as_tibble", "tibble")
|
|
|
|
} else if ("tbl_ts" %in% old_class && pkg_is_available("tsibble", also_load = FALSE)) {
|
|
|
|
fn <- import_fn("as_tsibble", "tsibble")
|
|
|
|
} else if ("data.table" %in% old_class && pkg_is_available("data.table", also_load = FALSE)) {
|
|
|
|
fn <- import_fn("as.data.table", "data.table")
|
2022-10-05 09:12:22 +02:00
|
|
|
} else if ("tabyl" %in% old_class && pkg_is_available("janitor", also_load = FALSE)) {
|
|
|
|
fn <- import_fn("as_tabyl", "janitor")
|
2022-08-27 20:49:37 +02:00
|
|
|
} else {
|
|
|
|
fn <- base::as.data.frame
|
|
|
|
}
|
|
|
|
fn(df)
|
|
|
|
}
|
|
|
|
|
2020-06-22 11:18:40 +02:00
|
|
|
# works exactly like round(), but rounds `round2(44.55, 1)` to 44.6 instead of 44.5
|
2020-05-16 13:05:47 +02:00
|
|
|
# and adds decimal zeroes until `digits` is reached when force_zero = TRUE
|
2021-05-24 15:29:17 +02:00
|
|
|
round2 <- function(x, digits = 1, force_zero = TRUE) {
|
2020-05-16 13:05:47 +02:00
|
|
|
x <- as.double(x)
|
|
|
|
# https://stackoverflow.com/a/12688836/4575331
|
2022-08-28 10:31:50 +02:00
|
|
|
val <- (trunc((abs(x) * 10^digits) + 0.5) / 10^digits) * sign(x)
|
2022-10-05 09:12:22 +02:00
|
|
|
if (digits > 0 && force_zero == TRUE) {
|
2020-05-16 13:05:47 +02:00
|
|
|
values_trans <- val[val != as.integer(val) & !is.na(val)]
|
2022-08-28 10:31:50 +02:00
|
|
|
val[val != as.integer(val) & !is.na(val)] <- paste0(
|
|
|
|
values_trans,
|
|
|
|
strrep(
|
|
|
|
"0",
|
|
|
|
max(
|
|
|
|
0,
|
|
|
|
digits - nchar(
|
|
|
|
format(
|
|
|
|
as.double(
|
|
|
|
gsub(
|
|
|
|
".*[.](.*)$",
|
|
|
|
"\\1",
|
|
|
|
values_trans
|
|
|
|
)
|
|
|
|
),
|
|
|
|
scientific = FALSE
|
|
|
|
)
|
|
|
|
)
|
|
|
|
)
|
|
|
|
)
|
|
|
|
)
|
2020-05-16 13:05:47 +02:00
|
|
|
}
|
|
|
|
as.double(val)
|
|
|
|
}
|
|
|
|
|
|
|
|
|
|
|
|
# percentage from our other package: 'cleaner'
|
|
|
|
percentage <- function(x, digits = NULL, ...) {
|
2020-10-26 12:23:03 +01:00
|
|
|
|
2020-05-16 13:05:47 +02:00
|
|
|
# getdecimalplaces() function
|
|
|
|
getdecimalplaces <- function(x, minimum = 0, maximum = 3) {
|
|
|
|
if (maximum < minimum) {
|
|
|
|
maximum <- minimum
|
|
|
|
}
|
|
|
|
if (minimum > maximum) {
|
|
|
|
minimum <- maximum
|
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
max_places <- max(unlist(lapply(
|
|
|
|
strsplit(sub(
|
|
|
|
"0+$", "",
|
|
|
|
as.character(x * 100)
|
|
|
|
), ".", fixed = TRUE),
|
|
|
|
function(y) ifelse(length(y) == 2, nchar(y[2]), 0)
|
|
|
|
)), na.rm = TRUE)
|
2020-05-16 13:05:47 +02:00
|
|
|
max(min(max_places,
|
2022-08-28 10:31:50 +02:00
|
|
|
maximum,
|
|
|
|
na.rm = TRUE
|
|
|
|
),
|
|
|
|
minimum,
|
|
|
|
na.rm = TRUE
|
|
|
|
)
|
2020-05-16 13:05:47 +02:00
|
|
|
}
|
2020-10-26 12:23:03 +01:00
|
|
|
|
2020-05-16 13:05:47 +02:00
|
|
|
# format_percentage() function
|
|
|
|
format_percentage <- function(x, digits = NULL, ...) {
|
|
|
|
if (is.null(digits)) {
|
|
|
|
digits <- getdecimalplaces(x)
|
|
|
|
}
|
2021-05-20 11:42:39 +02:00
|
|
|
if (is.null(digits) || is.na(digits) || !is.numeric(digits)) {
|
|
|
|
digits <- 2
|
|
|
|
}
|
2020-10-26 12:23:03 +01:00
|
|
|
|
2020-05-16 13:05:47 +02:00
|
|
|
# round right: percentage(0.4455) and format(as.percentage(0.4455), 1) should return "44.6%", not "44.5%"
|
|
|
|
x_formatted <- format(round2(as.double(x), digits = digits + 2) * 100,
|
2022-08-28 10:31:50 +02:00
|
|
|
scientific = FALSE,
|
|
|
|
digits = max(1, digits),
|
|
|
|
nsmall = digits,
|
|
|
|
...
|
|
|
|
)
|
2020-05-16 13:05:47 +02:00
|
|
|
x_formatted <- paste0(x_formatted, "%")
|
|
|
|
x_formatted[!grepl(pattern = "^[0-9.,e-]+$", x = x)] <- NA_character_
|
|
|
|
x_formatted
|
|
|
|
}
|
2020-10-26 12:23:03 +01:00
|
|
|
|
2020-05-16 13:05:47 +02:00
|
|
|
# the actual working part
|
|
|
|
x <- as.double(x)
|
|
|
|
if (is.null(digits)) {
|
|
|
|
# max one digit if undefined
|
|
|
|
digits <- getdecimalplaces(x, minimum = 0, maximum = 1)
|
|
|
|
}
|
2022-08-28 10:31:50 +02:00
|
|
|
format_percentage(structure(
|
|
|
|
.Data = as.double(x),
|
|
|
|
class = c("percentage", "numeric")
|
|
|
|
),
|
|
|
|
digits = digits, ...
|
|
|
|
)
|
2020-05-16 13:05:47 +02:00
|
|
|
}
|
2020-05-18 13:59:34 +02:00
|
|
|
|
2022-10-05 09:12:22 +02:00
|
|
|
trimws2 <- function(..., whitespace = "[\u0009\u000A\u000B\u000C\u000D\u0020\u0085\u00A0\u1680\u180E\u2000\u2001\u2002\u2003\u2004\u2005\u2006\u2007\u2008\u2009\u200A\u200B\u200C\u200D\u2028\u2029\u202F\u205F\u2060\u3000\uFEFF]") {
|
|
|
|
# this is even faster than trimws() itself which sets " \t\n\r".
|
|
|
|
trimws(..., whitespace = whitespace)
|
2020-05-18 13:59:34 +02:00
|
|
|
}
|
2022-10-05 09:12:22 +02:00
|
|
|
|
2022-12-27 15:16:15 +01:00
|
|
|
readRDS2 <- function(file, refhook = NULL) {
|
|
|
|
# this is readRDS with remote file support
|
|
|
|
con <- file(file)
|
|
|
|
on.exit(close(con))
|
|
|
|
readRDS(con, refhook = refhook)
|
|
|
|
}
|
|
|
|
|
2022-10-05 09:12:22 +02:00
|
|
|
# Faster data.table implementations ----
|
|
|
|
|
|
|
|
match <- function(x, table, ...) {
|
2022-10-30 21:05:46 +01:00
|
|
|
chmatch <- import_fn("chmatch", "data.table", error_on_fail = FALSE)
|
|
|
|
if (!is.null(chmatch) && is.character(x) && is.character(table)) {
|
2022-10-05 09:12:22 +02:00
|
|
|
# data.table::chmatch() is 35% faster than base::match() for character
|
2022-10-30 21:05:46 +01:00
|
|
|
chmatch(x, table, ...)
|
2022-10-05 09:12:22 +02:00
|
|
|
} else {
|
|
|
|
base::match(x, table, ...)
|
|
|
|
}
|
2020-08-16 21:38:42 +02:00
|
|
|
}
|
2022-10-05 09:12:22 +02:00
|
|
|
`%in%` <- function(x, table) {
|
2022-10-30 21:05:46 +01:00
|
|
|
chin <- import_fn("%chin%", "data.table", error_on_fail = FALSE)
|
|
|
|
if (!is.null(chin) && is.character(x) && is.character(table)) {
|
2022-10-05 09:12:22 +02:00
|
|
|
# data.table::`%chin%`() is 20-50% faster than base::`%in%`() for character
|
2022-10-30 21:05:46 +01:00
|
|
|
chin(x, table)
|
2022-10-05 09:12:22 +02:00
|
|
|
} else {
|
|
|
|
base::`%in%`(x, table)
|
|
|
|
}
|
2020-10-08 11:16:03 +02:00
|
|
|
}
|
2022-10-05 09:12:22 +02:00
|
|
|
|
|
|
|
# nolint start
|
|
|
|
|
|
|
|
# Register S3 methods ----
|
|
|
|
# copied from vctrs::s3_register by their permission:
|
|
|
|
# https://github.com/r-lib/vctrs/blob/05968ce8e669f73213e3e894b5f4424af4f46316/R/register-s3.R
|
|
|
|
s3_register <- function(generic, class, method = NULL) {
|
|
|
|
stopifnot(is.character(generic), length(generic) == 1)
|
|
|
|
stopifnot(is.character(class), length(class) == 1)
|
|
|
|
pieces <- strsplit(generic, "::")[[1]]
|
|
|
|
stopifnot(length(pieces) == 2)
|
|
|
|
package <- pieces[[1]]
|
|
|
|
generic <- pieces[[2]]
|
|
|
|
caller <- parent.frame()
|
|
|
|
get_method_env <- function() {
|
|
|
|
top <- topenv(caller)
|
|
|
|
if (isNamespace(top)) {
|
|
|
|
asNamespace(environmentName(top))
|
|
|
|
} else {
|
|
|
|
caller
|
|
|
|
}
|
|
|
|
}
|
|
|
|
get_method <- function(method, env) {
|
|
|
|
if (is.null(method)) {
|
|
|
|
get(paste0(generic, ".", class), envir = get_method_env())
|
|
|
|
} else {
|
|
|
|
method
|
|
|
|
}
|
|
|
|
}
|
|
|
|
method_fn <- get_method(method)
|
|
|
|
stopifnot(is.function(method_fn))
|
|
|
|
setHook(packageEvent(package, "onLoad"), function(...) {
|
|
|
|
ns <- asNamespace(package)
|
|
|
|
method_fn <- get_method(method)
|
|
|
|
registerS3method(generic, class, method_fn, envir = ns)
|
|
|
|
})
|
|
|
|
if (!isNamespaceLoaded(package)) {
|
|
|
|
return(invisible())
|
|
|
|
}
|
|
|
|
envir <- asNamespace(package)
|
|
|
|
if (exists(generic, envir)) {
|
|
|
|
registerS3method(generic, class, method_fn, envir = envir)
|
|
|
|
}
|
|
|
|
invisible()
|
2020-12-17 16:22:25 +01:00
|
|
|
}
|
2021-04-12 14:24:40 +02:00
|
|
|
|
2022-10-05 09:12:22 +02:00
|
|
|
|
|
|
|
# Support old R versions ----
|
|
|
|
# these functions were not available in previous versions of R
|
|
|
|
# see here for the full list: https://github.com/r-lib/backports
|
|
|
|
if (getRversion() < "3.1.0") {
|
2021-04-12 14:24:40 +02:00
|
|
|
# R-3.0 does not contain these functions, set them here to prevent installation failure
|
2022-10-19 11:47:57 +02:00
|
|
|
# (required for extension of the 'mic' class)
|
2021-04-12 14:24:40 +02:00
|
|
|
cospi <- function(...) 1
|
|
|
|
sinpi <- function(...) 1
|
|
|
|
tanpi <- function(...) 1
|
|
|
|
}
|
2022-10-05 09:12:22 +02:00
|
|
|
|
|
|
|
if (getRversion() < "3.2.0") {
|
|
|
|
anyNA <- function(x, recursive = FALSE) {
|
|
|
|
if (isTRUE(recursive) && (is.list(x) || is.pairlist(x))) {
|
|
|
|
return(any(rapply(x, anyNA, how = "unlist", recursive = FALSE)))
|
|
|
|
}
|
|
|
|
any(is.na(x))
|
|
|
|
}
|
|
|
|
dir.exists <- function(paths) {
|
|
|
|
x <- base::file.info(paths)$isdir
|
|
|
|
!is.na(x) & x
|
|
|
|
}
|
|
|
|
file.size <- function(...) {
|
|
|
|
file.info(...)$size
|
|
|
|
}
|
|
|
|
file.mtime <- function(...) {
|
|
|
|
file.info(...)$mtime
|
|
|
|
}
|
|
|
|
isNamespaceLoaded <- function(pkg) {
|
|
|
|
pkg %in% loadedNamespaces()
|
|
|
|
}
|
|
|
|
lengths <- function(x, use.names = TRUE) {
|
|
|
|
vapply(x, length, FUN.VALUE = NA_integer_, USE.NAMES = use.names)
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
if (getRversion() < "3.3.0") {
|
|
|
|
strrep <- function(x, times) {
|
|
|
|
x <- as.character(x)
|
|
|
|
if (length(x) == 0L) {
|
|
|
|
return(x)
|
|
|
|
}
|
|
|
|
unlist(.mapply(function(x, times) {
|
|
|
|
if (is.na(x) || is.na(times)) {
|
|
|
|
return(NA_character_)
|
|
|
|
}
|
|
|
|
if (times <= 0L) {
|
|
|
|
return("")
|
|
|
|
}
|
|
|
|
paste0(replicate(times, x), collapse = "")
|
|
|
|
}, list(x = x, times = times), MoreArgs = list()), use.names = FALSE)
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
if (getRversion() < "3.5.0") {
|
|
|
|
isFALSE <- function(x) {
|
|
|
|
is.logical(x) && length(x) == 1L && !is.na(x) && !x
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
if (getRversion() < "3.6.0") {
|
|
|
|
str2lang <- function(s) {
|
|
|
|
stopifnot(length(s) == 1L)
|
|
|
|
ex <- parse(text = s, keep.source = FALSE)
|
|
|
|
stopifnot(length(ex) == 1L)
|
|
|
|
ex[[1L]]
|
|
|
|
}
|
|
|
|
# trims() was introduced in 3.3.0, but its argument `whitespace` only in 3.6.0
|
|
|
|
trimws <- function(x, which = c("both", "left", "right"), whitespace = "[ \t\r\n]") {
|
|
|
|
which <- match.arg(which)
|
|
|
|
mysub <- function(re, x) sub(re, "", x, perl = TRUE)
|
|
|
|
switch(which,
|
|
|
|
left = mysub(paste0("^", whitespace, "+"), x),
|
|
|
|
right = mysub(paste0(whitespace, "+$"), x),
|
|
|
|
both = mysub(paste0(whitespace, "+$"), mysub(paste0("^", whitespace, "+"), x))
|
|
|
|
)
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
if (getRversion() < "4.0.0") {
|
|
|
|
deparse1 <- function(expr, collapse = " ", width.cutoff = 500L, ...) {
|
|
|
|
paste(deparse(expr, width.cutoff, ...), collapse = collapse)
|
|
|
|
}
|
2021-05-21 20:20:51 +02:00
|
|
|
}
|
2022-10-05 09:12:22 +02:00
|
|
|
|
|
|
|
# nolint end
|