1
0
mirror of https://github.com/msberends/AMR.git synced 2025-07-08 12:31:58 +02:00

(v0.7.1.9004) atc class removal

This commit is contained in:
2019-06-27 11:57:45 +02:00
parent 6013fbefae
commit 65c6702b21
49 changed files with 393 additions and 706 deletions

View File

@ -150,7 +150,7 @@ ab_ddd <- function(x, administration = "oral", units = FALSE, ...) {
ab_info <- function(x, language = get_locale(), ...) {
x <- AMR::as.ab(x, ...)
base::list(ab = as.character(x),
atc = as.character(ab_atc(x)),
atc = ab_atc(x),
cid = ab_cid(x),
name = ab_name(x, language = language),
group = ab_group(x, language = language),
@ -192,7 +192,7 @@ ab_validate <- function(x, property, ...) {
left_join(AMR::antibiotics, by = "ab") %>%
pull(property)
}
if (property %in% c("ab", "atc")) {
if (property == "ab") {
return(structure(x, class = property))
} else if (property == "cid") {
return(as.integer(x))

85
R/atc.R
View File

@ -1,85 +0,0 @@
# ==================================================================== #
# TITLE #
# Antimicrobial Resistance (AMR) Analysis #
# #
# SOURCE #
# https://gitlab.com/msberends/AMR #
# #
# LICENCE #
# (c) 2019 Berends MS (m.s.berends@umcg.nl), Luz CF (c.f.luz@umcg.nl) #
# #
# 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. #
# #
# This R package was created for academic research and was publicly #
# released in the hope that it will be useful, but it comes WITHOUT #
# ANY WARRANTY OR LIABILITY. #
# Visit our website for more info: https://msberends.gitlab.io/AMR. #
# ==================================================================== #
#' Transform to ATC code
#'
#' Use this function to determine the ATC code of one or more antibiotics. The data set \code{\link{antibiotics}} will be searched for abbreviations, official names and trade names.
#' @param x character vector to determine \code{ATC} code
#' @rdname as.atc
#' @aliases atc
#' @keywords atc
#' @inheritSection WHOCC WHOCC
#' @export
#' @importFrom dplyr %>% filter slice pull
#' @details Use the \code{\link{ab_property}} functions to get properties based on the returned ATC code, see Examples.
#'
#' In the ATC classification system, the active substances are classified in a hierarchy with five different levels. The system has fourteen main anatomical/pharmacological groups or 1st levels. Each ATC main group is divided into 2nd levels which could be either pharmacological or therapeutic groups. The 3rd and 4th levels are chemical, pharmacological or therapeutic subgroups and the 5th level is the chemical substance. The 2nd, 3rd and 4th levels are often used to identify pharmacological subgroups when that is considered more appropriate than therapeutic or chemical subgroups.
#' Source: \url{https://www.whocc.no/atc/structure_and_principles/}
#' @return Character (vector) with class \code{"atc"}. Unknown values will return \code{NA}.
#' @seealso \code{\link{antibiotics}} for the dataframe that is being used to determine ATCs.
#' @inheritSection AMR Read more on our website!
#' @examples
#' # These examples all return "J01FA01", the ATC code of Erythromycin:
#' as.atc("J01FA01")
#' as.atc("Erythromycin")
#' as.atc("eryt")
#' as.atc(" eryt 123")
#' as.atc("ERYT")
#' as.atc("ERY")
as.atc <- function(x) {
ab_atc(x)
}
#' @rdname as.atc
#' @export
is.atc <- function(x) {
identical(class(x), "atc")
}
#' @exportMethod print.atc
#' @export
#' @noRd
print.atc <- function(x, ...) {
cat("Class 'atc'\n")
print.default(as.character(x), quote = FALSE)
}
#' @exportMethod as.data.frame.atc
#' @export
#' @noRd
as.data.frame.atc <- function (x, ...) {
# same as as.data.frame.character but with removed stringsAsFactors
nm <- paste(deparse(substitute(x), width.cutoff = 500L),
collapse = " ")
if (!"nm" %in% names(list(...))) {
as.data.frame.vector(x, ..., nm = nm)
} else {
as.data.frame.vector(x, ...)
}
}
#' @exportMethod pull.atc
#' @export
#' @importFrom dplyr pull
#' @noRd
pull.atc <- function(.data, ...) {
pull(as.data.frame(.data), ...)
}

View File

@ -105,7 +105,7 @@ count_R <- function(..., also_single_tested = FALSE) {
include_I = FALSE,
minimum = 0,
as_percent = FALSE,
also_single_tested = FALSE,
also_single_tested = also_single_tested,
only_count = TRUE)
}
@ -117,7 +117,7 @@ count_IR <- function(..., also_single_tested = FALSE) {
include_I = TRUE,
minimum = 0,
as_percent = FALSE,
also_single_tested = FALSE,
also_single_tested = also_single_tested,
only_count = TRUE)
}
@ -129,7 +129,7 @@ count_I <- function(..., also_single_tested = FALSE) {
include_I = FALSE,
minimum = 0,
as_percent = FALSE,
also_single_tested = FALSE,
also_single_tested = also_single_tested,
only_count = TRUE)
}
@ -141,7 +141,7 @@ count_SI <- function(..., also_single_tested = FALSE) {
include_I = TRUE,
minimum = 0,
as_percent = FALSE,
also_single_tested = FALSE,
also_single_tested = also_single_tested,
only_count = TRUE)
}
@ -153,26 +153,24 @@ count_S <- function(..., also_single_tested = FALSE) {
include_I = FALSE,
minimum = 0,
as_percent = FALSE,
also_single_tested = FALSE,
also_single_tested = also_single_tested,
only_count = TRUE)
}
#' @rdname count
#' @export
count_all <- function(...) {
count_all <- function(..., also_single_tested = FALSE) {
res_SI <- count_SI(..., also_single_tested = also_single_tested)
# only print warnings once, if needed
count_S(...) + suppressWarnings(count_IR(...))
res_R <- suppressWarnings(count_R(..., also_single_tested = also_single_tested))
res_SI + res_R
}
#' @rdname count
#' @export
n_rsi <- function(...) {
# only print warnings once, if needed
count_S(...) + suppressWarnings(count_IR(...))
}
n_rsi<- count_all
#' @rdname count
#' @importFrom dplyr %>% select_if bind_rows summarise_if mutate group_vars select everything
#' @export
count_df <- function(data,
translate_ab = "name",

View File

@ -137,7 +137,7 @@ catalogue_of_life <- list(
#' \item{\code{gender}}{gender of the patient}
#' \item{\code{patient_id}}{ID of the patient, first 10 characters of an SHA hash containing irretrievable information}
#' \item{\code{mo}}{ID of microorganism created with \code{\link{as.mo}}, see also \code{\link{microorganisms}}}
#' \item{\code{peni:rifa}}{40 different antibiotics with class \code{rsi} (see \code{\link{as.rsi}}); these column names occur in \code{\link{antibiotics}} data set and can be translated with \code{\link{abname}}}
#' \item{\code{peni:rifa}}{40 different antibiotics with class \code{rsi} (see \code{\link{as.rsi}}); these column names occur in \code{\link{antibiotics}} data set and can be translated with \code{\link{ab_name}}}
#' }
#' @inheritSection AMR Read more on our website!
"septic_patients"
@ -172,7 +172,7 @@ catalogue_of_life <- list(
#' \item{\code{Inducible clindamycin resistance}}{Clindamycin can be induced?}
#' \item{\code{Comment}}{Other comments}
#' \item{\code{Date of data entry}}{Date this data was entered in WHONET}
#' \item{\code{AMP_ND10:CIP_EE}}{27 different antibiotics. You can lookup the abbreviatons in the \code{\link{antibiotics}} data set, or use e.g. \code{\link{atc_name}("AMP")} to get the official name immediately. Before analysis, you should transform this to a valid antibiotic class, using \code{\link{as.rsi}}.}
#' \item{\code{AMP_ND10:CIP_EE}}{27 different antibiotics. You can lookup the abbreviatons in the \code{\link{antibiotics}} data set, or use e.g. \code{\link{ab_name}("AMP")} to get the official name immediately. Before analysis, you should transform this to a valid antibiotic class, using \code{\link{as.rsi}}.}
#' }
#' @inheritSection AMR Read more on our website!
"WHONET"

View File

@ -27,71 +27,8 @@
#' @keywords internal
#' @name AMR-deprecated
#' @rdname AMR-deprecated
ratio <- function(x, ratio) {
.Deprecated(package = "AMR")
if (!all(is.numeric(x))) {
stop('`x` must be a vector of numeric values.')
}
if (length(ratio) == 1) {
if (ratio %like% '^([0-9]+([.][0-9]+)?[-,:])+[0-9]+([.][0-9]+)?$') {
# support for "1:2:1", "1-2-1", "1,2,1" and even "1.75:2:1.5"
ratio <- ratio %>% strsplit("[-,:]") %>% unlist() %>% as.double()
} else {
stop('Invalid `ratio`: ', ratio, '.')
}
}
if (length(x) != 1 & length(x) != length(ratio)) {
stop('`x` and `ratio` must be of same size.')
}
sum(x, na.rm = TRUE) * (ratio / sum(ratio, na.rm = TRUE))
as.atc <- function(x) {
.Deprecated("ab_atc", package = "AMR")
ab_atc(x)
}
#' @rdname AMR-deprecated
#' @export
abname <- function(...) {
.Deprecated("ab_name", package = "AMR")
ab_name(...)
}
#' @rdname AMR-deprecated
#' @export
atc_property <- function(...) {
.Deprecated("ab_property", package = "AMR")
ab_property(...)
}
#' @rdname AMR-deprecated
#' @export
atc_official <- function(...) {
.Deprecated("ab_name", package = "AMR")
ab_name(...)
}
#' @rdname AMR-deprecated
#' @export
ab_official <- function(...) {
.Deprecated("ab_name", package = "AMR")
ab_name(...)
}
#' @rdname AMR-deprecated
#' @export
atc_name <- function(...) {
.Deprecated("ab_name", package = "AMR")
ab_name(...)
}
#' @rdname AMR-deprecated
#' @export
atc_trivial_nl <- function(...) {
.Deprecated("ab_name", package = "AMR")
ab_name(..., language = "nl")
}
#' @rdname AMR-deprecated
#' @export
atc_tradenames <- function(...) {
.Deprecated("ab_tradenames", package = "AMR")
ab_tradenames(...)
}

View File

@ -392,7 +392,7 @@ eucast_rules <- function(x,
x_original[rows, cols] <<- to,
warning = function(w) {
if (w$message %like% 'invalid factor level') {
warning('Value "', to, '" could not be applied to column(s) `', paste(cols, collapse = '`, `'), '` because this value is not an existing factor level.', call. = FALSE)
warning('Value "', to, '" could not be applied to column(s) `', paste(cols, collapse = '`, `'), '` because this value is not an existing factor level. You can use as.rsi() to fix this.', call. = FALSE)
} else {
warning(w$message, call. = FALSE)
}

View File

@ -29,11 +29,10 @@
#' @param breaks numeric vector of positions
#' @param limits numeric vector of length two providing limits of the scale, use \code{NA} to refer to the existing minimum or maximum
#' @param facet variable to split plots by, either \code{"interpretation"} (default) or \code{"antibiotic"} or a grouping variable
#' @param fun function to transform \code{data}, either \code{\link{count_df}} (default) or \code{\link{portion_df}}
#' @inheritParams portion
#' @param nrow (when using \code{facet}) number of rows
#' @param colours a named vector with colours for the bars. The names must be one or more of: S, SI, I, IR, R or be \code{FALSE} to use default \code{ggplot2} colours.
#' @param datalabels show datalabels using \code{labels_rsi_count}, will only be shown when \code{fun = count_df}
#' @param datalabels show datalabels using \code{labels_rsi_count}
#' @param datalabels.size size of the datalabels
#' @param datalabels.colour colour of the datalabels
#' @param title text to show as title of the plot
@ -45,7 +44,7 @@
#' @details At default, the names of antibiotics will be shown on the plots using \code{\link{ab_name}}. This can be set with the \code{translate_ab} parameter. See \code{\link{count_df}}.
#'
#' \strong{The functions}\cr
#' \code{geom_rsi} will take any variable from the data that has an \code{rsi} class (created with \code{\link{as.rsi}}) using \code{fun} (\code{\link{count_df}} at default, can also be \code{\link{portion_df}}) and will plot bars with the percentage R, I and S. The default behaviour is to have the bars stacked and to have the different antibiotics on the x axis.
#' \code{geom_rsi} will take any variable from the data that has an \code{rsi} class (created with \code{\link{as.rsi}}) using \code{\link{rsi_df}} and will plot bars with the percentage R, I and S. The default behaviour is to have the bars stacked and to have the different antibiotics on the x axis.
#'
#' \code{facet_rsi} creates 2d plots (at default based on S/I/R) using \code{\link[ggplot2]{facet_wrap}}.
#'
@ -87,7 +86,7 @@
#' # get only portions and no counts:
#' septic_patients %>%
#' select(AMX, NIT, FOS, TMP, CIP) %>%
#' ggplot_rsi(fun = portion_df)
#' ggplot_rsi(datalabels = FALSE)
#'
#' # add other ggplot2 parameters as you like:
#' septic_patients %>%
@ -171,7 +170,6 @@ ggplot_rsi <- function(data,
combine_SI = TRUE,
combine_IR = FALSE,
language = get_locale(),
fun = count_df,
nrow = NULL,
colours = c(S = "#61a8ff",
SI = "#61a8ff",
@ -190,11 +188,6 @@ ggplot_rsi <- function(data,
stopifnot_installed_package("ggplot2")
fun_name <- deparse(substitute(fun))
if (!fun_name %in% c("portion_df", "count_df")) {
stop("`fun` must be portion_df or count_df")
}
x <- x[1]
facet <- facet[1]
@ -223,7 +216,7 @@ ggplot_rsi <- function(data,
p <- ggplot2::ggplot(data = data) +
geom_rsi(position = position, x = x, fill = fill, translate_ab = translate_ab,
fun = fun, combine_SI = combine_SI, combine_IR = combine_IR, ...) +
combine_SI = combine_SI, combine_IR = combine_IR, ...) +
theme_rsi()
if (fill == "interpretation") {
@ -235,13 +228,12 @@ ggplot_rsi <- function(data,
p <- p + scale_rsi_colours(colours = colours)
}
if (fun_name == "portion_df"
| (fun_name == "count_df" & identical(position, "fill"))) {
if (identical(position, "fill")) {
# portions, so use y scale with percentage
p <- p + scale_y_percent(breaks = breaks, limits = limits)
}
if (fun_name == "count_df" & datalabels == TRUE) {
if (datalabels == TRUE) {
p <- p + labels_rsi_count(position = position,
x = x,
translate_ab = translate_ab,
@ -273,7 +265,6 @@ geom_rsi <- function(position = NULL,
language = get_locale(),
combine_SI = TRUE,
combine_IR = FALSE,
fun = count_df,
...) {
stopifnot_installed_package("ggplot2")
@ -282,19 +273,9 @@ geom_rsi <- function(position = NULL,
stop("`position` is invalid. Did you accidentally use '%>%' instead of '+'?", call. = FALSE)
}
fun_name <- deparse(substitute(fun))
if (!fun_name %in% c("portion_df", "count_df", "fun")) {
stop("`fun` must be portion_df or count_df")
}
y <- "value"
if (identical(fun, count_df)) {
if (missing(position) | is.null(position)) {
position <- "fill"
}
} else {
if (missing(position) | is.null(position)) {
position <- "stack"
}
if (missing(position) | is.null(position)) {
position <- "fill"
}
if (identical(position, "fill")) {
@ -321,11 +302,11 @@ geom_rsi <- function(position = NULL,
ggplot2::layer(geom = "bar", stat = "identity", position = position,
mapping = ggplot2::aes_string(x = x, y = y, fill = fill),
params = list(...), data = function(x) {
fun(data = x,
translate_ab = translate_ab,
language = language,
combine_SI = combine_SI,
combine_IR = combine_IR)
AMR::rsi_df(data = x,
translate_ab = translate_ab,
language = language,
combine_SI = combine_SI,
combine_IR = combine_IR)
})
}
@ -431,14 +412,12 @@ labels_rsi_count <- function(position = NULL,
colour = datalabels.colour,
lineheight = 0.75,
data = function(x) {
# labels are only shown when function is count_df,
# so no need parameterise it here
count_df(data = x,
translate_ab = translate_ab,
combine_SI = combine_SI,
combine_IR = combine_IR) %>%
rsi_df(data = x,
translate_ab = translate_ab,
combine_SI = combine_SI,
combine_IR = combine_IR) %>%
group_by_at(x_name) %>%
mutate(lbl = paste0(percent(value / sum(value, na.rm = TRUE), force_zero = TRUE),
"\n(n=", value, ")"))
"\n(n=", isolates, ")"))
})
}

View File

@ -23,106 +23,66 @@ globalVariables(c(".",
"..property",
"ab",
"abbreviations",
"mdr",
"mono_count",
"second",
"xdr",
"antibiotic",
"Antibiotic",
"antibiotics",
"atc",
"authors",
"Becker",
"CNS_CPS",
"cnt",
"col_id",
"count",
"count.x",
"count.y",
"cum_count",
"cum_percent",
"date_lab",
"diff.percent",
"fctlvl",
"First name",
"First",
"first_isolate_row_index",
"Freq",
"fullname",
"fullname_lower",
"genus",
"gramstain",
"index",
"input",
"Interpretation",
"interpretation",
"isolates",
"item",
"key_ab",
"key_ab_lag",
"key_ab_other",
"kingdom",
"labs",
"Lancefield",
"lang",
"Last name",
"lbl",
"Last",
"lookup",
"mdr",
"median",
"mic",
"microorganisms",
"microorganisms.codes",
"microorganisms.old",
"microorganisms.oldDT",
"microorganisms.prevDT",
"microorganisms.unprevDT",
"microorganismsDT",
"missing_names",
"mo",
"mo.old",
"mono_count",
"more_than_episode_ago",
"MPM",
"n",
"name",
"name",
"name",
"new",
"observations",
"observed",
"official",
"old",
"other_pat_or_mo",
"package_v",
"Pasted",
"patient_id",
"pattern",
"phylum",
"plural",
"prevalence",
"prevalent",
"property",
"psae",
"R",
"real_first_isolate",
"ref",
"reference.rule",
"reference.rule_group",
"rsi",
"rule_group",
"rule_name",
"S",
"se_max",
"se_min",
"septic_patients",
"second",
"Sex",
"shortname",
"species",
"species_id",
"subspecies",
"synonyms",
"trade_name",
"trans",
"transmute",
"tsn",
"tsn_new",
"txt",
"value",
"Value",
"x",
"xdr",
"y",
"year"))

View File

@ -104,3 +104,100 @@ guess_ab_col <- function(x = NULL, search_string = NULL, verbose = FALSE) {
return(ab_result)
}
}
#' @importFrom crayon blue bold
#' @importFrom dplyr %>% mutate arrange pull
get_column_abx <- function(x,
soft_dependencies = NULL,
hard_dependencies = NULL,
verbose = FALSE,
...) {
# determine from given data set
df_trans <- data.frame(colnames = colnames(x),
abcode = suppressWarnings(as.ab(colnames(x))))
df_trans <- df_trans[!is.na(df_trans$abcode),]
x <- as.character(df_trans$colnames)
names(x) <- df_trans$abcode
# add from self-defined dots (...):
# get_column_abx(septic_patients %>% rename(thisone = AMX), amox = "thisone")
dots <- list(...)
if (length(dots) > 0) {
newnames <- suppressWarnings(as.ab(names(dots)))
if (any(is.na(newnames))) {
warning("Invalid antibiotic reference(s): ", toString(names(dots)[is.na(newnames)]),
call. = FALSE, immediate. = TRUE)
}
# turn all NULLs to NAs
dots <- unlist(lapply(dots, function(x) if (is.null(x)) NA else x))
names(dots) <- newnames
dots <- dots[!is.na(names(dots))]
# merge, but overwrite automatically determined ones by 'dots'
x <- c(x[!x %in% dots & !names(x) %in% names(dots)], dots)
# delete NAs, this will make e.g. eucast_rules(... TMP = NULL) work to prevent TMP from being used
x <- x[!is.na(x)]
}
# sort on name
x <- x[sort(names(x))]
dupes <- x[base::duplicated(x)]
if (verbose == TRUE) {
for (i in 1:length(x)) {
if (x[i] %in% dupes) {
message(red(paste0("NOTE: Using column `", bold(x[i]), "` as input for `", names(x)[i],
"` (", ab_name(names(x)[i], language = "en", tolower = TRUE), ") [DUPLICATED USE].")))
} else {
message(blue(paste0("NOTE: Using column `", bold(x[i]), "` as input for `", names(x)[i],
"` (", ab_name(names(x)[i], language = "en", tolower = TRUE), ").")))
}
}
}
if (n_distinct(x) != length(x)) {
msg_txt <- paste("Column(s)", paste0("`", dupes, "`", collapse = " and "), "used for more than one antibiotic.")
if (verbose == FALSE) {
msg_txt <- paste(msg_txt, "Use verbose = TRUE to see which antibiotics are used by which columns.")
}
stop(msg_txt, call. = FALSE)
}
if (!is.null(hard_dependencies)) {
if (!all(hard_dependencies %in% names(x))) {
# missing a hard dependency will return NA and consequently the data will not be analysed
missing <- hard_dependencies[!hard_dependencies %in% names(x)]
generate_warning_abs_missing(missing, any = FALSE)
return(NA)
}
}
if (!is.null(soft_dependencies)) {
if (!all(soft_dependencies %in% names(x))) {
# missing a soft dependency may lower the reliability
missing <- soft_dependencies[!soft_dependencies %in% names(x)]
missing_txt <- data.frame(missing = missing,
missing_names = AMR::ab_name(missing, tolower = TRUE),
stringsAsFactors = FALSE) %>%
mutate(txt = paste0(bold(missing), " (", missing_names, ")")) %>%
arrange(missing_names) %>%
pull(txt)
message(blue('NOTE: Reliability might be improved if these antimicrobial results would be available too:',
paste(missing_txt, collapse = ", ")))
}
}
x
}
generate_warning_abs_missing <- function(missing, any = FALSE) {
missing <- paste0(missing, " (", ab_name(missing, tolower = TRUE), ")")
if (any == TRUE) {
any_txt <- c(" any of", "is")
} else {
any_txt <- c("", "are")
}
warning(paste0("Introducing NAs since", any_txt[1], " these antimicrobials ", any_txt[2], " required: ",
paste(missing, collapse = ", ")),
immediate. = TRUE,
call. = FALSE)
}

View File

@ -154,96 +154,6 @@ search_type_in_df <- function(x, type) {
found
}
#' @importFrom crayon blue bold
get_column_abx <- function(x,
soft_dependencies = NULL,
hard_dependencies = NULL,
verbose = FALSE,
...) {
# determine from given data set
df_trans <- data.frame(colnames = colnames(x),
abcode = suppressWarnings(as.ab(colnames(x))))
df_trans <- df_trans[!is.na(df_trans$abcode),]
x <- as.character(df_trans$colnames)
names(x) <- df_trans$abcode
# add from self-defined dots (...):
# get_column_abx(septic_patients %>% rename(thisone = AMX), amox = "thisone")
dots <- list(...)
if (length(dots) > 0) {
newnames <- suppressWarnings(as.ab(names(dots)))
if (any(is.na(newnames))) {
warning("Invalid antibiotic reference(s): ", toString(names(dots)[is.na(newnames)]),
call. = FALSE, immediate. = TRUE)
}
# turn all NULLs to NAs
dots <- unlist(lapply(dots, function(x) if (is.null(x)) NA else x))
names(dots) <- newnames
dots <- dots[!is.na(names(dots))]
# merge, but overwrite automatically determined ones by 'dots'
x <- c(x[!x %in% dots & !names(x) %in% names(dots)], dots)
# delete NAs, this will make eucast_rules(... TMP = NULL) work to prevent TMP from being used
x <- x[!is.na(x)]
}
# sort on name
x <- x[sort(names(x))]
duplies <- x[base::duplicated(x)]
if (verbose == TRUE) {
for (i in 1:length(x)) {
if (x[i] %in% duplies) {
message(red(paste0("NOTE: Using column `", bold(x[i]), "` as input for `", names(x)[i],
"` (", ab_name(names(x)[i], language = "en", tolower = TRUE), ") [DUPLICATED USE].")))
} else {
message(blue(paste0("NOTE: Using column `", bold(x[i]), "` as input for `", names(x)[i],
"` (", ab_name(names(x)[i], language = "en", tolower = TRUE), ").")))
}
}
}
if (n_distinct(x) != length(x)) {
msg_txt <- paste("Column(s)", paste0("`", duplies, "`", collapse = " and "), "used for more than one antibiotic.")
if (verbose == FALSE) {
msg_txt <- paste(msg_txt, "Use verbose = TRUE to see which antibiotics are used by which columns.")
}
stop(msg_txt, call. = FALSE)
}
if (!is.null(hard_dependencies)) {
if (!all(hard_dependencies %in% names(x))) {
# missing a hard dependency will return NA and consequently the data will not be analysed
missing <- hard_dependencies[!hard_dependencies %in% names(x)]
generate_warning_abs_missing(missing, any = FALSE)
return(NA)
}
}
if (!is.null(soft_dependencies)) {
if (!all(soft_dependencies %in% names(x))) {
# missing a soft dependency may lower the reliability
missing <- soft_dependencies[!soft_dependencies %in% names(x)]
missing <- paste0(bold(missing), " (", ab_name(missing, tolower = TRUE), ")")
message(blue('NOTE: Reliability might be improved if these antimicrobial results would be available too:', paste(missing, collapse = ", ")))
}
}
x
}
generate_warning_abs_missing <- function(missing, any = FALSE) {
missing <- paste0(missing, " (", ab_name(missing, tolower = TRUE), ")")
if (any == TRUE) {
any_txt <- c(" any of", "is")
} else {
any_txt <- c("", "are")
}
warning(paste0("Introducing NAs since", any_txt[1], " these antimicrobials ", any_txt[2], " required: ",
paste(missing, collapse = ", ")),
immediate. = TRUE,
call. = FALSE)
}
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

39
R/mo.R
View File

@ -486,7 +486,7 @@ exec_as.mo <- function(x,
# remove genus as first word
x <- gsub("^Genus ", "", x)
# allow characters that resemble others
if (initial_search == FALSE) {
if (uncertainty_level >= 2) {
x <- tolower(x)
x <- gsub("[iy]+", "[iy]+", x)
x <- gsub("(c|k|q|qu|s|z|x|ks)+", "(c|k|q|qu|s|z|x|ks)+", x)
@ -494,9 +494,13 @@ exec_as.mo <- function(x,
x <- gsub("(th|t)+", "(th|t)+", x)
x <- gsub("a+", "a+", x)
x <- gsub("u+", "u+", x)
# allow any ending of -um, -us, -ium, -ius and -a (needs perl for the negative backward lookup):
x <- gsub("(um|u\\[sz\\]\\+|\\[iy\\]\\+um|\\[iy\\]\\+u\\[sz\\]\\+|a\\+)(?![a-z[])",
"(um|us|ium|ius|a)", x, ignore.case = TRUE, perl = TRUE)
# allow any ending of -um, -us, -ium, -icum, -ius, -icus, -ica and -a (needs perl for the negative backward lookup):
x <- gsub("(u\\+\\(c\\|k\\|q\\|qu\\+\\|s\\|z\\|x\\|ks\\)\\+)(?![a-z[])",
"(u[s|m]|[iy][ck]?u[ms]|[iy]?[ck]?a)", x, ignore.case = TRUE, perl = TRUE)
x <- gsub("(\\[iy\\]\\+\\(c\\|k\\|q\\|qu\\+\\|s\\|z\\|x\\|ks\\)\\+a\\+)(?![a-z[])",
"(u[s|m]|[iy][ck]?u[ms]|[iy]?[ck]?a)", x, ignore.case = TRUE, perl = TRUE)
x <- gsub("(\\[iy\\]\\+u\\+m)(?![a-z[])",
"(u[s|m]|[iy][ck]?u[ms]|[iy]?[ck]?a)", x, ignore.case = TRUE, perl = TRUE)
x <- gsub("e+", "e+", x, ignore.case = TRUE)
x <- gsub("o+", "o+", x, ignore.case = TRUE)
x <- gsub("(.)\\1+", "\\1+", x)
@ -1078,8 +1082,33 @@ exec_as.mo <- function(x,
return(found[1L])
}
# (5) try to strip off one element from end and check the remains ----
# (5a) try to strip off half an element from end and check the remains ----
x_strip <- a.x_backup %>% strsplit(" ") %>% unlist()
if (length(x_strip) > 1) {
for (i in 1:(length(x_strip) - 1)) {
lastword <- x_strip[length(x_strip) - i + 1]
lastword_half <- substr(lastword, 1, as.integer(nchar(lastword) / 2))
# remove last half of the second term
x_strip_collapsed <- paste(c(x_strip[1:(length(x_strip) - i)], lastword_half), collapse = " ")
if (nchar(x_strip_collapsed) >= 4) {
found <- suppressMessages(suppressWarnings(exec_as.mo(x_strip_collapsed, initial_search = FALSE, allow_uncertain = FALSE)))
if (!empty_result(found)) {
found_result <- found
found <- microorganismsDT[mo == found, ..property][[1]]
uncertainties <<- rbind(uncertainties,
data.frame(uncertainty = 2,
input = a.x_backup,
fullname = microorganismsDT[mo == found_result[1L], fullname][[1]],
mo = found_result[1L]))
if (initial_search == TRUE) {
set_mo_history(a.x_backup, get_mo_code(found[1L], property), 2, force = force_mo_history)
}
return(found[1L])
}
}
}
}
# (5b) try to strip off one element from end and check the remains ----
if (length(x_strip) > 1) {
for (i in 1:(length(x_strip) - 1)) {
x_strip_collapsed <- paste(x_strip[1:(length(x_strip) - i)], collapse = " ")

View File

@ -111,7 +111,7 @@
#' mo_fullname("S. pyo") # "Streptococcus pyogenes"
#' mo_fullname("S. pyo", Lancefield = TRUE) # "Streptococcus group A"
#' mo_shortname("S. pyo") # "S. pyogenes"
#' mo_shortname("S. pyo", Lancefield = TRUE) # "GAS" ('Group A streptococci')
#' mo_shortname("S. pyo", Lancefield = TRUE) # "GAS" (='Group A Streptococci')
#'
#'
#' # language support for German, Dutch, Spanish, Portuguese, Italian and French
@ -148,44 +148,17 @@ mo_fullname <- mo_name
#' @importFrom dplyr %>% mutate pull
#' @export
mo_shortname <- function(x, language = get_locale(), ...) {
dots <- list(...)
Becker <- dots$Becker
if (is.null(Becker)) {
Becker <- FALSE
}
Lancefield <- dots$Lancefield
if (is.null(Lancefield)) {
Lancefield <- FALSE
}
x.mo <- as.mo(x, ...)
# get first char of genus and complete species in English
shortnames <- paste0(substr(mo_genus(x.mo, language = NULL), 1, 1), ". ", mo_species(x.mo, language = NULL))
# get result without transformations
res1 <- AMR::as.mo(x, Becker = FALSE, Lancefield = FALSE, reference_df = dots$reference_df)
# and result with transformations
res2 <- suppressWarnings(AMR::as.mo(res1, ...))
res2_fullname <- mo_fullname(res2, language = language)
res2_fullname[res2_fullname %like% " \\(CoNS\\)"] <- "CoNS"
res2_fullname[res2_fullname %like% " \\(CoPS\\)"] <- "CoPS"
res2_fullname[res2_fullname %like% " \\(KNS\\)"] <- "KNS"
res2_fullname[res2_fullname %like% " \\(KPS\\)"] <- "KPS"
res2_fullname[res2_fullname %like% " \\(CNS\\)"] <- "CNS"
res2_fullname[res2_fullname %like% " \\(CPS\\)"] <- "CPS"
res2_fullname[res2_fullname %like% " \\(SCN\\)"] <- "SCN"
res2_fullname <- gsub("Streptococcus (group|Gruppe|gruppe|groep|grupo|gruppo|groupe) (.)",
"G\\2S",
res2_fullname) # turn "Streptococcus group A" and "Streptococcus grupo A" to "GAS"
res2_fullname_vector <- res2_fullname[res2_fullname == mo_fullname(res1)]
res2_fullname[res2_fullname == mo_fullname(res1)] <- paste0(substr(mo_genus(res2_fullname_vector), 1, 1),
". ",
suppressWarnings(mo_species(res2_fullname_vector)))
if (sum(res1 == res2, na.rm = TRUE) > 0) {
res1[res1 == res2] <- paste0(substr(mo_genus(res1[res1 == res2]), 1, 1),
". ",
suppressWarnings(mo_species(res1[res1 == res2])))
}
res1[res1 != res2] <- res2_fullname
result <- as.character(res1)
# exceptions for Staphylococci
shortnames[shortnames == "S. coagulase-negative" ] <- "CoNS"
shortnames[shortnames == "S. coagulase-positive" ] <- "CoPS"
# exceptions for Streptococci
shortnames[shortnames %like% "S. group [ABCDFGHK]"] <- paste0("G", gsub("S. group ([ABCDFGHK])", "\\1", shortnames[shortnames %like% "S. group [ABCDFGHK]"]), "S")
translate_AMR(result, language = language, only_unknown = FALSE)
translate_AMR(shortnames, language = language, only_unknown = FALSE)
}
#' @rdname mo_property
@ -246,7 +219,7 @@ mo_type <- function(x, language = get_locale(), ...) {
#' @export
mo_gramstain <- function(x, language = get_locale(), ...) {
x.mo <- as.mo(x, ...)
x.phylum <- mo_phylum(x.mo, language = "en")
x.phylum <- mo_phylum(x.mo, language = NULL)
# DETERMINE GRAM STAIN FOR BACTERIA
# Source: https://itis.gov/servlet/SingleRpt/SingleRpt?search_topic=TSN&search_value=956097
# It says this:
@ -259,7 +232,7 @@ mo_gramstain <- function(x, language = get_locale(), ...) {
# Phylum Tenericutes (Murray, 1984)
x <- NA_character_
# make all bacteria Gram negative
x[mo_kingdom(x.mo, language = "en") == "Bacteria"] <- "Gram-negative"
x[mo_kingdom(x.mo, language = NULL) == "Bacteria"] <- "Gram-negative"
# overwrite these phyla with Gram positive
x[x.phylum %in% c("Actinobacteria",
"Chloroflexi",

View File

@ -27,7 +27,7 @@
#' @param ... one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with \code{\link{as.rsi}} if needed. Use multiple columns to calculate (the lack of) co-resistance: the probability where one of two drugs have a resistant or susceptible result. See Examples.
#' @param minimum the minimum allowed number of available (tested) isolates. Any isolate count lower than \code{minimum} will return \code{NA} with a warning. The default number of \code{30} isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source.
#' @param as_percent a logical to indicate whether the output must be returned as a hundred fold with \% sign (a character). A value of \code{0.123456} will then be returned as \code{"12.3\%"}.
#' @param also_single_tested a logical to indicate whether (in combination therapies) also observations should be included where not all antibiotics were tested, but at least one of the tested antibiotics contains a target interpretation (e.g. S in case of \code{portion_S} and R in case of \code{portion_R}). \strong{This would lead to selection bias in almost all cases.}
#' @param also_single_tested a logical to indicate whether for combination therapies also observations should be included where not all antibiotics were tested, but at least one of the tested antibiotics contains a target interpretation (e.g. S in case of \code{portion_S} and R in case of \code{portion_R}). \strong{This could lead to selection bias.}
#' @param data a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}})
#' @param translate_ab a column name of the \code{\link{antibiotics}} data set to translate the antibiotic abbreviations to, using \code{\link{ab_property}}
#' @inheritParams ab_property
@ -112,6 +112,15 @@
#' septic_patients %>% portion_S(AMC, GEN) # S = 92.3%
#' septic_patients %>% count_all(AMC, GEN) # n = 1798
#'
#' # Using `also_single_tested` can be useful ...
#' septic_patients %>%
#' portion_S(AMC, GEN,
#' also_single_tested = TRUE) # S = 92.6%
#' # ... but can also lead to selection bias - the data only has 2,000 rows:
#' septic_patients %>%
#' count_all(AMC, GEN,
#' also_single_tested = TRUE) # n = 2555
#'
#'
#' septic_patients %>%
#' group_by(hospital_id) %>%

View File

@ -19,6 +19,23 @@
# Visit our website for more info: https://msberends.gitlab.io/AMR. #
# ==================================================================== #
#' @importFrom rlang enquos as_label
dots2vars <- function(...) {
paste(
unlist(
lapply(enquos(...),
function(x) {
l <- as_label(x)
if (l != ".") {
l
} else {
character(0)
}
})
),
collapse = ", ")
}
#' @importFrom dplyr %>% pull all_vars any_vars filter_all funs mutate_all
rsi_calc <- function(...,
type,
@ -28,6 +45,8 @@ rsi_calc <- function(...,
also_single_tested,
only_count) {
data_vars <- dots2vars(...)
if (!is.logical(include_I)) {
stop('`include_I` must be logical', call. = FALSE)
}
@ -138,7 +157,7 @@ rsi_calc <- function(...,
}
if (total < minimum) {
warning("Introducing NA: only ", total, " results available (minimum set to ", minimum, ").", call. = FALSE)
warning("Introducing NA: only ", total, " results available for ", data_vars, " (minimum set to ", minimum, ").", call. = FALSE)
result <- NA
} else {
result <- found / total

Binary file not shown.