(v0.7.1.9004) atc class removal

This commit is contained in:
dr. M.S. (Matthijs) Berends 2019-06-27 11:57:45 +02:00
parent 6013fbefae
commit 65c6702b21
49 changed files with 393 additions and 706 deletions

View File

@ -1,6 +1,6 @@
Package: AMR
Version: 0.7.1.9003
Date: 2019-06-23
Version: 0.7.1.9004
Date: 2019-06-27
Title: Antimicrobial Resistance Analysis
Authors@R: c(
person(

View File

@ -1,7 +1,6 @@
# Generated by roxygen2: do not edit by hand
S3method(as.data.frame,ab)
S3method(as.data.frame,atc)
S3method(as.data.frame,freq)
S3method(as.data.frame,mo)
S3method(as.double,mic)
@ -29,7 +28,6 @@ S3method(plot,mic)
S3method(plot,resistance_predict)
S3method(plot,rsi)
S3method(print,ab)
S3method(print,atc)
S3method(print,catalogue_of_life_version)
S3method(print,disk)
S3method(print,freq)
@ -40,7 +38,6 @@ S3method(print,mo_renamed)
S3method(print,mo_uncertainties)
S3method(print,rsi)
S3method(pull,ab)
S3method(pull,atc)
S3method(pull,mo)
S3method(select,freq)
S3method(skewness,data.frame)
@ -58,11 +55,9 @@ export(ab_ddd)
export(ab_group)
export(ab_info)
export(ab_name)
export(ab_official)
export(ab_property)
export(ab_synonyms)
export(ab_tradenames)
export(abname)
export(age)
export(age_groups)
export(anti_join_microorganisms)
@ -72,14 +67,9 @@ export(as.disk)
export(as.mic)
export(as.mo)
export(as.rsi)
export(atc_name)
export(atc_official)
export(atc_online_ddd)
export(atc_online_groups)
export(atc_online_property)
export(atc_property)
export(atc_tradenames)
export(atc_trivial_nl)
export(availability)
export(brmo)
export(catalogue_of_life_version)
@ -121,7 +111,6 @@ export(guess_ab_col)
export(header)
export(inner_join_microorganisms)
export(is.ab)
export(is.atc)
export(is.disk)
export(is.mic)
export(is.mo)
@ -169,7 +158,6 @@ export(portion_R)
export(portion_S)
export(portion_SI)
export(portion_df)
export(ratio)
export(read.4D)
export(resistance_predict)
export(right_join_microorganisms)
@ -185,7 +173,6 @@ export(skewness)
export(theme_rsi)
export(top_freq)
exportMethods(as.data.frame.ab)
exportMethods(as.data.frame.atc)
exportMethods(as.data.frame.freq)
exportMethods(as.data.frame.mo)
exportMethods(as.double.mic)
@ -209,7 +196,6 @@ exportMethods(plot.freq)
exportMethods(plot.mic)
exportMethods(plot.rsi)
exportMethods(print.ab)
exportMethods(print.atc)
exportMethods(print.catalogue_of_life_version)
exportMethods(print.disk)
exportMethods(print.freq)
@ -220,7 +206,6 @@ exportMethods(print.mo_renamed)
exportMethods(print.mo_uncertainties)
exportMethods(print.rsi)
exportMethods(pull.ab)
exportMethods(pull.atc)
exportMethods(pull.mo)
exportMethods(scale_type.ab)
exportMethods(scale_type.mo)

View File

@ -1,6 +1,11 @@
# AMR 0.7.1.9003
# AMR 0.7.1.9004
(no code changes yet)
### Changed
* Removed class `atc` - using `as.atc()` is now deprecated in favour of `ab_atc()` and this will return a character, not the `atc` class anymore
* Removed deprecated functions `abname()`, `ab_official()`, `atc_name()`, `atc_official()`, `atc_property()`, `atc_tradenames()`, `atc_trivial_nl()`
* Fix and speed improvement for `mo_shortname()`
* Fix for `as.mo()` where misspelled input would not be understood
* Fix for `also_single_tested` parameter in `count_*` functions
# AMR 0.7.1

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.

View File

@ -14,8 +14,8 @@ de unknown genus unbekannte Gattung FALSE FALSE
de unknown species unbekannte Art FALSE FALSE
de unknown subspecies unbekannte Unterart FALSE FALSE
de unknown rank unbekannter Rang FALSE FALSE
de (CoNS) (KNS) TRUE FALSE
de (CoPS) (KPS) TRUE FALSE
de CoNS KNS TRUE FALSE
de CoPS KPS TRUE FALSE
de Gram-negative Gramnegativ FALSE FALSE
de Gram-positive Grampositiv FALSE FALSE
de Bacteria Bakterien FALSE FALSE
@ -41,8 +41,8 @@ nl unknown genus onbekend geslacht FALSE FALSE
nl unknown species onbekende soort FALSE FALSE
nl unknown subspecies onbekende ondersoort FALSE FALSE
nl unknown rank onbekende rang FALSE FALSE
nl (CoNS) (CNS) TRUE FALSE
nl (CoPS) (CPS) TRUE FALSE
nl CoNS CNS TRUE FALSE
nl CoPS CPS TRUE FALSE
nl Gram-negative Gram-negatief FALSE FALSE
nl Gram-positive Gram-positief FALSE FALSE
nl Bacteria Bacteriën FALSE FALSE
@ -67,8 +67,8 @@ es unknown genus género desconocido FALSE FALSE
es unknown species especie desconocida FALSE FALSE
es unknown subspecies subespecie desconocida FALSE FALSE
es unknown rank rango desconocido FALSE FALSE
es (CoNS) (SCN) TRUE FALSE
es (CoPS) (SCP) TRUE FALSE
es CoNS SCN TRUE FALSE
es CoPS SCP TRUE FALSE
es Gram-negative Gram negativo FALSE FALSE
es Gram-positive Gram positivo FALSE FALSE
es Bacteria Bacterias FALSE FALSE
@ -179,32 +179,33 @@ nl Capreomycin Capreomycine
nl Carbenicillin Carbenicilline
nl Carindacillin Carindacilline
nl Caspofungin Caspofungine
nl Cefacetrile Cefacetril
nl Cefalexin Cefalexine
nl Cefalotin Cefalotine
nl Cefamandole Cefamandol
nl Cefapirin Cefapirine
nl Cefazedone Cefazedon
nl Cefazolin Cefazoline
nl Cefepime Cefepim
nl Cefixime Cefixim
nl Cefmenoxime Cefmenoxim
nl Cefmetazole Cefmetazol
nl Cefodizime Cefodizim
nl Cefonicid Cefonicide
nl Cefoperazone Cefoperazon
nl Cefoperazone/beta-lactamase inhibitor Cefoperazon/enzymremmer
nl Cefotaxime Cefotaxim
nl Cefoxitin Cefoxitine
nl Cefpirome Cefpirom
nl Cefpodoxime Cefpodoxim
nl Cefsulodin Cefsulodine
nl Ceftazidime Ceftazidim
nl Ceftezole Ceftezol
nl Ceftizoxime Ceftizoxim
nl Ceftriaxone Ceftriaxon
nl Cefuroxime Cefuroxim
nl Cefuroxime/metronidazole Cefuroxim/andere antibacteriele middelen
nl Ce(f|ph)acetrile Cefacetril FALSE
nl Ce(f|ph)alexin Cefalexine FALSE FALSE
nl Ce(f|ph)alotin Cefalotine FALSE
nl Ce(f|ph)amandole Cefamandol FALSE
nl Ce(f|ph)apirin Cefapirine FALSE
nl Ce(f|ph)azedone Cefazedon FALSE
nl Ce(f|ph)azolin Cefazoline FALSE
nl Ce(f|ph)epime Cefepim FALSE
nl Ce(f|ph)ixime Cefixim FALSE
nl Ce(f|ph)menoxime Cefmenoxim FALSE
nl Ce(f|ph)metazole Cefmetazol FALSE
nl Ce(f|ph)odizime Cefodizim FALSE
nl Ce(f|ph)onicid Cefonicide FALSE
nl Ce(f|ph)operazone Cefoperazon FALSE
nl Ce(f|ph)operazone/beta-lactamase inhibitor Cefoperazon/enzymremmer FALSE
nl Ce(f|ph)otaxime Cefotaxim FALSE
nl Ce(f|ph)oxitin Cefoxitine FALSE
nl Ce(f|ph)pirome Cefpirom FALSE
nl Ce(f|ph)podoxime Cefpodoxim FALSE
nl Ce(f|ph)radine Cefradine FALSE
nl Ce(f|ph)sulodin Cefsulodine FALSE
nl Ce(f|ph)tazidime Ceftazidim FALSE
nl Ce(f|ph)tezole Ceftezol FALSE
nl Ce(f|ph)tizoxime Ceftizoxim FALSE
nl Ce(f|ph)triaxone Ceftriaxon FALSE
nl Ce(f|ph)uroxime Cefuroxim FALSE
nl Ce(f|ph)uroxime/metronidazole Cefuroxim/andere antibacteriele middelen FALSE
nl Chloramphenicol Chlooramfenicol
nl Chlortetracycline Chloortetracycline
nl Cinoxacin Cinoxacine

Can't render this file because it has a wrong number of fields in line 159.

Binary file not shown.

View File

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

View File

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

View File

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

View File

@ -31,10 +31,9 @@ $('head').append('<!-- Updated Font Awesome library --><link rel="stylesheet" hr
$( document ).ready(function() {
// add SurveyMonkey
$('body').append('<script>(function(t,e,s,o){var n,a,c;t.SMCX=t.SMCX||[],e.getElementById(o)||(n=e.getElementsByTagName(s),a=n[n.length-1],c=e.createElement(s),c.type="text/javascript",c.async=!0,c.id=o,c.src=["https:"===location.protocol?"https://":"http://","widget.surveymonkey.com/collect/website/js/tRaiETqnLgj758hTBazgd_2BrwaGaWbg59AiLjNGdPaaJiBHKqgXKIw46VauwBvZ67.js"].join(""),a.parentNode.insertBefore(c,a))})(window,document,"script","smcx-sdk");</script>');
// $('body').append('<script>(function(t,e,s,o){var n,a,c;t.SMCX=t.SMCX||[],e.getElementById(o)||(n=e.getElementsByTagName(s),a=n[n.length-1],c=e.createElement(s),c.type="text/javascript",c.async=!0,c.id=o,c.src=["https:"===location.protocol?"https://":"http://","widget.surveymonkey.com/collect/website/js/tRaiETqnLgj758hTBazgd_2BrwaGaWbg59AiLjNGdPaaJiBHKqgXKIw46VauwBvZ67.js"].join(""),a.parentNode.insertBefore(c,a))})(window,document,"script","smcx-sdk");</script>');
// add link to survey at home sidebar
$('.template-home #sidebar .list-unstyled:first').append('<li><strong>Please fill in our survey at</strong> <br><a href="https://www.surveymonkey.com/r/AMR_for_R" target="_blank">https://www.surveymonkey.com/r/AMR_for_R</a></li>');
// $('.template-home #sidebar .list-unstyled:first').append('<li><strong>Please fill in our survey at</strong> <br><a href="https://www.surveymonkey.com/r/AMR_for_R" target="_blank">https://www.surveymonkey.com/r/AMR_for_R</a></li>');
// remove version label from header

View File

@ -42,7 +42,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9004</span>
</span>
</div>
@ -314,7 +314,7 @@
<p>It <strong>cleanses existing data</strong> by providing new <em>classes</em> for microoganisms, antibiotics and antimicrobial results (both S/I/R and MIC). By installing this package, you teach R everything about microbiology that is needed for analysis. These functions all use intelligent rules to guess results that you would expect:</p>
<ul>
<li>Use <code><a href="reference/as.mo.html">as.mo()</a></code> to get a microbial ID. The IDs are human readable for the trained eye - the ID of <em>Klebsiella pneumoniae</em> is “B_KLBSL_PNE” (B stands for Bacteria) and the ID of <em>S. aureus</em> is “B_STPHY_AUR”. The function takes almost any text as input that looks like the name or code of a microorganism like “E. coli”, “esco” or “esccol” and tries to find expected results using intelligent rules combined with the included Catalogue of Life data set. It only takes milliseconds to find results, please see our <a href="./articles/benchmarks.html">benchmarks</a>. Moreover, it can group <em>Staphylococci</em> into coagulase negative and positive (CoNS and CoPS, see <a href="./reference/as.mo.html#source">source</a>) and can categorise <em>Streptococci</em> into Lancefield groups (like beta-haemolytic <em>Streptococcus</em> Group B, <a href="./reference/as.mo.html#source">source</a>).</li>
<li>Use <code><a href="reference/as.ab.html">as.ab()</a></code> to get an antibiotic ID. Like microbial IDs, these IDs are also human readable based on those used by EARS-Net. For example, the ID of amoxicillin is <code>AMX</code> and the ID of gentamicin is <code>GEN</code>. The <code><a href="reference/as.ab.html">as.ab()</a></code> function also uses intelligent rules to find results like accepting misspelling, trade names and abbrevations used in many laboratory systems. For instance, the values “Furabid”, “Furadantin”, “nitro” all return the ID of Nitrofurantoine. To accomplish this, the package contains a database with most LIS codes, official names, trade names, DDDs and categories of antibiotics. The function <code><a href="reference/as.atc.html">as.atc()</a></code> will return the ATC code of an antibiotic as defined by the WHO.</li>
<li>Use <code><a href="reference/as.ab.html">as.ab()</a></code> to get an antibiotic ID. Like microbial IDs, these IDs are also human readable based on those used by EARS-Net. For example, the ID of amoxicillin is <code>AMX</code> and the ID of gentamicin is <code>GEN</code>. The <code><a href="reference/as.ab.html">as.ab()</a></code> function also uses intelligent rules to find results like accepting misspelling, trade names and abbrevations used in many laboratory systems. For instance, the values “Furabid”, “Furadantin”, “nitro” all return the ID of Nitrofurantoine. To accomplish this, the package contains a database with most LIS codes, official names, trade names, DDDs and categories of antibiotics. The function <code><a href="reference/AMR-deprecated.html">as.atc()</a></code> will return the ATC code of an antibiotic as defined by the WHO.</li>
<li>Use <code><a href="reference/as.rsi.html">as.rsi()</a></code> to get antibiotic interpretations based on raw MIC values (in mg/L) or disk diffusion values (in mm), or transform existing values to valid antimicrobial results. It produces just S, I or R based on your input and warns about invalid values. Even values like “&lt;=0.002; S” (combined MIC/RSI) will result in “S”.</li>
<li>Use <code><a href="reference/as.mic.html">as.mic()</a></code> to cleanse your MIC values. It produces a so-called factor (called <em>ordinal</em> in SPSS) with valid MIC values as levels. A value like “&lt;=0.002; S” (combined MIC/RSI) will result in “&lt;=0.002”.</li>
</ul>

View File

@ -78,7 +78,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9004</span>
</span>
</div>
@ -232,11 +232,23 @@
</div>
<div id="amr-0719003" class="section level1">
<div id="amr-0719004" class="section level1">
<h1 class="page-header">
<a href="#amr-0719003" class="anchor"></a>AMR 0.7.1.9003<small> Unreleased </small>
<a href="#amr-0719004" class="anchor"></a>AMR 0.7.1.9004<small> Unreleased </small>
</h1>
<p>(no code changes yet)</p>
<div id="changed" class="section level3">
<h3 class="hasAnchor">
<a href="#changed" class="anchor"></a>Changed</h3>
<ul>
<li>Removed class <code>atc</code> - using <code><a href="../reference/AMR-deprecated.html">as.atc()</a></code> is now deprecated in favour of <code><a href="../reference/ab_property.html">ab_atc()</a></code> and this will return a character, not the <code>atc</code> class anymore</li>
<li>Removed deprecated functions <code>abname()</code>, <code>ab_official()</code>, <code>atc_name()</code>, <code>atc_official()</code>, <code>atc_property()</code>, <code>atc_tradenames()</code>, <code>atc_trivial_nl()</code>
</li>
<li>Fix and speed improvement for <code><a href="../reference/mo_property.html">mo_shortname()</a></code>
</li>
<li>Fix for <code><a href="../reference/as.mo.html">as.mo()</a></code> where misspelled input would not be understood</li>
<li>Fix for <code>also_single_tested</code> parameter in <code>count_*</code> functions</li>
</ul>
</div>
</div>
<div id="amr-071" class="section level1">
<h1 class="page-header">
@ -284,9 +296,9 @@
<li><p>Function <code><a href="../reference/mo_property.html">mo_synonyms()</a></code> to get all previously accepted taxonomic names of a microorganism</p></li>
</ul>
</div>
<div id="changed" class="section level4">
<div id="changed-1" class="section level4">
<h4 class="hasAnchor">
<a href="#changed" class="anchor"></a>Changed</h4>
<a href="#changed-1" class="anchor"></a>Changed</h4>
<ul>
<li>Column names of output <code><a href="../reference/count.html">count_df()</a></code> and <code><a href="../reference/portion.html">portion_df()</a></code> are now lowercase</li>
<li>Fixed bug in translation of microorganism names</li>
@ -333,9 +345,9 @@
<li>Added guidelines of the WHO to determine multi-drug resistance (MDR) for TB (<code><a href="../reference/mdro.html">mdr_tb()</a></code>) and added a new vignette about MDR. Read this tutorial <a href="https://msberends.gitlab.io/AMR/articles/MDR.html">here on our website</a>.</li>
</ul>
</div>
<div id="changed-1" class="section level4">
<div id="changed-2" class="section level4">
<h4 class="hasAnchor">
<a href="#changed-1" class="anchor"></a>Changed</h4>
<a href="#changed-2" class="anchor"></a>Changed</h4>
<ul>
<li>Fixed a critical bug in <code><a href="../reference/first_isolate.html">first_isolate()</a></code> where missing species would lead to incorrect FALSEs. This bug was not present in AMR v0.5.0, but was in v0.6.0 and v0.6.1.</li>
<li>Fixedd a bug in <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> where antibiotics from WHONET software would not be recognised</li>
@ -420,9 +432,9 @@ Please <a href="https://gitlab.com/msberends/AMR/issues/new?issue%5Btitle%5D=EUC
<h1 class="page-header">
<a href="#amr-061" class="anchor"></a>AMR 0.6.1<small> 2019-03-29 </small>
</h1>
<div id="changed-2" class="section level4">
<div id="changed-3" class="section level4">
<h4 class="hasAnchor">
<a href="#changed-2" class="anchor"></a>Changed</h4>
<a href="#changed-3" class="anchor"></a>Changed</h4>
<ul>
<li>Fixed a critical bug when using <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> with <code>verbose = TRUE</code>
</li>
@ -488,14 +500,14 @@ This data is updated annually - check the included version with the new function
</li>
<li>
<p>All <code>ab_*</code> functions are deprecated and replaced by <code>atc_*</code> functions:</p>
<div class="sourceCode" id="cb6"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb6-1" title="1">ab_property -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_property</a></span>()</a>
<a class="sourceLine" id="cb6-2" title="2">ab_name -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_name</a></span>()</a>
<a class="sourceLine" id="cb6-3" title="3">ab_official -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_official</a></span>()</a>
<a class="sourceLine" id="cb6-4" title="4">ab_trivial_nl -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_trivial_nl</a></span>()</a>
<div class="sourceCode" id="cb6"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb6-1" title="1">ab_property -&gt;<span class="st"> </span><span class="kw">atc_property</span>()</a>
<a class="sourceLine" id="cb6-2" title="2">ab_name -&gt;<span class="st"> </span><span class="kw">atc_name</span>()</a>
<a class="sourceLine" id="cb6-3" title="3">ab_official -&gt;<span class="st"> </span><span class="kw">atc_official</span>()</a>
<a class="sourceLine" id="cb6-4" title="4">ab_trivial_nl -&gt;<span class="st"> </span><span class="kw">atc_trivial_nl</span>()</a>
<a class="sourceLine" id="cb6-5" title="5">ab_certe -&gt;<span class="st"> </span><span class="kw">atc_certe</span>()</a>
<a class="sourceLine" id="cb6-6" title="6">ab_umcg -&gt;<span class="st"> </span><span class="kw">atc_umcg</span>()</a>
<a class="sourceLine" id="cb6-7" title="7">ab_tradenames -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_tradenames</a></span>()</a></code></pre></div>
These functions use <code><a href="../reference/as.atc.html">as.atc()</a></code> internally. The old <code>atc_property</code> has been renamed <code><a href="../reference/atc_online.html">atc_online_property()</a></code>. This is done for two reasons: firstly, not all ATC codes are of antibiotics (ab) but can also be of antivirals or antifungals. Secondly, the input must have class <code>atc</code> or must be coerable to this class. Properties of these classes should start with the same class name, analogous to <code><a href="../reference/as.mo.html">as.mo()</a></code> and e.g. <code>mo_genus</code>.</li>
<a class="sourceLine" id="cb6-7" title="7">ab_tradenames -&gt;<span class="st"> </span><span class="kw">atc_tradenames</span>()</a></code></pre></div>
These functions use <code><a href="../reference/AMR-deprecated.html">as.atc()</a></code> internally. The old <code>atc_property</code> has been renamed <code><a href="../reference/atc_online.html">atc_online_property()</a></code>. This is done for two reasons: firstly, not all ATC codes are of antibiotics (ab) but can also be of antivirals or antifungals. Secondly, the input must have class <code>atc</code> or must be coerable to this class. Properties of these classes should start with the same class name, analogous to <code><a href="../reference/as.mo.html">as.mo()</a></code> and e.g. <code>mo_genus</code>.</li>
<li>New functions <code><a href="../reference/mo_source.html">set_mo_source()</a></code> and <code><a href="../reference/mo_source.html">get_mo_source()</a></code> to use your own predefined MO codes as input for <code><a href="../reference/as.mo.html">as.mo()</a></code> and consequently all <code>mo_*</code> functions</li>
<li>Support for the upcoming <a href="https://dplyr.tidyverse.org"><code>dplyr</code></a> version 0.8.0</li>
<li>New function <code><a href="../reference/guess_ab_col.html">guess_ab_col()</a></code> to find an antibiotic column in a table</li>
@ -526,9 +538,9 @@ These functions use <code><a href="../reference/as.atc.html">as.atc()</a></code>
<li><p>New vignettes about how to conduct AMR analysis, predict antimicrobial resistance, use the <em>G</em>-test and more. These are also available (and even easier readable) on our website: <a href="https://msberends.gitlab.io/AMR" class="uri">https://msberends.gitlab.io/AMR</a>.</p></li>
</ul>
</div>
<div id="changed-3" class="section level4">
<div id="changed-4" class="section level4">
<h4 class="hasAnchor">
<a href="#changed-3" class="anchor"></a>Changed</h4>
<a href="#changed-4" class="anchor"></a>Changed</h4>
<ul>
<li>Function <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code>:
<ul>
@ -543,7 +555,7 @@ These functions use <code><a href="../reference/as.atc.html">as.atc()</a></code>
<li>Removed columns <code>atc_group1_nl</code> and <code>atc_group2_nl</code> from the <code>antibiotics</code> data set</li>
<li>Functions <code>atc_ddd()</code> and <code>atc_groups()</code> have been renamed <code><a href="../reference/atc_online.html">atc_online_ddd()</a></code> and <code><a href="../reference/atc_online.html">atc_online_groups()</a></code>. The old functions are deprecated and will be removed in a future version.</li>
<li>Function <code>guess_mo()</code> is now deprecated in favour of <code><a href="../reference/as.mo.html">as.mo()</a></code> and will be removed in future versions</li>
<li>Function <code>guess_atc()</code> is now deprecated in favour of <code><a href="../reference/as.atc.html">as.atc()</a></code> and will be removed in future versions</li>
<li>Function <code>guess_atc()</code> is now deprecated in favour of <code><a href="../reference/AMR-deprecated.html">as.atc()</a></code> and will be removed in future versions</li>
<li>Improvements for <code><a href="../reference/as.mo.html">as.mo()</a></code>:
<ul>
<li>
@ -681,9 +693,9 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<li>Functions <code>mo_authors</code> and <code>mo_year</code> to get specific values about the scientific reference of a taxonomic entry</li>
</ul>
</div>
<div id="changed-4" class="section level4">
<div id="changed-5" class="section level4">
<h4 class="hasAnchor">
<a href="#changed-4" class="anchor"></a>Changed</h4>
<a href="#changed-5" class="anchor"></a>Changed</h4>
<ul>
<li>Functions <code>MDRO</code>, <code>BRMO</code>, <code>MRGN</code> and <code>EUCAST_exceptional_phenotypes</code> were renamed to <code>mdro</code>, <code>brmo</code>, <code>mrgn</code> and <code>eucast_exceptional_phenotypes</code>
</li>
@ -865,14 +877,14 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<li><p>Renamed <code>septic_patients$sex</code> to <code>septic_patients$gender</code></p></li>
</ul>
</div>
<div id="changed-5" class="section level4">
<div id="changed-6" class="section level4">
<h4 class="hasAnchor">
<a href="#changed-5" class="anchor"></a>Changed</h4>
<a href="#changed-6" class="anchor"></a>Changed</h4>
<ul>
<li>Added three antimicrobial agents to the <code>antibiotics</code> data set: Terbinafine (D01BA02), Rifaximin (A07AA11) and Isoconazole (D01AC05)</li>
<li>
<p>Added 163 trade names to the <code>antibiotics</code> data set, it now contains 298 different trade names in total, e.g.:</p>
<div class="sourceCode" id="cb21"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb21-1" title="1"><span class="kw"><a href="../reference/AMR-deprecated.html">ab_official</a></span>(<span class="st">"Bactroban"</span>)</a>
<div class="sourceCode" id="cb21"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb21-1" title="1"><span class="kw">ab_official</span>(<span class="st">"Bactroban"</span>)</a>
<a class="sourceLine" id="cb21-2" title="2"><span class="co"># [1] "Mupirocin"</span></a>
<a class="sourceLine" id="cb21-3" title="3"><span class="kw"><a href="../reference/ab_property.html">ab_name</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="st">"Bactroban"</span>, <span class="st">"Amoxil"</span>, <span class="st">"Zithromax"</span>, <span class="st">"Floxapen"</span>))</a>
<a class="sourceLine" id="cb21-4" title="4"><span class="co"># [1] "Mupirocin" "Amoxicillin" "Azithromycin" "Flucloxacillin"</span></a>
@ -976,7 +988,7 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<li>
<del>Function <code>ratio</code> to transform a vector of values to a preset ratio</del>
<ul>
<li><del>For example: <code><a href="../reference/AMR-deprecated.html">ratio(c(10, 500, 10), ratio = "1:2:1")</a></code> would return <code>130, 260, 130</code></del></li>
<li><del>For example: <code>ratio(c(10, 500, 10), ratio = "1:2:1")</code> would return <code>130, 260, 130</code></del></li>
</ul>
</li>
<li>Support for Addins menu in RStudio to quickly insert <code>%in%</code> or <code>%like%</code> (and give them keyboard shortcuts), or to view the datasets that come with this package</li>
@ -1002,9 +1014,9 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
</li>
</ul>
</div>
<div id="changed-6" class="section level4">
<div id="changed-7" class="section level4">
<h4 class="hasAnchor">
<a href="#changed-6" class="anchor"></a>Changed</h4>
<a href="#changed-7" class="anchor"></a>Changed</h4>
<ul>
<li>Improvements for forecasting with <code>resistance_predict</code> and added more examples</li>
<li>More antibiotics added as parameters for EUCAST rules</li>
@ -1034,7 +1046,7 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
</li>
<li>Now possible to coerce MIC values with a space between operator and value, i.e. <code><a href="../reference/as.mic.html">as.mic("&lt;= 0.002")</a></code> now works</li>
<li>Classes <code>rsi</code> and <code>mic</code> do not add the attribute <code>package.version</code> anymore</li>
<li>Added <code>"groups"</code> option for <code><a href="../reference/AMR-deprecated.html">atc_property(..., property)</a></code>. It will return a vector of the ATC hierarchy as defined by the <a href="https://www.whocc.no/atc/structure_and_principles/">WHO</a>. The new function <code>atc_groups</code> is a convenient wrapper around this.</li>
<li>Added <code>"groups"</code> option for <code>atc_property(..., property)</code>. It will return a vector of the ATC hierarchy as defined by the <a href="https://www.whocc.no/atc/structure_and_principles/">WHO</a>. The new function <code>atc_groups</code> is a convenient wrapper around this.</li>
<li>Build-in host check for <code>atc_property</code> as it requires the host set by <code>url</code> to be responsive</li>
<li>Improved <code>first_isolate</code> algorithm to exclude isolates where bacteria ID or genus is unavailable</li>
<li>Fix for warning <em>hybrid evaluation forced for row_number</em> (<a href="https://github.com/tidyverse/dplyr/commit/924b62"><code>924b62</code></a>) from the <code>dplyr</code> package v0.7.5 and above</li>
@ -1088,9 +1100,9 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<li>New print format for <code>tibble</code>s and <code>data.table</code>s</li>
</ul>
</div>
<div id="changed-7" class="section level4">
<div id="changed-8" class="section level4">
<h4 class="hasAnchor">
<a href="#changed-7" class="anchor"></a>Changed</h4>
<a href="#changed-8" class="anchor"></a>Changed</h4>
<ul>
<li>Fixed <code>rsi</code> class for vectors that contain only invalid antimicrobial interpretations</li>
<li>Renamed dataset <code>ablist</code> to <code>antibiotics</code>
@ -1147,7 +1159,7 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<div id="tocnav">
<h2>Contents</h2>
<ul class="nav nav-pills nav-stacked">
<li><a href="#amr-0719003">0.7.1.9003</a></li>
<li><a href="#amr-0719004">0.7.1.9004</a></li>
<li><a href="#amr-071">0.7.1</a></li>
<li><a href="#amr-070">0.7.0</a></li>
<li><a href="#amr-061">0.6.1</a></li>

View File

@ -80,7 +80,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9004</span>
</span>
</div>
@ -241,21 +241,7 @@
</div>
<pre class="usage"><span class='fu'>ratio</span>(<span class='no'>x</span>, <span class='no'>ratio</span>)
<span class='fu'>abname</span>(<span class='no'>...</span>)
<span class='fu'>atc_property</span>(<span class='no'>...</span>)
<span class='fu'>atc_official</span>(<span class='no'>...</span>)
<span class='fu'>ab_official</span>(<span class='no'>...</span>)
<span class='fu'>atc_name</span>(<span class='no'>...</span>)
<span class='fu'>atc_trivial_nl</span>(<span class='no'>...</span>)
<span class='fu'>atc_tradenames</span>(<span class='no'>...</span>)</pre>
<pre class="usage"><span class='fu'>as.atc</span>(<span class='no'>x</span>)</pre>
<h2 class="hasAnchor" id="read-more-on-our-website-"><a class="anchor" href="#read-more-on-our-website-"></a>Read more on our website!</h2>

View File

@ -80,7 +80,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9004</span>
</span>
</div>
@ -271,7 +271,7 @@
<dt><code>Inducible clindamycin resistance</code></dt><dd><p>Clindamycin can be induced?</p></dd>
<dt><code>Comment</code></dt><dd><p>Other comments</p></dd>
<dt><code>Date of data entry</code></dt><dd><p>Date this data was entered in WHONET</p></dd>
<dt><code>AMP_ND10:CIP_EE</code></dt><dd><p>27 different antibiotics. You can lookup the abbreviatons in the <code><a href='antibiotics.html'>antibiotics</a></code> data set, or use e.g. <code><a href='AMR-deprecated.html'>atc_name</a>("AMP")</code> to get the official name immediately. Before analysis, you should transform this to a valid antibiotic class, using <code><a href='as.rsi.html'>as.rsi</a></code>.</p></dd>
<dt><code>AMP_ND10:CIP_EE</code></dt><dd><p>27 different antibiotics. You can lookup the abbreviatons in the <code><a href='antibiotics.html'>antibiotics</a></code> data set, or use e.g. <code><a href='ab_property.html'>ab_name</a>("AMP")</code> to get the official name immediately. Before analysis, you should transform this to a valid antibiotic class, using <code><a href='as.rsi.html'>as.rsi</a></code>.</p></dd>
</dl>
<h2 class="hasAnchor" id="read-more-on-our-website-"><a class="anchor" href="#read-more-on-our-website-"></a>Read more on our website!</h2>

View File

@ -81,7 +81,7 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9004</span>
</span>
</div>
@ -253,9 +253,9 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
<span class='fu'>count_S</span>(<span class='no'>...</span>, <span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>count_all</span>(<span class='no'>...</span>)
<span class='fu'>count_all</span>(<span class='no'>...</span>, <span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>n_rsi</span>(<span class='no'>...</span>)
<span class='fu'>n_rsi</span>(<span class='no'>...</span>, <span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>count_df</span>(<span class='no'>data</span>, <span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='st'>"name"</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(),
<span class='kw'>combine_SI</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='kw'>combine_IR</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)</pre>
@ -269,7 +269,7 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
</tr>
<tr>
<th>also_single_tested</th>
<td><p>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</code> and R in case of <code>portion_R</code>). <strong>This would lead to selection bias in almost all cases.</strong></p></td>
<td><p>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</code> and R in case of <code>portion_R</code>). <strong>This could lead to selection bias.</strong></p></td>
</tr>
<tr>
<th>data</th>

View File

@ -80,7 +80,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9004</span>
</span>
</div>
@ -244,17 +244,16 @@
<pre class="usage"><span class='fu'>ggplot_rsi</span>(<span class='no'>data</span>, <span class='kw'>position</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>x</span> <span class='kw'>=</span> <span class='st'>"antibiotic"</span>,
<span class='kw'>fill</span> <span class='kw'>=</span> <span class='st'>"interpretation"</span>, <span class='kw'>facet</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>breaks</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/seq'>seq</a></span>(<span class='fl'>0</span>, <span class='fl'>1</span>, <span class='fl'>0.1</span>),
<span class='kw'>limits</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='st'>"name"</span>, <span class='kw'>combine_SI</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>,
<span class='kw'>combine_IR</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='kw'>fun</span> <span class='kw'>=</span> <span class='no'>count_df</span>,
<span class='kw'>nrow</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>colours</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/c'>c</a></span>(<span class='kw'>S</span> <span class='kw'>=</span> <span class='st'>"#61a8ff"</span>, <span class='kw'>SI</span> <span class='kw'>=</span> <span class='st'>"#61a8ff"</span>, <span class='kw'>I</span> <span class='kw'>=</span>
<span class='st'>"#61f7ff"</span>, <span class='kw'>IR</span> <span class='kw'>=</span> <span class='st'>"#ff6961"</span>, <span class='kw'>R</span> <span class='kw'>=</span> <span class='st'>"#ff6961"</span>), <span class='kw'>datalabels</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>,
<span class='kw'>datalabels.size</span> <span class='kw'>=</span> <span class='fl'>2.5</span>, <span class='kw'>datalabels.colour</span> <span class='kw'>=</span> <span class='st'>"gray15"</span>, <span class='kw'>title</span> <span class='kw'>=</span> <span class='kw'>NULL</span>,
<span class='kw'>subtitle</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>caption</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>x.title</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>y.title</span> <span class='kw'>=</span> <span class='kw'>NULL</span>,
<span class='no'>...</span>)
<span class='kw'>combine_IR</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='kw'>nrow</span> <span class='kw'>=</span> <span class='kw'>NULL</span>,
<span class='kw'>colours</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/c'>c</a></span>(<span class='kw'>S</span> <span class='kw'>=</span> <span class='st'>"#61a8ff"</span>, <span class='kw'>SI</span> <span class='kw'>=</span> <span class='st'>"#61a8ff"</span>, <span class='kw'>I</span> <span class='kw'>=</span> <span class='st'>"#61f7ff"</span>, <span class='kw'>IR</span> <span class='kw'>=</span>
<span class='st'>"#ff6961"</span>, <span class='kw'>R</span> <span class='kw'>=</span> <span class='st'>"#ff6961"</span>), <span class='kw'>datalabels</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='kw'>datalabels.size</span> <span class='kw'>=</span> <span class='fl'>2.5</span>,
<span class='kw'>datalabels.colour</span> <span class='kw'>=</span> <span class='st'>"gray15"</span>, <span class='kw'>title</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>subtitle</span> <span class='kw'>=</span> <span class='kw'>NULL</span>,
<span class='kw'>caption</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>x.title</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>y.title</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='no'>...</span>)
<span class='fu'>geom_rsi</span>(<span class='kw'>position</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>x</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/c'>c</a></span>(<span class='st'>"antibiotic"</span>, <span class='st'>"interpretation"</span>),
<span class='kw'>fill</span> <span class='kw'>=</span> <span class='st'>"interpretation"</span>, <span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='st'>"name"</span>,
<span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='kw'>combine_SI</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='kw'>combine_IR</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>,
<span class='kw'>fun</span> <span class='kw'>=</span> <span class='no'>count_df</span>, <span class='no'>...</span>)
<span class='no'>...</span>)
<span class='fu'>facet_rsi</span>(<span class='kw'>facet</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/c'>c</a></span>(<span class='st'>"interpretation"</span>, <span class='st'>"antibiotic"</span>), <span class='kw'>nrow</span> <span class='kw'>=</span> <span class='kw'>NULL</span>)
@ -316,10 +315,6 @@
<th>language</th>
<td><p>language of the returned text, defaults to system language (see <code><a href='translate.html'>get_locale</a></code>) and can also be set with <code><a href='https://www.rdocumentation.org/packages/base/topics/options'>getOption</a>("AMR_locale")</code>. Use <code>language = NULL</code> or <code>language = ""</code> to prevent translation.</p></td>
</tr>
<tr>
<th>fun</th>
<td><p>function to transform <code>data</code>, either <code><a href='count.html'>count_df</a></code> (default) or <code><a href='portion.html'>portion_df</a></code></p></td>
</tr>
<tr>
<th>nrow</th>
<td><p>(when using <code>facet</code>) number of rows</p></td>
@ -330,7 +325,7 @@
</tr>
<tr>
<th>datalabels</th>
<td><p>show datalabels using <code>labels_rsi_count</code>, will only be shown when <code>fun = count_df</code></p></td>
<td><p>show datalabels using <code>labels_rsi_count</code></p></td>
</tr>
<tr>
<th>datalabels.size</th>
@ -370,7 +365,7 @@
<p>At default, the names of antibiotics will be shown on the plots using <code><a href='ab_property.html'>ab_name</a></code>. This can be set with the <code>translate_ab</code> parameter. See <code><a href='count.html'>count_df</a></code>.</p>
<p><strong>The functions</strong><br />
<code>geom_rsi</code> will take any variable from the data that has an <code>rsi</code> class (created with <code><a href='as.rsi.html'>as.rsi</a></code>) using <code>fun</code> (<code><a href='count.html'>count_df</a></code> at default, can also be <code><a href='portion.html'>portion_df</a></code>) 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.</p>
<code>geom_rsi</code> will take any variable from the data that has an <code>rsi</code> class (created with <code><a href='as.rsi.html'>as.rsi</a></code>) using <code><a href='portion.html'>rsi_df</a></code> 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.</p>
<p><code>facet_rsi</code> creates 2d plots (at default based on S/I/R) using <code><a href='https://ggplot2.tidyverse.org/reference/facet_wrap.html'>facet_wrap</a></code>.</p>
<p><code>scale_y_percent</code> transforms the y axis to a 0 to 100% range using <code>scale_continuous</code>.</p>
<p><code>scale_rsi_colours</code> sets colours to the bars: pastel blue for S, pastel turquoise for I and pastel red for R, using <code>scale_brewer</code>.</p>
@ -410,7 +405,7 @@
<span class='co'># get only portions and no counts:</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>AMX</span>, <span class='no'>NIT</span>, <span class='no'>FOS</span>, <span class='no'>TMP</span>, <span class='no'>CIP</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>ggplot_rsi</span>(<span class='kw'>fun</span> <span class='kw'>=</span> <span class='no'>portion_df</span>)
<span class='fu'>ggplot_rsi</span>(<span class='kw'>datalabels</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='co'># add other ggplot2 parameters as you like:</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>

View File

@ -78,7 +78,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9004</span>
</span>
</div>
@ -286,12 +286,6 @@
<td><p>Transform to antibiotic ID</p></td>
</tr><tr>
<td>
<p><code><a href="as.atc.html">as.atc()</a></code> <code><a href="as.atc.html">is.atc()</a></code> </p>
</td>
<td><p>Transform to ATC code</p></td>
</tr><tr>
<td>
<p><code><a href="as.disk.html">as.disk()</a></code> <code><a href="as.disk.html">is.disk()</a></code> </p>
</td>
@ -569,7 +563,7 @@
<tr>
<td>
<p><code><a href="AMR-deprecated.html">ratio()</a></code> <code><a href="AMR-deprecated.html">abname()</a></code> <code><a href="AMR-deprecated.html">atc_property()</a></code> <code><a href="AMR-deprecated.html">atc_official()</a></code> <code><a href="AMR-deprecated.html">ab_official()</a></code> <code><a href="AMR-deprecated.html">atc_name()</a></code> <code><a href="AMR-deprecated.html">atc_trivial_nl()</a></code> <code><a href="AMR-deprecated.html">atc_tradenames()</a></code> </p>
<p><code><a href="AMR-deprecated.html">as.atc()</a></code> </p>
</td>
<td><p>Deprecated functions</p></td>
</tr>

View File

@ -80,7 +80,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9004</span>
</span>
</div>
@ -417,7 +417,7 @@ This package contains the complete taxonomic tree of almost all microorganisms (
<span class='fu'>mo_fullname</span>(<span class='st'>"S. pyo"</span>) <span class='co'># "Streptococcus pyogenes"</span>
<span class='fu'>mo_fullname</span>(<span class='st'>"S. pyo"</span>, <span class='kw'>Lancefield</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) <span class='co'># "Streptococcus group A"</span>
<span class='fu'>mo_shortname</span>(<span class='st'>"S. pyo"</span>) <span class='co'># "S. pyogenes"</span>
<span class='fu'>mo_shortname</span>(<span class='st'>"S. pyo"</span>, <span class='kw'>Lancefield</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) <span class='co'># "GAS" ('Group A streptococci')</span>
<span class='fu'>mo_shortname</span>(<span class='st'>"S. pyo"</span>, <span class='kw'>Lancefield</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) <span class='co'># "GAS" (='Group A Streptococci')</span>
<span class='co'># language support for German, Dutch, Spanish, Portuguese, Italian and French</span>

View File

@ -81,7 +81,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9004</span>
</span>
</div>
@ -283,7 +283,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
</tr>
<tr>
<th>also_single_tested</th>
<td><p>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</code> and R in case of <code>portion_R</code>). <strong>This would lead to selection bias in almost all cases.</strong></p></td>
<td><p>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</code> and R in case of <code>portion_R</code>). <strong>This could lead to selection bias.</strong></p></td>
</tr>
<tr>
<th>data</th>
@ -403,6 +403,15 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'>portion_S</span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>) <span class='co'># S = 92.3%</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>) <span class='co'># n = 1798</span>
<span class='co'># Using `also_single_tested` can be useful ...</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'>portion_S</span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>,
<span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) <span class='co'># S = 92.6%</span>
<span class='co'># ... but can also lead to selection bias - the data only has 2,000 rows:</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>AMC</span>, <span class='no'>GEN</span>,
<span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) <span class='co'># n = 2555</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/group_by.html'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>

