mirror of
https://github.com/msberends/AMR.git
synced 2025-07-08 10:31:53 +02:00
(v1.1.0.9004) lose dependencies
This commit is contained in:
@ -19,6 +19,48 @@
|
||||
# Visit our website for more info: https://msberends.gitlab.io/AMR. #
|
||||
# ==================================================================== #
|
||||
|
||||
# functions from dplyr, will perhaps become poorman
|
||||
distinct <- function(.data, ..., .keep_all = FALSE) {
|
||||
check_is_dataframe(.data)
|
||||
if ("grouped_data" %in% class(.data)) {
|
||||
distinct.grouped_data(.data, ..., .keep_all = .keep_all)
|
||||
} else {
|
||||
distinct.default(.data, ..., .keep_all = .keep_all)
|
||||
}
|
||||
}
|
||||
distinct.default <- function(.data, ..., .keep_all = FALSE) {
|
||||
names <- rownames(.data)
|
||||
rownames(.data) <- NULL
|
||||
if (length(deparse_dots(...)) == 0) {
|
||||
selected <- .data
|
||||
} else {
|
||||
selected <- select(.data, ...)
|
||||
}
|
||||
rows <- as.integer(rownames(unique(selected)))
|
||||
if (isTRUE(.keep_all)) {
|
||||
res <- .data[rows, , drop = FALSE]
|
||||
} else {
|
||||
res <- selected[rows, , drop = FALSE]
|
||||
}
|
||||
rownames(res) <- names[rows]
|
||||
res
|
||||
}
|
||||
distinct.grouped_data <- function(.data, ..., .keep_all = FALSE) {
|
||||
apply_grouped_function(.data, "distinct", ..., .keep_all = .keep_all)
|
||||
}
|
||||
filter_join_worker <- function(x, y, by = NULL, type = c("anti", "semi")) {
|
||||
type <- match.arg(type, choices = c("anti", "semi"), several.ok = FALSE)
|
||||
if (is.null(by)) {
|
||||
by <- intersect(names(x), names(y))
|
||||
join_message(by)
|
||||
}
|
||||
rows <- interaction(x[, by]) %in% interaction(y[, by])
|
||||
if (type == "anti") rows <- !rows
|
||||
res <- x[rows, , drop = FALSE]
|
||||
rownames(res) <- NULL
|
||||
res
|
||||
}
|
||||
|
||||
# No export, no Rd
|
||||
addin_insert_in <- function() {
|
||||
rstudioapi::insertText(" %in% ")
|
||||
@ -36,7 +78,7 @@ check_dataset_integrity <- function() {
|
||||
"species", "subspecies", "rank",
|
||||
"col_id", "species_id", "source",
|
||||
"ref", "prevalence", "snomed") %in% colnames(microorganisms),
|
||||
na.rm = TRUE) & NROW(microorganisms) == NROW(microorganismsDT)
|
||||
na.rm = TRUE) & NROW(microorganisms) == NROW(MO_lookup)
|
||||
check_antibiotics <- all(c("ab", "atc", "cid", "name", "group",
|
||||
"atc_group1", "atc_group2", "abbreviations",
|
||||
"synonyms", "oral_ddd", "oral_units",
|
||||
@ -51,12 +93,11 @@ check_dataset_integrity <- function() {
|
||||
invisible(TRUE)
|
||||
}
|
||||
|
||||
#' @importFrom crayon blue bold red
|
||||
#' @importFrom dplyr %>% pull
|
||||
search_type_in_df <- function(x, type) {
|
||||
# try to find columns based on type
|
||||
found <- NULL
|
||||
|
||||
|
||||
x <- as.data.frame(x, stringsAsFactors = FALSE)
|
||||
colnames(x) <- trimws(colnames(x))
|
||||
|
||||
# -- mo
|
||||
@ -89,14 +130,14 @@ search_type_in_df <- function(x, type) {
|
||||
if (any(colnames(x) %like% "^(specimen date|specimen_date|spec_date)")) {
|
||||
# WHONET support
|
||||
found <- colnames(x)[colnames(x) %like% "^(specimen date|specimen_date|spec_date)"][1]
|
||||
if (!any(class(x %>% pull(found)) %in% c("Date", "POSIXct"))) {
|
||||
stop(red(paste0("ERROR: Found column `", bold(found), "` to be used as input for `col_", type,
|
||||
if (!any(class(pull(x, found)) %in% c("Date", "POSIXct"))) {
|
||||
stop(font_red(paste0("ERROR: 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)
|
||||
}
|
||||
} else {
|
||||
for (i in seq_len(ncol(x))) {
|
||||
if (any(class(x %>% pull(i)) %in% c("Date", "POSIXct"))) {
|
||||
if (any(class(pull(x, i)) %in% c("Date", "POSIXct"))) {
|
||||
found <- colnames(x)[i]
|
||||
break
|
||||
}
|
||||
@ -127,7 +168,7 @@ search_type_in_df <- function(x, type) {
|
||||
if (!is.null(found)) {
|
||||
# this column should contain logicals
|
||||
if (!is.logical(x[, found, drop = TRUE])) {
|
||||
message(red(paste0("NOTE: Column `", bold(found), "` found as input for `col_", type,
|
||||
message(font_red(paste0("NOTE: Column `", font_bold(found), "` found as input for `col_", type,
|
||||
"`, but this column does not contain 'logical' values (TRUE/FALSE) and was ignored.")))
|
||||
found <- NULL
|
||||
}
|
||||
@ -135,11 +176,11 @@ search_type_in_df <- function(x, type) {
|
||||
}
|
||||
|
||||
if (!is.null(found)) {
|
||||
msg <- paste0("NOTE: Using column `", bold(found), "` as input for `col_", type, "`.")
|
||||
msg <- paste0("NOTE: Using column `", font_bold(found), "` as input for `col_", type, "`.")
|
||||
if (type %in% c("keyantibiotics", "specimen")) {
|
||||
msg <- paste(msg, "Use", bold(paste0("col_", type), "= FALSE"), "to prevent this.")
|
||||
msg <- paste(msg, "Use", font_bold(paste0("col_", type), "= FALSE"), "to prevent this.")
|
||||
}
|
||||
message(blue(msg))
|
||||
message(font_blue(msg))
|
||||
}
|
||||
found
|
||||
}
|
||||
@ -147,10 +188,11 @@ search_type_in_df <- function(x, type) {
|
||||
stopifnot_installed_package <- function(package) {
|
||||
# no "utils::installed.packages()" since it requires non-staged install since R 3.6.0
|
||||
# https://developer.r-project.org/Blog/public/2019/02/14/staged-install/index.html
|
||||
tryCatch(get(".packageName", envir = asNamespace(package)),
|
||||
error = function(e) stop("package '", package, "' required but not installed",
|
||||
' - try to install it with: install.packages("', package, '")',
|
||||
call. = FALSE))
|
||||
sapply(package, function(x)
|
||||
tryCatch(get(".packageName", envir = asNamespace(x)),
|
||||
error = function(e) stop("package '", x, "' required but not installed.",
|
||||
"\nTry to install it with: install.packages(\"", x, "\")",
|
||||
call. = FALSE)))
|
||||
return(invisible())
|
||||
}
|
||||
|
||||
@ -206,3 +248,184 @@ dataset_UTF8_to_ASCII <- function(df) {
|
||||
}
|
||||
df
|
||||
}
|
||||
|
||||
|
||||
# replace crayon::has_color
|
||||
has_colour <- function() {
|
||||
if (Sys.getenv("TERM") == "dumb") {
|
||||
return(FALSE)
|
||||
}
|
||||
if (tolower(Sys.info()["sysname"]) == "windows") {
|
||||
if (Sys.getenv("ConEmuANSI") == "ON" | Sys.getenv("CMDER_ROOT") != "") {
|
||||
return(TRUE)
|
||||
} else {
|
||||
return(FALSE)
|
||||
}
|
||||
}
|
||||
"COLORTERM" %in% names(Sys.getenv()) | grepl("^screen|^xterm|^vt100|color|ansi|cygwin|linux",
|
||||
Sys.getenv("TERM"),
|
||||
ignore.case = TRUE,
|
||||
perl = TRUE)
|
||||
}
|
||||
|
||||
|
||||
# the crayon colours
|
||||
try_colour <- function(..., before, after, collapse = " ") {
|
||||
txt <- paste0(unlist(list(...)), collapse = collapse)
|
||||
if (isTRUE(has_colour())) {
|
||||
if (is.null(collapse)) {
|
||||
paste0(before, txt, after, collapse = NULL)
|
||||
} else {
|
||||
paste0(before, txt, after, collapse = "")
|
||||
}
|
||||
} else {
|
||||
txt
|
||||
}
|
||||
}
|
||||
font_black <- function(..., collapse = " ") {
|
||||
try_colour(..., before = "\033[38;5;232m", after = "\033[39m", collapse = collapse)
|
||||
}
|
||||
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_white <- function(..., collapse = " ") {
|
||||
try_colour(..., before = "\033[37m", 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)
|
||||
}
|
||||
font_green_bg <- function(..., collapse = " ") {
|
||||
try_colour(..., before = "\033[42m", after = "\033[49m", collapse = collapse)
|
||||
}
|
||||
font_red_bg <- function(..., collapse = " ") {
|
||||
try_colour(..., before = "\033[41m", after = "\033[49m", collapse = collapse)
|
||||
}
|
||||
font_yellow_bg <- function(..., collapse = " ") {
|
||||
try_colour(..., before = "\033[43m", after = "\033[49m", collapse = collapse)
|
||||
}
|
||||
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)
|
||||
}
|
||||
font_stripstyle <- function(x) {
|
||||
# from crayon:::ansi_regex
|
||||
gsub("(?:(?:\\x{001b}\\[)|\\x{009b})(?:(?:[0-9]{1,3})?(?:(?:;[0-9]{0,3})*)?[A-M|f-m])|\\x{001b}[A-M]", "", x, perl = TRUE)
|
||||
}
|
||||
|
||||
progress_estimated <- function(n = 1, n_min = 0, ...) {
|
||||
# initiate with:
|
||||
# progress <- progressbar(n)
|
||||
# on.exit(close(progress))
|
||||
#
|
||||
# update with:
|
||||
# progress$tick()
|
||||
if (n >= n_min) {
|
||||
pb <- utils::txtProgressBar(max = n, style = 3)
|
||||
pb$tick <- function() {
|
||||
pb$up(pb$getVal() + 1)
|
||||
}
|
||||
pb
|
||||
} else {
|
||||
pb <- list()
|
||||
pb$tick <- function() {
|
||||
invisible()
|
||||
}
|
||||
pb$kill <- function() {
|
||||
invisible()
|
||||
}
|
||||
structure(pb, class = "txtProgressBar")
|
||||
}
|
||||
}
|
||||
|
||||
# works exactly like round(), but rounds `round(44.55, 1)` as 44.6 instead of 44.5
|
||||
# and adds decimal zeroes until `digits` is reached when force_zero = TRUE
|
||||
round2 <- function(x, digits = 0, force_zero = TRUE) {
|
||||
x <- as.double(x)
|
||||
# https://stackoverflow.com/a/12688836/4575331
|
||||
val <- (trunc((abs(x) * 10 ^ digits) + 0.5) / 10 ^ digits) * sign(x)
|
||||
if (digits > 0 & force_zero == TRUE) {
|
||||
values_trans <- val[val != as.integer(val) & !is.na(val)]
|
||||
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)))))
|
||||
}
|
||||
as.double(val)
|
||||
}
|
||||
|
||||
|
||||
# percentage from our other package: 'cleaner'
|
||||
percentage <- function(x, digits = NULL, ...) {
|
||||
|
||||
# getdecimalplaces() function
|
||||
getdecimalplaces <- function(x, minimum = 0, maximum = 3) {
|
||||
if (maximum < minimum) {
|
||||
maximum <- minimum
|
||||
}
|
||||
if (minimum > maximum) {
|
||||
minimum <- maximum
|
||||
}
|
||||
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)
|
||||
max(min(max_places,
|
||||
maximum, na.rm = TRUE),
|
||||
minimum, na.rm = TRUE)
|
||||
}
|
||||
|
||||
# format_percentage() function
|
||||
format_percentage <- function(x, digits = NULL, ...) {
|
||||
if (is.null(digits)) {
|
||||
digits <- getdecimalplaces(x)
|
||||
}
|
||||
|
||||
# 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,
|
||||
scientific = FALSE,
|
||||
digits = digits,
|
||||
nsmall = digits,
|
||||
...)
|
||||
x_formatted <- paste0(x_formatted, "%")
|
||||
x_formatted[!grepl(pattern = "^[0-9.,e-]+$", x = x)] <- NA_character_
|
||||
x_formatted
|
||||
}
|
||||
|
||||
# the actual working part
|
||||
x <- as.double(x)
|
||||
if (is.null(digits)) {
|
||||
# max one digit if undefined
|
||||
digits <- getdecimalplaces(x, minimum = 0, maximum = 1)
|
||||
}
|
||||
format_percentage(structure(.Data = as.double(x),
|
||||
class = c("percentage", "numeric")),
|
||||
digits = digits, ...)
|
||||
}
|
||||
|
Reference in New Issue
Block a user