View File

@ -80,7 +80,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.1.9004</span>
</span>
</div>
@ -255,7 +255,7 @@
<dt><code>gender</code></dt><dd><p>gender of the patient</p></dd>
<dt><code>patient_id</code></dt><dd><p>ID of the patient, first 10 characters of an SHA hash containing irretrievable information</p></dd>
<dt><code>mo</code></dt><dd><p>ID of microorganism created with <code><a href='as.mo.html'>as.mo</a></code>, see also <code><a href='microorganisms.html'>microorganisms</a></code></p></dd>
<dt><code>peni:rifa</code></dt><dd><p>40 different antibiotics with class <code>rsi</code> (see <code><a href='as.rsi.html'>as.rsi</a></code>); these column names occur in <code><a href='antibiotics.html'>antibiotics</a></code> data set and can be translated with <code><a href='AMR-deprecated.html'>abname</a></code></p></dd>
<dt><code>peni:rifa</code></dt><dd><p>40 different antibiotics with class <code>rsi</code> (see <code><a href='as.rsi.html'>as.rsi</a></code>); these column names occur in <code><a href='antibiotics.html'>antibiotics</a></code> data set and can be translated with <code><a href='ab_property.html'>ab_name</a></code></p></dd>
</dl>
<h2 class="hasAnchor" id="read-more-on-our-website-"><a class="anchor" href="#read-more-on-our-website-"></a>Read more on our website!</h2>

View File

@ -30,9 +30,6 @@
<url>
<loc>https://msberends.gitlab.io/AMR/reference/as.ab.html</loc>
</url>
<url>
<loc>https://msberends.gitlab.io/AMR/reference/as.atc.html</loc>
</url>
<url>
<loc>https://msberends.gitlab.io/AMR/reference/as.disk.html</loc>
</url>

View File

@ -2,31 +2,10 @@
% Please edit documentation in R/deprecated.R
\name{AMR-deprecated}
\alias{AMR-deprecated}
\alias{ratio}
\alias{abname}
\alias{atc_property}
\alias{atc_official}
\alias{ab_official}
\alias{atc_name}
\alias{atc_trivial_nl}
\alias{atc_tradenames}
\alias{as.atc}
\title{Deprecated functions}
\usage{
ratio(x, ratio)
abname(...)
atc_property(...)
atc_official(...)
ab_official(...)
atc_name(...)
atc_trivial_nl(...)
atc_tradenames(...)
as.atc(x)
}
\description{
These functions are so-called '\link{Deprecated}'. They will be removed in a future release. Using the functions will give a warning with the name of the function it has been replaced by (if there is one).

View File

@ -31,7 +31,7 @@
\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}}.}
}}
\usage{
WHONET

View File

@ -1,55 +0,0 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/atc.R
\name{as.atc}
\alias{as.atc}
\alias{atc}
\alias{is.atc}
\title{Transform to ATC code}
\usage{
as.atc(x)
is.atc(x)
}
\arguments{
\item{x}{character vector to determine \code{ATC} code}
}
\value{
Character (vector) with class \code{"atc"}. Unknown values will return \code{NA}.
}
\description{
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.
}
\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/}
}
\section{WHOCC}{
\if{html}{\figure{logo_who.png}{options: height=60px style=margin-bottom:5px} \cr}
This package contains \strong{all ~450 antimicrobial drugs} and their Anatomical Therapeutic Chemical (ATC) codes, ATC groups and Defined Daily Dose (DDD) from the World Health Organization Collaborating Centre for Drug Statistics Methodology (WHOCC, \url{https://www.whocc.no}) and the Pharmaceuticals Community Register of the European Commission (\url{http://ec.europa.eu/health/documents/community-register/html/atc.htm}).
These have become the gold standard for international drug utilisation monitoring and research.
The WHOCC is located in Oslo at the Norwegian Institute of Public Health and funded by the Norwegian government. The European Commission is the executive of the European Union and promotes its general interest.
}
\section{Read more on our website!}{
On our website \url{https://msberends.gitlab.io/AMR} you can find \href{https://msberends.gitlab.io/AMR/articles/AMR.html}{a tutorial} about how to conduct AMR analysis, the \href{https://msberends.gitlab.io/AMR/reference}{complete documentation of all functions} (which reads a lot easier than here in R) and \href{https://msberends.gitlab.io/AMR/articles/WHONET.html}{an example analysis using WHONET data}.
}
\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")
}
\seealso{
\code{\link{antibiotics}} for the dataframe that is being used to determine ATCs.
}
\keyword{atc}

View File

@ -25,9 +25,9 @@ count_SI(..., also_single_tested = FALSE)
count_S(..., also_single_tested = FALSE)
count_all(...)
count_all(..., also_single_tested = FALSE)
n_rsi(...)
n_rsi(..., also_single_tested = FALSE)
count_df(data, translate_ab = "name", language = get_locale(),
combine_SI = TRUE, combine_IR = FALSE)
@ -35,7 +35,7 @@ count_df(data, translate_ab = "name", language = get_locale(),
\arguments{
\item{...}{one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with \code{\link{as.rsi}} if needed.}
\item{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.}}
\item{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.}}
\item{data}{a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}})}

View File

@ -13,17 +13,16 @@
ggplot_rsi(data, position = NULL, x = "antibiotic",
fill = "interpretation", facet = NULL, breaks = seq(0, 1, 0.1),
limits = NULL, translate_ab = "name", combine_SI = TRUE,
combine_IR = FALSE, language = get_locale(), fun = count_df,
nrow = NULL, colours = c(S = "#61a8ff", SI = "#61a8ff", I =
"#61f7ff", IR = "#ff6961", R = "#ff6961"), datalabels = TRUE,
datalabels.size = 2.5, datalabels.colour = "gray15", title = NULL,
subtitle = NULL, caption = NULL, x.title = NULL, y.title = NULL,
...)
combine_IR = FALSE, language = get_locale(), nrow = NULL,
colours = c(S = "#61a8ff", SI = "#61a8ff", I = "#61f7ff", IR =
"#ff6961", R = "#ff6961"), datalabels = TRUE, datalabels.size = 2.5,
datalabels.colour = "gray15", title = NULL, subtitle = NULL,
caption = NULL, x.title = NULL, y.title = NULL, ...)
geom_rsi(position = NULL, x = c("antibiotic", "interpretation"),
fill = "interpretation", translate_ab = "name",
language = get_locale(), combine_SI = TRUE, combine_IR = FALSE,
fun = count_df, ...)
...)
facet_rsi(facet = c("interpretation", "antibiotic"), nrow = NULL)
@ -61,13 +60,11 @@ labels_rsi_count(position = NULL, x = "antibiotic",
\item{language}{language of the returned text, defaults to system language (see \code{\link{get_locale}}) and can also be set with \code{\link{getOption}("AMR_locale")}. Use \code{language = NULL} or \code{language = ""} to prevent translation.}
\item{fun}{function to transform \code{data}, either \code{\link{count_df}} (default) or \code{\link{portion_df}}}
\item{nrow}{(when using \code{facet}) number of rows}
\item{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.}
\item{datalabels}{show datalabels using \code{labels_rsi_count}, will only be shown when \code{fun = count_df}}
\item{datalabels}{show datalabels using \code{labels_rsi_count}}
\item{datalabels.size}{size of the datalabels}
@ -92,7 +89,7 @@ Use these functions to create bar plots for antimicrobial resistance analysis. A
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}}.
@ -136,7 +133,7 @@ septic_patients \%>\%
# 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 \%>\%

View File

@ -188,7 +188,7 @@ mo_shortname("S. epi", Becker = TRUE) # "CoNS"
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

View File

@ -46,7 +46,7 @@ rsi_df(data, translate_ab = "name", language = get_locale(),
\item{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\%"}.}
\item{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.}}
\item{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.}}
\item{data}{a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}})}
@ -155,6 +155,15 @@ septic_patients \%>\% count_all(GEN) # n = 1855
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

@ -15,7 +15,7 @@
\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}}}
}}
\usage{
septic_patients

View File

@ -31,10 +31,9 @@ $('head').append('<!-- Updated Font Awesome library --><link rel="stylesheet" hr
$( document ).ready(function() {
// add SurveyMonkey
$('body').append('<script>(function(t,e,s,o){var n,a,c;t.SMCX=t.SMCX||[],e.getElementById(o)||(n=e.getElementsByTagName(s),a=n[n.length-1],c=e.createElement(s),c.type="text/javascript",c.async=!0,c.id=o,c.src=["https:"===location.protocol?"https://":"http://","widget.surveymonkey.com/collect/website/js/tRaiETqnLgj758hTBazgd_2BrwaGaWbg59AiLjNGdPaaJiBHKqgXKIw46VauwBvZ67.js"].join(""),a.parentNode.insertBefore(c,a))})(window,document,"script","smcx-sdk");</script>');
// $('body').append('<script>(function(t,e,s,o){var n,a,c;t.SMCX=t.SMCX||[],e.getElementById(o)||(n=e.getElementsByTagName(s),a=n[n.length-1],c=e.createElement(s),c.type="text/javascript",c.async=!0,c.id=o,c.src=["https:"===location.protocol?"https://":"http://","widget.surveymonkey.com/collect/website/js/tRaiETqnLgj758hTBazgd_2BrwaGaWbg59AiLjNGdPaaJiBHKqgXKIw46VauwBvZ67.js"].join(""),a.parentNode.insertBefore(c,a))})(window,document,"script","smcx-sdk");</script>');
// add link to survey at home sidebar
$('.template-home #sidebar .list-unstyled:first').append('<li><strong>Please fill in our survey at</strong> <br><a href="https://www.surveymonkey.com/r/AMR_for_R" target="_blank">https://www.surveymonkey.com/r/AMR_for_R</a></li>');
// $('.template-home #sidebar .list-unstyled:first').append('<li><strong>Please fill in our survey at</strong> <br><a href="https://www.surveymonkey.com/r/AMR_for_R" target="_blank">https://www.surveymonkey.com/r/AMR_for_R</a></li>');
// remove version label from header

View File

@ -48,14 +48,6 @@ test_that("as.ab works", {
expect_identical(class(pull(antibiotics, ab)), "ab")
# first 5 chars of official name
expect_equal(as.character(as.atc(c("nitro", "cipro"))),
c("J01XE01", "J01MA02"))
# EARS-Net
expect_equal(as.character(as.atc("AMX")),
"J01CA04")
expect_equal(as.character(as.ab("Phloxapen")),
"FLC")

View File

@ -1,39 +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. #
# ==================================================================== #
context("ab.R")
test_that("as.atc works", {
expect_identical(class(as.atc("amox")), "atc")
expect_true(is.atc(as.atc("amox")))
expect_output(print(as.atc("amox")))
expect_output(print(data.frame(a = as.atc("amox"))))
expect_identical(class(pull(antibiotics, atc)), "atc")
expect_warning(as.atc("Z00ZZ00")) # not yet availatcle in data set
expect_warning(as.atc("UNKNOWN"))
expect_output(print(as.atc("amox")))
})

View File

@ -23,18 +23,16 @@ context("deprecated.R")
test_that("deprecated functions work", {
expect_error(suppressWarnings(ratio("A")))
expect_error(suppressWarnings(ratio(1, ratio = "abc")))
expect_error(suppressWarnings(ratio(c(1, 2), ratio = c(1, 2, 3))))
expect_warning(ratio(c(772, 1611, 737), ratio = "1:2:1"))
expect_identical(suppressWarnings(ratio(c(772, 1611, 737), ratio = "1:2:1")), c(780, 1560, 780))
expect_identical(suppressWarnings(ratio(c(1752, 1895), ratio = c(1, 1))), c(1823.5, 1823.5))
# first 5 chars of official name
expect_equal(suppressWarnings(as.character(as.atc(c("nitro", "cipro")))),
c("J01XE01", "J01MA02"))
expect_warning(atc_property("amox"))
expect_warning(atc_official("amox"))
expect_warning(ab_official("amox"))
expect_warning(atc_name("amox"))
expect_warning(atc_trivial_nl("amox"))
expect_warning(atc_tradenames("amox"))
# EARS-Net
expect_equal(suppressWarnings(as.character(as.atc("AMX"))),
"J01CA04")
expect_equal(suppressWarnings(guess_ab_col(data.frame(AMP_ND10 = "R",
AMC_ED20 = "S"),
as.atc("augmentin"))),
"AMC_ED20")
})

View File

@ -36,32 +36,31 @@ test_that("ggplot_rsi works", {
summarise_all(portion_IR) %>% as.double()
)
print(septic_patients %>% select(AMC, CIP) %>% ggplot_rsi(x = "interpretation", facet = "antibiotic"))
print(septic_patients %>% select(AMC, CIP) %>% ggplot_rsi(x = "antibiotic", facet = "interpretation"))
expect_equal(
(septic_patients %>% select(AMC, CIP) %>% ggplot_rsi(x = "Interpretation", facet = "Antibiotic"))$data %>%
(septic_patients %>% select(AMC, CIP) %>% ggplot_rsi(x = "interpretation", facet = "antibiotic"))$data %>%
summarise_all(portion_IR) %>% as.double(),
septic_patients %>% select(AMC, CIP) %>%
summarise_all(portion_IR) %>% as.double()
)
expect_equal(
(septic_patients %>% select(AMC, CIP) %>% ggplot_rsi(x = "Antibiotic", facet = "Interpretation"))$data %>%
(septic_patients %>% select(AMC, CIP) %>% ggplot_rsi(x = "antibiotic", facet = "interpretation"))$data %>%
summarise_all(portion_IR) %>% as.double(),
septic_patients %>% select(AMC, CIP) %>%
summarise_all(portion_IR) %>% as.double()
)
expect_equal(
(septic_patients %>% select(AMC, CIP) %>% ggplot_rsi(x = "Antibiotic",
facet = "Interpretation",
fun = count_df))$data %>%
(septic_patients %>% select(AMC, CIP) %>% ggplot_rsi(x = "antibiotic",
facet = "interpretation"))$data %>%
summarise_all(count_IR) %>% as.double(),
septic_patients %>% select(AMC, CIP) %>%
summarise_all(count_IR) %>% as.double()
)
expect_error(ggplot_rsi(septic_patients, fun = "invalid"))
expect_error(geom_rsi(septic_patients, fun = "invalid"))
# support for scale_type ab and mo
expect_equal(class((data.frame(mo = as.mo(c("e. coli", "s aureus")),
n = c(40, 100)) %>%

View File

@ -40,6 +40,5 @@ test_that("guess_ab_col works", {
"AMP_ND10")
expect_equal(guess_ab_col(df, "J01CR02"),
"AMC_ED20")
expect_equal(guess_ab_col(df, as.atc("augmentin")),
"AMC_ED20")
})