atc_ functions

This commit is contained in:
dr. M.S. (Matthijs) Berends 2019-01-26 23:22:56 +01:00
parent 5493e1f05d
commit f836722269
56 changed files with 1397 additions and 910 deletions

View File

@ -1,6 +1,6 @@
Package: AMR
Version: 0.5.0.9012
Date: 2019-01-25
Date: 2019-01-26
Title: Antimicrobial Resistance Analysis
Authors@R: c(
person(

View File

@ -54,9 +54,16 @@ export(as.atc)
export(as.mic)
export(as.mo)
export(as.rsi)
export(atc_ddd)
export(atc_groups)
export(atc_certe)
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(atc_umcg)
export(brmo)
export(count_I)
export(count_IR)

13
NEWS.md
View File

@ -3,6 +3,17 @@
#### New
* **BREAKING**: removed deprecated functions, parameters and references to 'bactid'. Use `as.mo()` to identify an MO code.
* All `ab_*` functions are deprecated and replaced by `atc_*` functions:
```r
ab_property -> atc_property()
ab_name -> atc_name()
ab_official -> atc_official()
ab_trivial_nl -> atc_trivial_nl()
ab_certe -> atc_certe()
ab_umcg -> atc_umcg()
ab_tradenames -> atc_tradenames()
```
These functions use `as.atc()` internally. The old `atc_property` has been renamed `atc_online_property()`. 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 `atc` or must be coerable to this class. Properties of these classes should start with the same class name, analogous to `as.mo()` and e.g. `mo_genus`.
* New website: https://msberends.gitlab.io/AMR (built with the great [`pkgdown`](https://pkgdown.r-lib.org/))
* Contains the complete manual of this package and all of its functions with an explanation of their parameters
* Contains a comprehensive tutorial about how to conduct antimicrobial resistance analysis
@ -37,6 +48,8 @@
#### Changed
* Added 65 antibiotics to the `antibiotics` data set, from the [Pharmaceuticals Community Register](http://ec.europa.eu/health/documents/community-register/html/atc.htm) of the European Commission
* Removed columns `atc_group1_nl` and `atc_group2_nl` from the `antibiotics` data set
* Function `atc_ddd` has been renamed `atc_online_ddd()`
* Function `atc_groups` has been renamed `atc_online_groups()`
* Function `eucast_rules()`:
* Updated EUCAST Clinical breakpoints to [version 9.0 of 1 January 2019](http://www.eucast.org/clinical_breakpoints/)
* Fixed a critical bug where some rules that depend on previous applied rules would not be applied adequately

188
R/atc.R
View File

@ -186,191 +186,3 @@ as.data.frame.atc <- function (x, ...) {
pull.atc <- function(.data, ...) {
pull(as.data.frame(.data), ...)
}
#' Properties of an ATC code
#'
#' Gets data from the WHO to determine properties of an ATC (e.g. an antibiotic) like name, defined daily dose (DDD) or standard unit. \cr \strong{This function requires an internet connection.}
#' @param atc_code a character or character vector with ATC code(s) of antibiotic(s)
#' @param property property of an ATC code. Valid values are \code{"ATC"}, \code{"Name"}, \code{"DDD"}, \code{"U"} (\code{"unit"}), \code{"Adm.R"}, \code{"Note"} and \code{groups}. For this last option, all hierarchical groups of an ATC code will be returned, see Examples.
#' @param administration type of administration when using \code{property = "Adm.R"}, see Details
#' @param url url of website of the WHO. The sign \code{\%s} can be used as a placeholder for ATC codes.
#' @param ... parameters to pass on to \code{atc_property}
#' @details
#' Options for parameter \code{administration}:
#' \itemize{
#' \item{\code{"Implant"}}{ = Implant}
#' \item{\code{"Inhal"}}{ = Inhalation}
#' \item{\code{"Instill"}}{ = Instillation}
#' \item{\code{"N"}}{ = nasal}
#' \item{\code{"O"}}{ = oral}
#' \item{\code{"P"}}{ = parenteral}
#' \item{\code{"R"}}{ = rectal}
#' \item{\code{"SL"}}{ = sublingual/buccal}
#' \item{\code{"TD"}}{ = transdermal}
#' \item{\code{"V"}}{ = vaginal}
#' }
#'
#' Abbreviations of return values when using \code{property = "U"} (unit):
#' \itemize{
#' \item{\code{"g"}}{ = gram}
#' \item{\code{"mg"}}{ = milligram}
#' \item{\code{"mcg"}}{ = microgram}
#' \item{\code{"U"}}{ = unit}
#' \item{\code{"TU"}}{ = thousand units}
#' \item{\code{"MU"}}{ = million units}
#' \item{\code{"mmol"}}{ = millimole}
#' \item{\code{"ml"}}{ = milliliter (e.g. eyedrops)}
#' }
#' @export
#' @rdname atc_property
#' @importFrom dplyr %>% progress_estimated
#' @importFrom xml2 read_html
#' @importFrom rvest html_children html_node html_nodes html_table
#' @importFrom curl nslookup
#' @source \url{https://www.whocc.no/atc_ddd_alterations__cumulative/ddd_alterations/abbrevations/}
#' @examples
#' \donttest{
#' # What's the ATC of amoxicillin?
#' guess_atc("Amoxicillin")
#' # [1] "J01CA04"
#'
#' # oral DDD (Defined Daily Dose) of amoxicillin
#' atc_property("J01CA04", "DDD", "O")
#' # parenteral DDD (Defined Daily Dose) of amoxicillin
#' atc_property("J01CA04", "DDD", "P")
#'
#' atc_property("J01CA04", property = "groups") # search hierarchical groups of amoxicillin
#' # [1] "ANTIINFECTIVES FOR SYSTEMIC USE"
#' # [2] "ANTIBACTERIALS FOR SYSTEMIC USE"
#' # [3] "BETA-LACTAM ANTIBACTERIALS, PENICILLINS"
#' # [4] "Penicillins with extended spectrum"
#' }
atc_property <- function(atc_code,
property,
administration = 'O',
url = 'https://www.whocc.no/atc_ddd_index/?code=%s&showdescription=no') {
# check active network interface, from https://stackoverflow.com/a/5078002/4575331
has_internet <- function(url) {
# extract host from given url
# https://www.whocc.no/atc_ddd_index/ -> www.whocc.no
url <- url %>%
gsub("^(http://|https://)", "", .) %>%
strsplit('/', fixed = TRUE) %>%
unlist() %>%
.[1]
!is.null(curl::nslookup(url, error = FALSE))
}
# check for connection using the ATC of amoxicillin
if (!has_internet(url = url)) {
message("The URL could not be reached.")
return(rep(NA, length(atc_code)))
}
if (length(property) != 1L) {
stop('`property` must be of length 1', call. = FALSE)
}
if (length(administration) != 1L) {
stop('`administration` must be of length 1', call. = FALSE)
}
# also allow unit as property
if (property %like% 'unit') {
property <- 'U'
}
# validation of properties
valid_properties <- c("ATC", "Name", "DDD", "U", "Adm.R", "Note", "groups")
valid_properties.bak <- valid_properties
property <- tolower(property)
valid_properties <- tolower(valid_properties)
if (!property %in% valid_properties) {
stop('Invalid `property`, use one of ', paste(valid_properties.bak, collapse = ", "), '.')
}
if (property == 'ddd') {
returnvalue <- rep(NA_real_, length(atc_code))
} else if (property == 'groups') {
returnvalue <- list()
} else {
returnvalue <- rep(NA_character_, length(atc_code))
}
progress <- progress_estimated(n = length(atc_code))
for (i in 1:length(atc_code)) {
progress$tick()$print()
atc_url <- sub('%s', atc_code[i], url, fixed = TRUE)
if (property == "groups") {
tbl <- xml2::read_html(atc_url) %>%
rvest::html_node("#content") %>%
rvest::html_children() %>%
rvest::html_node("a")
# get URLS of items
hrefs <- tbl %>% rvest::html_attr("href")
# get text of items
texts <- tbl %>% rvest::html_text()
# select only text items where URL like "code="
texts <- texts[grepl("?code=", tolower(hrefs), fixed = TRUE)]
# last one is antibiotics, skip it
texts <- texts[1:length(texts) - 1]
returnvalue <- c(list(texts), returnvalue)
} else {
tbl <- xml2::read_html(atc_url) %>%
rvest::html_nodes('table') %>%
rvest::html_table(header = TRUE) %>%
as.data.frame(stringsAsFactors = FALSE)
# case insensitive column names
colnames(tbl) <- tolower(colnames(tbl)) %>% gsub('^atc.*', 'atc', .)
if (length(tbl) == 0) {
warning('ATC not found: ', atc_code[i], '. Please check ', atc_url, '.', call. = FALSE)
returnvalue[i] <- NA
next
}
if (property %in% c('atc', 'name')) {
# ATC and name are only in first row
returnvalue[i] <- tbl[1, property]
} else {
if (!'adm.r' %in% colnames(tbl) | is.na(tbl[1, 'adm.r'])) {
returnvalue[i] <- NA
next
} else {
for (j in 1:nrow(tbl)) {
if (tbl[j, 'adm.r'] == administration) {
returnvalue[i] <- tbl[j, property]
}
}
}
}
}
}
if (property == "groups" & length(returnvalue) == 1) {
returnvalue <- returnvalue[[1]]
}
returnvalue
}
#' @rdname atc_property
#' @export
atc_groups <- function(atc_code, ...) {
atc_property(atc_code = atc_code, property = "groups", ...)
}
#' @rdname atc_property
#' @export
atc_ddd <- function(atc_code, ...) {
atc_property(atc_code = atc_code, property = "ddd", ...)
}

204
R/atc_online.R Normal file
View File

@ -0,0 +1,204 @@
# ==================================================================== #
# 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.gitab.io/AMR. #
# ==================================================================== #
#' Properties of an ATC code
#'
#' Gets data from the WHO to determine properties of an ATC (e.g. an antibiotic) like name, defined daily dose (DDD) or standard unit. \cr \strong{This function requires an internet connection.}
#' @param atc_code a character or character vector with ATC code(s) of antibiotic(s)
#' @param property property of an ATC code. Valid values are \code{"ATC"}, \code{"Name"}, \code{"DDD"}, \code{"U"} (\code{"unit"}), \code{"Adm.R"}, \code{"Note"} and \code{groups}. For this last option, all hierarchical groups of an ATC code will be returned, see Examples.
#' @param administration type of administration when using \code{property = "Adm.R"}, see Details
#' @param url url of website of the WHO. The sign \code{\%s} can be used as a placeholder for ATC codes.
#' @param ... parameters to pass on to \code{atc_property}
#' @details
#' Options for parameter \code{administration}:
#' \itemize{
#' \item{\code{"Implant"}}{ = Implant}
#' \item{\code{"Inhal"}}{ = Inhalation}
#' \item{\code{"Instill"}}{ = Instillation}
#' \item{\code{"N"}}{ = nasal}
#' \item{\code{"O"}}{ = oral}
#' \item{\code{"P"}}{ = parenteral}
#' \item{\code{"R"}}{ = rectal}
#' \item{\code{"SL"}}{ = sublingual/buccal}
#' \item{\code{"TD"}}{ = transdermal}
#' \item{\code{"V"}}{ = vaginal}
#' }
#'
#' Abbreviations of return values when using \code{property = "U"} (unit):
#' \itemize{
#' \item{\code{"g"}}{ = gram}
#' \item{\code{"mg"}}{ = milligram}
#' \item{\code{"mcg"}}{ = microgram}
#' \item{\code{"U"}}{ = unit}
#' \item{\code{"TU"}}{ = thousand units}
#' \item{\code{"MU"}}{ = million units}
#' \item{\code{"mmol"}}{ = millimole}
#' \item{\code{"ml"}}{ = milliliter (e.g. eyedrops)}
#' }
#' @export
#' @rdname atc_online
#' @importFrom dplyr %>% progress_estimated
#' @importFrom xml2 read_html
#' @importFrom rvest html_children html_node html_nodes html_table
#' @importFrom curl nslookup
#' @source \url{https://www.whocc.no/atc_ddd_alterations__cumulative/ddd_alterations/abbrevations/}
#' @examples
#' \donttest{
#' # oral DDD (Defined Daily Dose) of amoxicillin
#' atc_online_property("J01CA04", "DDD", "O")
#' # parenteral DDD (Defined Daily Dose) of amoxicillin
#' atc_online_property("J01CA04", "DDD", "P")
#'
#' atc_online_property("J01CA04", property = "groups") # search hierarchical groups of amoxicillin
#' # [1] "ANTIINFECTIVES FOR SYSTEMIC USE"
#' # [2] "ANTIBACTERIALS FOR SYSTEMIC USE"
#' # [3] "BETA-LACTAM ANTIBACTERIALS, PENICILLINS"
#' # [4] "Penicillins with extended spectrum"
#' }
atc_online_property <- function(atc_code,
property,
administration = 'O',
url = 'https://www.whocc.no/atc_ddd_index/?code=%s&showdescription=no') {
# check active network interface, from https://stackoverflow.com/a/5078002/4575331
has_internet <- function(url) {
# extract host from given url
# https://www.whocc.no/atc_ddd_index/ -> www.whocc.no
url <- url %>%
gsub("^(http://|https://)", "", .) %>%
strsplit('/', fixed = TRUE) %>%
unlist() %>%
.[1]
!is.null(curl::nslookup(url, error = FALSE))
}
# check for connection using the ATC of amoxicillin
if (!has_internet(url = url)) {
message("The URL could not be reached.")
return(rep(NA, length(atc_code)))
}
if (length(property) != 1L) {
stop('`property` must be of length 1', call. = FALSE)
}
if (length(administration) != 1L) {
stop('`administration` must be of length 1', call. = FALSE)
}
# also allow unit as property
if (property %like% 'unit') {
property <- 'U'
}
# validation of properties
valid_properties <- c("ATC", "Name", "DDD", "U", "Adm.R", "Note", "groups")
valid_properties.bak <- valid_properties
property <- tolower(property)
valid_properties <- tolower(valid_properties)
if (!property %in% valid_properties) {
stop('Invalid `property`, use one of ', paste(valid_properties.bak, collapse = ", "), '.')
}
if (property == 'ddd') {
returnvalue <- rep(NA_real_, length(atc_code))
} else if (property == 'groups') {
returnvalue <- list()
} else {
returnvalue <- rep(NA_character_, length(atc_code))
}
progress <- progress_estimated(n = length(atc_code))
for (i in 1:length(atc_code)) {
progress$tick()$print()
atc_url <- sub('%s', atc_code[i], url, fixed = TRUE)
if (property == "groups") {
tbl <- xml2::read_html(atc_url) %>%
rvest::html_node("#content") %>%
rvest::html_children() %>%
rvest::html_node("a")
# get URLS of items
hrefs <- tbl %>% rvest::html_attr("href")
# get text of items
texts <- tbl %>% rvest::html_text()
# select only text items where URL like "code="
texts <- texts[grepl("?code=", tolower(hrefs), fixed = TRUE)]
# last one is antibiotics, skip it
texts <- texts[1:length(texts) - 1]
returnvalue <- c(list(texts), returnvalue)
} else {
tbl <- xml2::read_html(atc_url) %>%
rvest::html_nodes('table') %>%
rvest::html_table(header = TRUE) %>%
as.data.frame(stringsAsFactors = FALSE)
# case insensitive column names
colnames(tbl) <- tolower(colnames(tbl)) %>% gsub('^atc.*', 'atc', .)
if (length(tbl) == 0) {
warning('ATC not found: ', atc_code[i], '. Please check ', atc_url, '.', call. = FALSE)
returnvalue[i] <- NA
next
}
if (property %in% c('atc', 'name')) {
# ATC and name are only in first row
returnvalue[i] <- tbl[1, property]
} else {
if (!'adm.r' %in% colnames(tbl) | is.na(tbl[1, 'adm.r'])) {
returnvalue[i] <- NA
next
} else {
for (j in 1:nrow(tbl)) {
if (tbl[j, 'adm.r'] == administration) {
returnvalue[i] <- tbl[j, property]
}
}
}
}
}
}
if (property == "groups" & length(returnvalue) == 1) {
returnvalue <- returnvalue[[1]]
}
returnvalue
}
#' @rdname atc_online
#' @export
atc_online_groups <- function(atc_code, ...) {
atc_online_property(atc_code = atc_code, property = "groups", ...)
}
#' @rdname atc_online
#' @export
atc_online_ddd <- function(atc_code, ...) {
atc_online_property(atc_code = atc_code, property = "ddd", ...)
}

View File

@ -25,20 +25,20 @@
#' @param x a (vector of a) valid \code{\link{atc}} code or any text that can be coerced to a valid atc with \code{\link{as.atc}}
#' @param property one of the column names of one of the \code{\link{antibiotics}} data set, like \code{"atc"} and \code{"official"}
#' @param language language of the returned text, defaults to English (\code{"en"}) and can be set with \code{\link{getOption}("AMR_locale")}. Either one of \code{"en"} (English) or \code{"nl"} (Dutch).
#' @rdname ab_property
#' @return A vector of values. In case of \code{ab_tradenames}, if \code{x} is of length one, a vector will be returned. Otherwise a \code{\link{list}}, with \code{x} as names.
#' @rdname atc_property
#' @return A vector of values. In case of \code{atc_tradenames}, if \code{x} is of length one, a vector will be returned. Otherwise a \code{\link{list}}, with \code{x} as names.
#' @export
#' @importFrom dplyr %>% left_join pull
#' @seealso \code{\link{antibiotics}}
#' @inheritSection AMR Read more on our website!
#' @examples
#' ab_atc("amcl") # J01CR02
#' ab_name("amcl") # Amoxicillin and beta-lactamase inhibitor
#' ab_name("amcl", "nl") # Amoxicilline met enzymremmer
#' ab_trivial_nl("amcl") # Amoxicilline/clavulaanzuur
#' ab_certe("amcl") # amcl
#' ab_umcg("amcl") # AMCL
ab_property <- function(x, property = 'official') {
#' as.atc("amcl") # J01CR02
#' atc_name("amcl") # Amoxicillin and beta-lactamase inhibitor
#' atc_name("amcl", "nl") # Amoxicilline met enzymremmer
#' atc_trivial_nl("amcl") # Amoxicilline/clavulaanzuur
#' atc_certe("amcl") # amcl
#' atc_umcg("amcl") # AMCL
atc_property <- function(x, property = 'official') {
property <- property[1]
if (!property %in% colnames(AMR::antibiotics)) {
stop("invalid property: ", property, " - use a column name of the `antibiotics` data set")
@ -53,15 +53,9 @@ ab_property <- function(x, property = 'official') {
)
}
#' @rdname ab_property
#' @rdname atc_property
#' @export
ab_atc <- function(x) {
as.character(as.atc(x))
}
#' @rdname ab_property
#' @export
ab_official <- function(x, language = NULL) {
atc_official <- function(x, language = NULL) {
if (is.null(language)) {
language <- getOption("AMR_locale", default = "en")[1L]
@ -69,40 +63,40 @@ ab_official <- function(x, language = NULL) {
language <- tolower(language[1])
}
if (language %in% c("en", "")) {
ab_property(x, "official")
atc_property(x, "official")
} else if (language == "nl") {
ab_property(x, "official_nl")
atc_property(x, "official_nl")
} else {
stop("Unsupported language: '", language, "' - use one of: 'en', 'nl'", call. = FALSE)
}
}
#' @rdname ab_property
#' @rdname atc_property
#' @export
ab_name <- ab_official
atc_name <- atc_official
#' @rdname ab_property
#' @rdname atc_property
#' @export
ab_trivial_nl <- function(x) {
ab_property(x, "trivial_nl")
atc_trivial_nl <- function(x) {
atc_property(x, "trivial_nl")
}
#' @rdname ab_property
#' @rdname atc_property
#' @export
ab_certe <- function(x) {
ab_property(x, "certe")
atc_certe <- function(x) {
atc_property(x, "certe")
}
#' @rdname ab_property
#' @rdname atc_property
#' @export
ab_umcg <- function(x) {
ab_property(x, "umcg")
atc_umcg <- function(x) {
atc_property(x, "umcg")
}
#' @rdname ab_property
#' @rdname atc_property
#' @export
ab_tradenames <- function(x) {
res <- ab_property(x, "trade_name")
atc_tradenames <- function(x) {
res <- atc_property(x, "trade_name")
res <- strsplit(res, "|", fixed = TRUE)
if (length(x) == 1) {
res <- unlist(res)

View File

@ -21,7 +21,7 @@
#' Deprecated functions
#'
#' These functions are \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.
#' 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).
#' @inheritSection AMR Read more on our website!
#' @export
#' @keywords internal
@ -53,3 +53,59 @@ guess_mo <- function(...) {
.Deprecated(new = "as.mo", package = "AMR")
as.mo(...)
}
#' @rdname AMR-deprecated
#' @export
ab_property <- function(...) {
.Deprecated(new = "atc_property", package = "AMR")
atc_property(...)
}
#' @rdname AMR-deprecated
#' @export
ab_atc <- function(...) {
.Deprecated(new = "as.atc", package = "AMR")
as.atc(...)
}
#' @rdname AMR-deprecated
#' @export
ab_official <- function(...) {
.Deprecated(new = "atc_official", package = "AMR")
atc_official(...)
}
#' @rdname AMR-deprecated
#' @export
ab_name <- function(...) {
.Deprecated(new = "atc_name", package = "AMR")
atc_name(...)
}
#' @rdname AMR-deprecated
#' @export
ab_trivial_nl <- function(...) {
.Deprecated(new = "atc_trivial_nl", package = "AMR")
atc_trivial_nl(...)
}
#' @rdname AMR-deprecated
#' @export
ab_certe <- function(...) {
.Deprecated(new = "atc_certe", package = "AMR")
atc_certe(...)
}
#' @rdname AMR-deprecated
#' @export
ab_umcg <- function(...) {
.Deprecated(new = "atc_umcg", package = "AMR")
atc_umcg(...)
}
#' @rdname AMR-deprecated
#' @export
ab_tradenames <- function(...) {
.Deprecated(new = "atc_tradenames", package = "AMR")
atc_tradenames(...)
}

View File

@ -25,7 +25,7 @@
#' @details
#' This package was intended to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial properties by using evidence-based methods.
#'
#' This package was created for academic research by PhD students of the Faculty of Medical Sciences of the University of Groningen and the Medical Microbiology & Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG).
#' This package was created for both academic research and routine analysis by PhD students of the Faculty of Medical Sciences of the University of Groningen and the Medical Microbiology & Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG).
#' @section Read more on our website!:
#' \if{html}{\figure{logo.png}{options: height=40px style=margin-bottom:5px} \cr}
#' On our website \url{https://msberends.gitlab.io/AMR} you can find \href{https://msberends.gitlab.io/AMR/articles/AMR.html}{a omprehensive tutorial} about how to conduct AMR analysis and find \href{https://msberends.gitlab.io/AMR/reference}{the complete documentation of all functions}, which reads a lot easier than in R.

View File

@ -104,8 +104,8 @@ reference:
- '`mdro`'
- '`key_antibiotics`'
- '`mo_property`'
- '`ab_property`'
- '`atc_property`'
- '`atc_online_property`'
- '`abname`'
- '`age`'
- '`age_groups`'
@ -146,6 +146,8 @@ reference:
- '`like`'
- '`mo_failures`'
- '`mo_renamed`'
- '`ab_property`'
authors:
Matthijs S. Berends:

View File

@ -178,7 +178,7 @@
<h1>How to conduct AMR analysis</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">25 January 2019</h4>
<h4 class="date">26 January 2019</h4>
<div class="hidden name"><code>AMR.Rmd</code></div>
@ -187,7 +187,7 @@
<p><strong>Note:</strong> values on this page will change with every website update since they are based on randomly created values and the page was written in <a href="https://rmarkdown.rstudio.com/">RMarkdown</a>. However, the methodology remains unchanged. This page was generated on 25 January 2019.</p>
<p><strong>Note:</strong> values on this page will change with every website update since they are based on randomly created values and the page was written in <a href="https://rmarkdown.rstudio.com/">RMarkdown</a>. However, the methodology remains unchanged. This page was generated on 26 January 2019.</p>
<div id="introduction" class="section level2">
<h2 class="hasAnchor">
<a href="#introduction" class="anchor"></a>Introduction</h2>
@ -203,21 +203,21 @@
</tr></thead>
<tbody>
<tr class="odd">
<td align="center">2019-01-25</td>
<td align="center">2019-01-26</td>
<td align="center">abcd</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">S</td>
</tr>
<tr class="even">
<td align="center">2019-01-25</td>
<td align="center">2019-01-26</td>
<td align="center">abcd</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">R</td>
</tr>
<tr class="odd">
<td align="center">2019-01-25</td>
<td align="center">2019-01-26</td>
<td align="center">efgh</td>
<td align="center">Escherichia coli</td>
<td align="center">R</td>
@ -229,11 +229,14 @@
<div id="needed-r-packages" class="section level2">
<h2 class="hasAnchor">
<a href="#needed-r-packages" class="anchor"></a>Needed R packages</h2>
<p>As with many uses in R, we need some additional packages for AMR analysis. The most important one is <a href="https://dplyr.tidyverse.org/"><code>dplyr</code></a>, which tremendously improves the way we work with data - it allows for a very natural way of writing syntaxes in R. Another important dependency is <a href="https://ggplot2.tidyverse.org/"><code>ggplot2</code></a>. This package can be used to create beautiful plots in R.</p>
<p>As with many uses in R, we need some additional packages for AMR analysis. Our package works closely together with the <a href="https://www.tidyverse.org">tidyverse packages</a> <a href="https://dplyr.tidyverse.org/"><code>dplyr</code></a> and <a href="https://ggplot2.tidyverse.org"><code>ggplot2</code></a> by <a href="https://www.linkedin.com/in/hadleywickham/">Dr Hadley Wickham</a>. The tidyverse tremendously improves the way we conduct data science - it allows for a very natural way of writing syntaxes and creating beautiful plots in R.</p>
<p>Our <code>AMR</code> package depends on these packages and even extends their use and functions.</p>
<div class="sourceCode" id="cb1"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb1-1" data-line-number="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/library">library</a></span>(dplyr) <span class="co"># the data science package</span></a>
<a class="sourceLine" id="cb1-2" data-line-number="2"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/library">library</a></span>(AMR) <span class="co"># this package, to simplify and automate AMR analysis</span></a>
<a class="sourceLine" id="cb1-3" data-line-number="3"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/library">library</a></span>(ggplot2) <span class="co"># for appealing plots</span></a></code></pre></div>
<div class="sourceCode" id="cb1"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb1-1" data-line-number="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/library">library</a></span>(dplyr)</a>
<a class="sourceLine" id="cb1-2" data-line-number="2"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/library">library</a></span>(ggplot2)</a>
<a class="sourceLine" id="cb1-3" data-line-number="3"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/library">library</a></span>(AMR)</a>
<a class="sourceLine" id="cb1-4" data-line-number="4"></a>
<a class="sourceLine" id="cb1-5" data-line-number="5"><span class="co"># (if not yet installed, install with:)</span></a>
<a class="sourceLine" id="cb1-6" data-line-number="6"><span class="co"># install.packages(c("tidyverse", "AMR"))</span></a></code></pre></div>
</div>
<div id="creation-of-data" class="section level2">
<h2 class="hasAnchor">
@ -275,18 +278,18 @@
<div id="put-everything-together" class="section level4">
<h4 class="hasAnchor">
<a href="#put-everything-together" class="anchor"></a>Put everything together</h4>
<p>Using the <code><a href="https://www.rdocumentation.org/packages/dplyr/topics/sample">sample()</a></code> function, we can randomly select items from all objects we defined earlier. To let our fake data reflect reality a bit, we will also approximately define the probabilities of bacteria and the antibiotic results with the <code>prob</code> parameter.</p>
<div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb7-1" data-line-number="1">data &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/data.frame">data.frame</a></span>(<span class="dt">date =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/sample">sample</a></span>(dates, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>),</a>
<a class="sourceLine" id="cb7-2" data-line-number="2"> <span class="dt">patient_id =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/sample">sample</a></span>(patients, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>),</a>
<a class="sourceLine" id="cb7-3" data-line-number="3"> <span class="dt">hospital =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/sample">sample</a></span>(hospitals, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>, <span class="dt">prob =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="fl">0.30</span>, <span class="fl">0.35</span>, <span class="fl">0.15</span>, <span class="fl">0.20</span>)),</a>
<a class="sourceLine" id="cb7-4" data-line-number="4"> <span class="dt">bacteria =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/sample">sample</a></span>(bacteria, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>, <span class="dt">prob =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="fl">0.50</span>, <span class="fl">0.25</span>, <span class="fl">0.15</span>, <span class="fl">0.10</span>)),</a>
<a class="sourceLine" id="cb7-5" data-line-number="5"> <span class="dt">amox =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/sample">sample</a></span>(ab_interpretations, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>, <span class="dt">prob =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="fl">0.60</span>, <span class="fl">0.05</span>, <span class="fl">0.35</span>)),</a>
<a class="sourceLine" id="cb7-6" data-line-number="6"> <span class="dt">amcl =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/sample">sample</a></span>(ab_interpretations, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>, <span class="dt">prob =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="fl">0.75</span>, <span class="fl">0.10</span>, <span class="fl">0.15</span>)),</a>
<a class="sourceLine" id="cb7-7" data-line-number="7"> <span class="dt">cipr =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/sample">sample</a></span>(ab_interpretations, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>, <span class="dt">prob =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="fl">0.80</span>, <span class="fl">0.00</span>, <span class="fl">0.20</span>)),</a>
<a class="sourceLine" id="cb7-8" data-line-number="8"> <span class="dt">gent =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/sample">sample</a></span>(ab_interpretations, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>, <span class="dt">prob =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="fl">0.92</span>, <span class="fl">0.00</span>, <span class="fl">0.08</span>))</a>
<p>Using the <code><a href="https://dplyr.tidyverse.org/reference/sample.html">sample()</a></code> function, we can randomly select items from all objects we defined earlier. To let our fake data reflect reality a bit, we will also approximately define the probabilities of bacteria and the antibiotic results with the <code>prob</code> parameter.</p>
<div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb7-1" data-line-number="1">data &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/data.frame">data.frame</a></span>(<span class="dt">date =</span> <span class="kw"><a href="https://dplyr.tidyverse.org/reference/sample.html">sample</a></span>(dates, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>),</a>
<a class="sourceLine" id="cb7-2" data-line-number="2"> <span class="dt">patient_id =</span> <span class="kw"><a href="https://dplyr.tidyverse.org/reference/sample.html">sample</a></span>(patients, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>),</a>
<a class="sourceLine" id="cb7-3" data-line-number="3"> <span class="dt">hospital =</span> <span class="kw"><a href="https://dplyr.tidyverse.org/reference/sample.html">sample</a></span>(hospitals, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>, <span class="dt">prob =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="fl">0.30</span>, <span class="fl">0.35</span>, <span class="fl">0.15</span>, <span class="fl">0.20</span>)),</a>
<a class="sourceLine" id="cb7-4" data-line-number="4"> <span class="dt">bacteria =</span> <span class="kw"><a href="https://dplyr.tidyverse.org/reference/sample.html">sample</a></span>(bacteria, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>, <span class="dt">prob =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="fl">0.50</span>, <span class="fl">0.25</span>, <span class="fl">0.15</span>, <span class="fl">0.10</span>)),</a>
<a class="sourceLine" id="cb7-5" data-line-number="5"> <span class="dt">amox =</span> <span class="kw"><a href="https://dplyr.tidyverse.org/reference/sample.html">sample</a></span>(ab_interpretations, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>, <span class="dt">prob =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="fl">0.60</span>, <span class="fl">0.05</span>, <span class="fl">0.35</span>)),</a>
<a class="sourceLine" id="cb7-6" data-line-number="6"> <span class="dt">amcl =</span> <span class="kw"><a href="https://dplyr.tidyverse.org/reference/sample.html">sample</a></span>(ab_interpretations, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>, <span class="dt">prob =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="fl">0.75</span>, <span class="fl">0.10</span>, <span class="fl">0.15</span>)),</a>
<a class="sourceLine" id="cb7-7" data-line-number="7"> <span class="dt">cipr =</span> <span class="kw"><a href="https://dplyr.tidyverse.org/reference/sample.html">sample</a></span>(ab_interpretations, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>, <span class="dt">prob =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="fl">0.80</span>, <span class="fl">0.00</span>, <span class="fl">0.20</span>)),</a>
<a class="sourceLine" id="cb7-8" data-line-number="8"> <span class="dt">gent =</span> <span class="kw"><a href="https://dplyr.tidyverse.org/reference/sample.html">sample</a></span>(ab_interpretations, <span class="dv">5000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>, <span class="dt">prob =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="fl">0.92</span>, <span class="fl">0.00</span>, <span class="fl">0.08</span>))</a>
<a class="sourceLine" id="cb7-9" data-line-number="9"> )</a></code></pre></div>
<p>Using the <code><a href="https://www.rdocumentation.org/packages/dplyr/topics/join">left_join()</a></code> function from the <code>dplyr</code> package, we can map the gender to the patient ID using the <code>patients_table</code> object we created earlier:</p>
<div class="sourceCode" id="cb8"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb8-1" data-line-number="1">data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/join">left_join</a></span>(patients_table)</a></code></pre></div>
<p>Using the <code><a href="https://dplyr.tidyverse.org/reference/join.html">left_join()</a></code> function from the <code>dplyr</code> package, we can map the gender to the patient ID using the <code>patients_table</code> object we created earlier:</p>
<div class="sourceCode" id="cb8"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb8-1" data-line-number="1">data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/join.html">left_join</a></span>(patients_table)</a></code></pre></div>
<p>The resulting data set contains 5,000 blood culture isolates. With the <code><a href="https://www.rdocumentation.org/packages/utils/topics/head">head()</a></code> function we can preview the first 6 values of this data set:</p>
<div class="sourceCode" id="cb9"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb9-1" data-line-number="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/utils/topics/head">head</a></span>(data)</a></code></pre></div>
<table class="table">
@ -303,32 +306,32 @@
</tr></thead>
<tbody>
<tr class="odd">
<td align="center">2013-03-25</td>
<td align="center">O5</td>
<td align="center">2012-01-02</td>
<td align="center">K9</td>
<td align="center">Hospital A</td>
<td align="center">Escherichia coli</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td>
</tr>
<tr class="even">
<td align="center">2011-05-22</td>
<td align="center">Y3</td>
<td align="center">Hospital B</td>
<td align="center">Streptococcus pneumoniae</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="even">
<td align="center">2014-05-07</td>
<td align="center">W10</td>
<td align="center">Hospital A</td>
<td align="center">Klebsiella pneumoniae</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="odd">
<td align="center">2014-08-13</td>
<td align="center">L5</td>
<td align="center">Hospital D</td>
<td align="center">Escherichia coli</td>
<td align="center">2015-11-10</td>
<td align="center">F1</td>
<td align="center">Hospital C</td>
<td align="center">Staphylococcus aureus</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
@ -336,10 +339,10 @@
<td align="center">M</td>
</tr>
<tr class="even">
<td align="center">2014-07-10</td>
<td align="center">Z2</td>
<td align="center">2011-10-10</td>
<td align="center">X7</td>
<td align="center">Hospital D</td>
<td align="center">Escherichia coli</td>
<td align="center">Staphylococcus aureus</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
@ -347,24 +350,24 @@
<td align="center">F</td>
</tr>
<tr class="odd">
<td align="center">2014-09-18</td>
<td align="center">Z9</td>
<td align="center">2017-11-10</td>
<td align="center">B3</td>
<td align="center">Hospital D</td>
<td align="center">Staphylococcus aureus</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
<td align="center">M</td>
</tr>
<tr class="even">
<td align="center">2015-04-27</td>
<td align="center">Q3</td>
<td align="center">Hospital C</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">2014-11-09</td>
<td align="center">O5</td>
<td align="center">Hospital B</td>
<td align="center">Klebsiella pneumoniae</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
@ -386,15 +389,15 @@
#
# Item Count Percent Cum. Count Cum. Percent
# --- ----- ------ -------- ----------- -------------
# 1 M 2,653 53.1% 2,653 53.1%
# 2 F 2,347 46.9% 5,000 100.0%</code></pre>
# 1 M 2,593 51.9% 2,593 51.9%
# 2 F 2,407 48.1% 5,000 100.0%</code></pre>
<p>So, we can draw at least two conclusions immediately. From a data scientist perspective, the data looks clean: only values <code>M</code> and <code>F</code>. From a researcher perspective: there are slightly more men. Nothing we didnt already know.</p>
<p>The data is already quite clean, but we still need to transform some variables. The <code>bacteria</code> column now consists of text, and we want to add more variables based on microbial IDs later on. So, we will transform this column to valid IDs. The <code><a href="https://www.rdocumentation.org/packages/dplyr/topics/mutate">mutate()</a></code> function of the <code>dplyr</code> package makes this really easy:</p>
<p>The data is already quite clean, but we still need to transform some variables. The <code>bacteria</code> column now consists of text, and we want to add more variables based on microbial IDs later on. So, we will transform this column to valid IDs. The <code><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate()</a></code> function of the <code>dplyr</code> package makes this really easy:</p>
<div class="sourceCode" id="cb12"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb12-1" data-line-number="1">data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb12-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/mutate">mutate</a></span>(<span class="dt">bacteria =</span> <span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(bacteria))</a></code></pre></div>
<p>We also want to transform the antibiotics, because in real life data we dont know if they are really clean. The <code><a href="../reference/as.rsi.html">as.rsi()</a></code> function ensures reliability and reproducibility in these kind of variables. The <code><a href="https://www.rdocumentation.org/packages/dplyr/topics/summarise_all">mutate_at()</a></code> will run the <code><a href="../reference/as.rsi.html">as.rsi()</a></code> function on defined variables:</p>
<a class="sourceLine" id="cb12-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="dt">bacteria =</span> <span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(bacteria))</a></code></pre></div>
<p>We also want to transform the antibiotics, because in real life data we dont know if they are really clean. The <code><a href="../reference/as.rsi.html">as.rsi()</a></code> function ensures reliability and reproducibility in these kind of variables. The <code><a href="https://dplyr.tidyverse.org/reference/summarise_all.html">mutate_at()</a></code> will run the <code><a href="../reference/as.rsi.html">as.rsi()</a></code> function on defined variables:</p>
<div class="sourceCode" id="cb13"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb13-1" data-line-number="1">data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb13-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/summarise_all">mutate_at</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/vars">vars</a></span>(amox<span class="op">:</span>gent), as.rsi)</a></code></pre></div>
<a class="sourceLine" id="cb13-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/summarise_all.html">mutate_at</a></span>(<span class="kw"><a href="https://dplyr.tidyverse.org/reference/vars.html">vars</a></span>(amox<span class="op">:</span>gent), as.rsi)</a></code></pre></div>
<p>Finally, we will apply <a href="http://www.eucast.org/expert_rules_and_intrinsic_resistance/">EUCAST rules</a> on our antimicrobial results. In Europe, most medical microbiological laboratories already apply these rules. Our package features their latest insights on intrinsic resistance and exceptional phenotypes. Moreover, the <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> function can also apply additional rules, like forcing <help title="ATC: J01CA01">ampicillin</help> = R when <help title="ATC: J01CR02">amoxicillin/clavulanic acid</help> = R.</p>
<p>Because the amoxicillin (column <code>amox</code>) and amoxicillin/clavulanic acid (column <code>amcl</code>) in our data were generated randomly, some rows will undoubtedly contain amox = S and amcl = R, which is technically impossible. The <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> fixes this:</p>
<div class="sourceCode" id="cb14"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb14-1" data-line-number="1">data &lt;-<span class="st"> </span><span class="kw"><a href="../reference/eucast_rules.html">eucast_rules</a></span>(data, <span class="dt">col_mo =</span> <span class="st">"bacteria"</span>)</a>
@ -418,10 +421,10 @@
<a class="sourceLine" id="cb14-19" data-line-number="19"><span class="co"># Kingella kingae (no changes)</span></a>
<a class="sourceLine" id="cb14-20" data-line-number="20"><span class="co"># </span></a>
<a class="sourceLine" id="cb14-21" data-line-number="21"><span class="co"># EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)</span></a>
<a class="sourceLine" id="cb14-22" data-line-number="22"><span class="co"># Table 1: Intrinsic resistance in Enterobacteriaceae (324 changes)</span></a>
<a class="sourceLine" id="cb14-22" data-line-number="22"><span class="co"># Table 1: Intrinsic resistance in Enterobacteriaceae (345 changes)</span></a>
<a class="sourceLine" id="cb14-23" data-line-number="23"><span class="co"># Table 2: Intrinsic resistance in non-fermentative Gram-negative bacteria (no changes)</span></a>
<a class="sourceLine" id="cb14-24" data-line-number="24"><span class="co"># Table 3: Intrinsic resistance in other Gram-negative bacteria (no changes)</span></a>
<a class="sourceLine" id="cb14-25" data-line-number="25"><span class="co"># Table 4: Intrinsic resistance in Gram-positive bacteria (672 changes)</span></a>
<a class="sourceLine" id="cb14-25" data-line-number="25"><span class="co"># Table 4: Intrinsic resistance in Gram-positive bacteria (673 changes)</span></a>
<a class="sourceLine" id="cb14-26" data-line-number="26"><span class="co"># Table 8: Interpretive rules for B-lactam agents and Gram-positive cocci (no changes)</span></a>
<a class="sourceLine" id="cb14-27" data-line-number="27"><span class="co"># Table 9: Interpretive rules for B-lactam agents and Gram-negative rods (no changes)</span></a>
<a class="sourceLine" id="cb14-28" data-line-number="28"><span class="co"># Table 10: Interpretive rules for B-lactam agents and other Gram-negative bacteria (no changes)</span></a>
@ -437,14 +440,14 @@
<a class="sourceLine" id="cb14-38" data-line-number="38"><span class="co"># Non-EUCAST: piperacillin/tazobactam = S where piperacillin = S (no changes)</span></a>
<a class="sourceLine" id="cb14-39" data-line-number="39"><span class="co"># Non-EUCAST: trimethoprim/sulfa = S where trimethoprim = S (no changes)</span></a>
<a class="sourceLine" id="cb14-40" data-line-number="40"><span class="co"># </span></a>
<a class="sourceLine" id="cb14-41" data-line-number="41"><span class="co"># =&gt; EUCAST rules affected 1,808 out of 5,000 rows -&gt; changed 996 test results.</span></a></code></pre></div>
<a class="sourceLine" id="cb14-41" data-line-number="41"><span class="co"># =&gt; EUCAST rules affected 1,860 out of 5,000 rows -&gt; changed 1,018 test results.</span></a></code></pre></div>
</div>
<div id="adding-new-variables" class="section level2">
<h2 class="hasAnchor">
<a href="#adding-new-variables" class="anchor"></a>Adding new variables</h2>
<p>Now that we have the microbial ID, we can add some taxonomic properties:</p>
<div class="sourceCode" id="cb15"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb15-1" data-line-number="1">data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb15-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/mutate">mutate</a></span>(<span class="dt">gramstain =</span> <span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(bacteria),</a>
<a class="sourceLine" id="cb15-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="dt">gramstain =</span> <span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(bacteria),</a>
<a class="sourceLine" id="cb15-3" data-line-number="3"> <span class="dt">genus =</span> <span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(bacteria),</a>
<a class="sourceLine" id="cb15-4" data-line-number="4"> <span class="dt">species =</span> <span class="kw"><a href="../reference/mo_property.html">mo_species</a></span>(bacteria))</a></code></pre></div>
<div id="first-isolates" class="section level3">
@ -458,14 +461,14 @@
</blockquote>
<p>This <code>AMR</code> package includes this methodology with the <code><a href="../reference/first_isolate.html">first_isolate()</a></code> function. It adopts the episode of a year (can be changed by user) and it starts counting days after every selected isolate. This new variable can easily be added to our data:</p>
<div class="sourceCode" id="cb16"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb16-1" data-line-number="1">data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb16-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/mutate">mutate</a></span>(<span class="dt">first =</span> <span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(.))</a>
<a class="sourceLine" id="cb16-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="dt">first =</span> <span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(.))</a>
<a class="sourceLine" id="cb16-3" data-line-number="3"><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `bacteria` as input for `col_mo`.</span></a>
<a class="sourceLine" id="cb16-4" data-line-number="4"><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `date` as input for `col_date`.</span></a>
<a class="sourceLine" id="cb16-5" data-line-number="5"><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></a>
<a class="sourceLine" id="cb16-6" data-line-number="6"><span class="co"># =&gt; Found 2,928 first isolates (58.6% of total)</span></a></code></pre></div>
<p>So only 58.6% is suitable for resistance analysis! We can now filter on is with the <code><a href="https://www.rdocumentation.org/packages/dplyr/topics/filter">filter()</a></code> function, also from the <code>dplyr</code> package:</p>
<a class="sourceLine" id="cb16-6" data-line-number="6"><span class="co"># =&gt; Found 2,924 first isolates (58.5% of total)</span></a></code></pre></div>
<p>So only 58.5% is suitable for resistance analysis! We can now filter on is with the <code><a href="https://dplyr.tidyverse.org/reference/filter.html">filter()</a></code> function, also from the <code>dplyr</code> package:</p>
<div class="sourceCode" id="cb17"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb17-1" data-line-number="1">data_1st &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb17-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/filter">filter</a></span>(first <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>)</a></code></pre></div>
<a class="sourceLine" id="cb17-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(first <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>)</a></code></pre></div>
<p>For future use, the above two syntaxes can be shortened with the <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> function:</p>
<div class="sourceCode" id="cb18"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb18-1" data-line-number="1">data_1st &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb18-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>()</a></code></pre></div>
@ -489,41 +492,30 @@
<tbody>
<tr class="odd">
<td align="center">1</td>
<td align="center">2010-03-08</td>
<td align="center">V6</td>
<td align="center">2010-08-27</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">2</td>
<td align="center">2011-02-03</td>
<td align="center">V6</td>
<td align="center">2010-10-24</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
</tr>
<tr class="odd">
<td align="center">3</td>
<td align="center">2011-12-31</td>
<td align="center">V6</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">4</td>
<td align="center">2012-10-20</td>
<td align="center">V6</td>
<td align="center">2010-10-26</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
@ -531,86 +523,97 @@
<td align="center">S</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">4</td>
<td align="center">2011-12-25</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">5</td>
<td align="center">2012-12-17</td>
<td align="center">V6</td>
<td align="center">2012-05-04</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">I</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">6</td>
<td align="center">2013-08-27</td>
<td align="center">V6</td>
<td align="center">2012-05-18</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
</tr>
<tr class="odd">
<td align="center">7</td>
<td align="center">2012-05-23</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">7</td>
<td align="center">2013-09-21</td>
<td align="center">V6</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">8</td>
<td align="center">2014-07-19</td>
<td align="center">V6</td>
<td align="center">2012-06-18</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">FALSE</td>
</tr>
<tr class="odd">
<td align="center">9</td>
<td align="center">2014-07-24</td>
<td align="center">V6</td>
<td align="center">2013-10-02</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">10</td>
<td align="center">2013-10-22</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">10</td>
<td align="center">2014-11-23</td>
<td align="center">V6</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">TRUE</td>
</tr>
</tbody>
</table>
<p>Only 4 isolates are marked as first according to CLSI guideline. But when reviewing the antibiogram, it is obvious that some isolates are absolutely different strains and show be included too. This is why we weigh isolates, based on their antibiogram. The <code><a href="../reference/key_antibiotics.html">key_antibiotics()</a></code> function adds a vector with 18 key antibiotics: 6 broad spectrum ones, 6 small spectrum for Gram negatives and 6 small spectrum for Gram positives. These can be defined by the user.</p>
<p>Only 3 isolates are marked as first according to CLSI guideline. But when reviewing the antibiogram, it is obvious that some isolates are absolutely different strains and show be included too. This is why we weigh isolates, based on their antibiogram. The <code><a href="../reference/key_antibiotics.html">key_antibiotics()</a></code> function adds a vector with 18 key antibiotics: 6 broad spectrum ones, 6 small spectrum for Gram negatives and 6 small spectrum for Gram positives. These can be defined by the user.</p>
<p>If a column exists with a name like key(…)ab the <code><a href="../reference/first_isolate.html">first_isolate()</a></code> function will automatically use it and determine the first weighted isolates. Mind the NOTEs in below output:</p>
<div class="sourceCode" id="cb19"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb19-1" data-line-number="1">data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb19-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/mutate">mutate</a></span>(<span class="dt">keyab =</span> <span class="kw"><a href="../reference/key_antibiotics.html">key_antibiotics</a></span>(.)) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb19-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/mutate">mutate</a></span>(<span class="dt">first_weighted =</span> <span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(.))</a>
<a class="sourceLine" id="cb19-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="dt">keyab =</span> <span class="kw"><a href="../reference/key_antibiotics.html">key_antibiotics</a></span>(.)) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb19-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="dt">first_weighted =</span> <span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(.))</a>
<a class="sourceLine" id="cb19-4" data-line-number="4"><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `bacteria` as input for `col_mo`.</span></a>
<a class="sourceLine" id="cb19-5" data-line-number="5"><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `bacteria` as input for `col_mo`.</span></a>
<a class="sourceLine" id="cb19-6" data-line-number="6"><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `date` as input for `col_date`.</span></a>
<a class="sourceLine" id="cb19-7" data-line-number="7"><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></a>
<a class="sourceLine" id="cb19-8" data-line-number="8"><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `keyab` as input for `col_keyantibiotics`. Use col_keyantibiotics = FALSE to prevent this.</span></a>
<a class="sourceLine" id="cb19-9" data-line-number="9"><span class="co"># [Criterion] Inclusion based on key antibiotics, ignoring I.</span></a>
<a class="sourceLine" id="cb19-10" data-line-number="10"><span class="co"># =&gt; Found 4,422 first weighted isolates (88.4% of total)</span></a></code></pre></div>
<a class="sourceLine" id="cb19-10" data-line-number="10"><span class="co"># =&gt; Found 4,414 first weighted isolates (88.3% of total)</span></a></code></pre></div>
<table class="table">
<thead><tr class="header">
<th align="center">isolate</th>
@ -627,68 +630,44 @@
<tbody>
<tr class="odd">
<td align="center">1</td>
<td align="center">2010-03-08</td>
<td align="center">V6</td>
<td align="center">2010-08-27</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">TRUE</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">2</td>
<td align="center">2011-02-03</td>
<td align="center">V6</td>
<td align="center">2010-10-24</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">3</td>
<td align="center">2011-12-31</td>
<td align="center">V6</td>
<td align="center">2010-10-26</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">TRUE</td>
<td align="center">TRUE</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">4</td>
<td align="center">2012-10-20</td>
<td align="center">V6</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td>
</tr>
<tr class="odd">
<td align="center">5</td>
<td align="center">2012-12-17</td>
<td align="center">V6</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">6</td>
<td align="center">2013-08-27</td>
<td align="center">V6</td>
<td align="center">2011-12-25</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
@ -698,67 +677,92 @@
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">5</td>
<td align="center">2012-05-04</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">I</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">6</td>
<td align="center">2012-05-18</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">7</td>
<td align="center">2013-09-21</td>
<td align="center">V6</td>
<td align="center">2012-05-23</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">8</td>
<td align="center">2014-07-19</td>
<td align="center">V6</td>
<td align="center">2012-06-18</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">9</td>
<td align="center">2014-07-24</td>
<td align="center">V6</td>
<td align="center">2013-10-02</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">TRUE</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">10</td>
<td align="center">2013-10-22</td>
<td align="center">Q10</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">10</td>
<td align="center">2014-11-23</td>
<td align="center">V6</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">TRUE</td>
<td align="center">TRUE</td>
</tr>
</tbody>
</table>
<p>Instead of 4, now 8 isolates are flagged. In total, 88.4% of all isolates are marked first weighted - 147% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.</p>
<p>Instead of 3, now 8 isolates are flagged. In total, 88.3% of all isolates are marked first weighted - 146.8% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.</p>
<p>As with <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code>, theres a shortcut for this new algorithm too:</p>
<div class="sourceCode" id="cb20"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb20-1" data-line-number="1">data_1st &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb20-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_weighted_isolate</a></span>()</a></code></pre></div>
<p>So we end up with 4,422 isolates for analysis.</p>
<p>So we end up with 4,414 isolates for analysis.</p>
<p>We can remove unneeded columns:</p>
<div class="sourceCode" id="cb21"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb21-1" data-line-number="1">data_1st &lt;-<span class="st"> </span>data_1st <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb21-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/select">select</a></span>(<span class="op">-</span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(first, keyab))</a></code></pre></div>
<a class="sourceLine" id="cb21-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(<span class="op">-</span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(first, keyab))</a></code></pre></div>
<p>Now our data looks like:</p>
<div class="sourceCode" id="cb22"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb22-1" data-line-number="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/utils/topics/head">head</a></span>(data_1st)</a></code></pre></div>
<table class="table">
<thead><tr class="header">
<th></th>
<th align="center">date</th>
<th align="center">patient_id</th>
<th align="center">hospital</th>
@ -775,13 +779,14 @@
</tr></thead>
<tbody>
<tr class="odd">
<td align="center">2013-03-25</td>
<td align="center">O5</td>
<td>2</td>
<td align="center">2011-05-22</td>
<td align="center">Y3</td>
<td align="center">Hospital B</td>
<td align="center">B_STRPTC_PNE</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">F</td>
<td align="center">Gram positive</td>
@ -790,56 +795,28 @@
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">2014-05-07</td>
<td align="center">W10</td>
<td align="center">Hospital A</td>
<td align="center">B_KLBSL_PNE</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
<td align="center">Gram negative</td>
<td align="center">Klebsiella</td>
<td align="center">pneumoniae</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">2014-08-13</td>
<td align="center">L5</td>
<td align="center">Hospital D</td>
<td align="center">B_ESCHR_COL</td>
<td>3</td>
<td align="center">2015-11-10</td>
<td align="center">F1</td>
<td align="center">Hospital C</td>
<td align="center">B_STPHY_AUR</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td>
<td align="center">Gram negative</td>
<td align="center">Escherichia</td>
<td align="center">coli</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">2014-07-10</td>
<td align="center">Z2</td>
<td align="center">Hospital D</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
<td align="center">Gram negative</td>
<td align="center">Escherichia</td>
<td align="center">coli</td>
<td align="center">Gram positive</td>
<td align="center">Staphylococcus</td>
<td align="center">aureus</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">2014-09-18</td>
<td align="center">Z9</td>
<td>4</td>
<td align="center">2011-10-10</td>
<td align="center">X7</td>
<td align="center">Hospital D</td>
<td align="center">B_STPHY_AUR</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
@ -850,15 +827,48 @@
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">2015-04-27</td>
<td align="center">Q3</td>
<td align="center">Hospital C</td>
<td>5</td>
<td align="center">2017-11-10</td>
<td align="center">B3</td>
<td align="center">Hospital D</td>
<td align="center">B_STPHY_AUR</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">M</td>
<td align="center">Gram positive</td>
<td align="center">Staphylococcus</td>
<td align="center">aureus</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td>6</td>
<td align="center">2014-11-09</td>
<td align="center">O5</td>
<td align="center">Hospital B</td>
<td align="center">B_KLBSL_PNE</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">F</td>
<td align="center">Gram negative</td>
<td align="center">Klebsiella</td>
<td align="center">pneumoniae</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td>7</td>
<td align="center">2013-01-26</td>
<td align="center">F4</td>
<td align="center">Hospital B</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
<td align="center">M</td>
<td align="center">Gram negative</td>
<td align="center">Escherichia</td>
<td align="center">coli</td>
@ -879,7 +889,7 @@
<div class="sourceCode" id="cb24"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb24-1" data-line-number="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(genus, species)</a></code></pre></div>
<p><strong>Frequency table of <code>genus</code> and <code>species</code></strong><br>
Columns: 2<br>
Length: 4,422 (of which NA: 0 = 0.00%)<br>
Length: 4,414 (of which NA: 0 = 0.00%)<br>
Unique: 4</p>
<p>Shortest: 16<br>
Longest: 24</p>
@ -896,33 +906,33 @@ Longest: 24</p>
<tr class="odd">
<td align="left">1</td>
<td align="left">Escherichia coli</td>
<td align="right">2,183</td>
<td align="right">49.4%</td>
<td align="right">2,183</td>
<td align="right">49.4%</td>
<td align="right">2,153</td>
<td align="right">48.8%</td>
<td align="right">2,153</td>
<td align="right">48.8%</td>
</tr>
<tr class="even">
<td align="left">2</td>
<td align="left">Staphylococcus aureus</td>
<td align="right">1,120</td>
<td align="right">25.3%</td>
<td align="right">3,303</td>
<td align="right">74.7%</td>
<td align="right">1,107</td>
<td align="right">25.1%</td>
<td align="right">3,260</td>
<td align="right">73.9%</td>
</tr>
<tr class="odd">
<td align="left">3</td>
<td align="left">Streptococcus pneumoniae</td>
<td align="right">666</td>
<td align="right">15.1%</td>
<td align="right">3,969</td>
<td align="right">89.8%</td>
<td align="right">677</td>
<td align="right">15.3%</td>
<td align="right">3,937</td>
<td align="right">89.2%</td>
</tr>
<tr class="even">
<td align="left">4</td>
<td align="left">Klebsiella pneumoniae</td>
<td align="right">453</td>
<td align="right">10.2%</td>
<td align="right">4,422</td>
<td align="right">477</td>
<td align="right">10.8%</td>
<td align="right">4,414</td>
<td align="right">100.0%</td>
</tr>
</tbody>
@ -932,11 +942,11 @@ Longest: 24</p>
<a href="#resistance-percentages" class="anchor"></a>Resistance percentages</h3>
<p>The functions <code>portion_R</code>, <code>portion_RI</code>, <code>portion_I</code>, <code>portion_IS</code> and <code>portion_S</code> can be used to determine the portion of a specific antimicrobial outcome. They can be used on their own:</p>
<div class="sourceCode" id="cb25"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb25-1" data-line-number="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_IR</a></span>(amox)</a>
<a class="sourceLine" id="cb25-2" data-line-number="2"><span class="co"># [1] 0.4730891</span></a></code></pre></div>
<p>Or can be used in conjuction with <code><a href="https://www.rdocumentation.org/packages/dplyr/topics/group_by">group_by()</a></code> and <code><a href="https://www.rdocumentation.org/packages/dplyr/topics/summarise">summarise()</a></code>, both from the <code>dplyr</code> package:</p>
<a class="sourceLine" id="cb25-2" data-line-number="2"><span class="co"># [1] 0.4857272</span></a></code></pre></div>
<p>Or can be used in conjuction with <code><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by()</a></code> and <code><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise()</a></code>, both from the <code>dplyr</code> package:</p>
<div class="sourceCode" id="cb26"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb26-1" data-line-number="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb26-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/group_by">group_by</a></span>(hospital) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb26-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/summarise">summarise</a></span>(<span class="dt">amoxicillin =</span> <span class="kw"><a href="../reference/portion.html">portion_IR</a></span>(amox))</a></code></pre></div>
<a class="sourceLine" id="cb26-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(hospital) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb26-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise</a></span>(<span class="dt">amoxicillin =</span> <span class="kw"><a href="../reference/portion.html">portion_IR</a></span>(amox))</a></code></pre></div>
<table class="table">
<thead><tr class="header">
<th align="center">hospital</th>
@ -945,26 +955,26 @@ Longest: 24</p>
<tbody>
<tr class="odd">
<td align="center">Hospital A</td>
<td align="center">0.4980784</td>
<td align="center">0.4615385</td>
</tr>
<tr class="even">
<td align="center">Hospital B</td>
<td align="center">0.4516332</td>
<td align="center">0.4961089</td>
</tr>
<tr class="odd">
<td align="center">Hospital C</td>
<td align="center">0.4705882</td>
<td align="center">0.4975767</td>
</tr>
<tr class="even">
<td align="center">Hospital D</td>
<td align="center">0.4767837</td>
<td align="center">0.4942288</td>
</tr>
</tbody>
</table>
<p>Of course it would be very convenient to know the number of isolates responsible for the percentages. For that purpose the <code><a href="../reference/count.html">n_rsi()</a></code> can be used, which works exactly like <code><a href="https://www.rdocumentation.org/packages/dplyr/topics/n_distinct">n_distinct()</a></code> from the <code>dplyr</code> package. It counts all isolates available for every group (i.e. values S, I or R):</p>
<p>Of course it would be very convenient to know the number of isolates responsible for the percentages. For that purpose the <code><a href="../reference/count.html">n_rsi()</a></code> can be used, which works exactly like <code><a href="https://dplyr.tidyverse.org/reference/n_distinct.html">n_distinct()</a></code> from the <code>dplyr</code> package. It counts all isolates available for every group (i.e. values S, I or R):</p>
<div class="sourceCode" id="cb27"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb27-1" data-line-number="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb27-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/group_by">group_by</a></span>(hospital) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb27-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/summarise">summarise</a></span>(<span class="dt">amoxicillin =</span> <span class="kw"><a href="../reference/portion.html">portion_IR</a></span>(amox),</a>
<a class="sourceLine" id="cb27-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(hospital) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb27-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise</a></span>(<span class="dt">amoxicillin =</span> <span class="kw"><a href="../reference/portion.html">portion_IR</a></span>(amox),</a>
<a class="sourceLine" id="cb27-4" data-line-number="4"> <span class="dt">available =</span> <span class="kw"><a href="../reference/count.html">n_rsi</a></span>(amox))</a></code></pre></div>
<table class="table">
<thead><tr class="header">
@ -975,30 +985,30 @@ Longest: 24</p>
<tbody>
<tr class="odd">
<td align="center">Hospital A</td>
<td align="center">0.4980784</td>
<td align="center">1301</td>
<td align="center">0.4615385</td>
<td align="center">1300</td>
</tr>
<tr class="even">
<td align="center">Hospital B</td>
<td align="center">0.4516332</td>
<td align="center">1592</td>
<td align="center">0.4961089</td>
<td align="center">1542</td>
</tr>
<tr class="odd">
<td align="center">Hospital C</td>
<td align="center">0.4705882</td>
<td align="center">646</td>
<td align="center">0.4975767</td>
<td align="center">619</td>
</tr>
<tr class="even">
<td align="center">Hospital D</td>
<td align="center">0.4767837</td>
<td align="center">883</td>
<td align="center">0.4942288</td>
<td align="center">953</td>
</tr>
</tbody>
</table>
<p>These functions can also be used to get the portion of multiple antibiotics, to calculate co-resistance very easily:</p>
<div class="sourceCode" id="cb28"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb28-1" data-line-number="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb28-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/group_by">group_by</a></span>(genus) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb28-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/summarise">summarise</a></span>(<span class="dt">amoxicillin =</span> <span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl),</a>
<a class="sourceLine" id="cb28-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(genus) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb28-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise</a></span>(<span class="dt">amoxicillin =</span> <span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl),</a>
<a class="sourceLine" id="cb28-4" data-line-number="4"> <span class="dt">gentamicin =</span> <span class="kw"><a href="../reference/portion.html">portion_S</a></span>(gent),</a>
<a class="sourceLine" id="cb28-5" data-line-number="5"> <span class="st">"amox + gent"</span> =<span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent))</a></code></pre></div>
<table class="table">
@ -1011,34 +1021,34 @@ Longest: 24</p>
<tbody>
<tr class="odd">
<td align="center">Escherichia</td>
<td align="center">0.7498855</td>
<td align="center">0.9079249</td>
<td align="center">0.9775538</td>
<td align="center">0.7445425</td>
<td align="center">0.9173247</td>
<td align="center">0.9804923</td>
</tr>
<tr class="even">
<td align="center">Klebsiella</td>
<td align="center">0.7505519</td>
<td align="center">0.9006623</td>
<td align="center">0.9713024</td>
<td align="center">0.7169811</td>
<td align="center">0.9119497</td>
<td align="center">0.9769392</td>
</tr>
<tr class="odd">
<td align="center">Staphylococcus</td>
<td align="center">0.7437500</td>
<td align="center">0.9196429</td>
<td align="center">0.9767857</td>
<td align="center">0.7705510</td>
<td align="center">0.9168925</td>
<td align="center">0.9828365</td>
</tr>
<tr class="even">
<td align="center">Streptococcus</td>
<td align="center">0.7357357</td>
<td align="center">0.7474151</td>
<td align="center">0.0000000</td>
<td align="center">0.7357357</td>
<td align="center">0.7474151</td>
</tr>
</tbody>
</table>
<p>To make a transition to the next part, lets see how this difference could be plotted:</p>
<div class="sourceCode" id="cb29"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb29-1" data-line-number="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb29-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/group_by">group_by</a></span>(genus) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb29-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/summarise">summarise</a></span>(<span class="st">"1. Amoxicillin"</span> =<span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl),</a>
<a class="sourceLine" id="cb29-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(genus) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb29-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise</a></span>(<span class="st">"1. Amoxicillin"</span> =<span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl),</a>
<a class="sourceLine" id="cb29-4" data-line-number="4"> <span class="st">"2. Gentamicin"</span> =<span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(gent),</a>
<a class="sourceLine" id="cb29-5" data-line-number="5"> <span class="st">"3. Amox + gent"</span> =<span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent)) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb29-6" data-line-number="6"><span class="st"> </span>tidyr<span class="op">::</span><span class="kw"><a href="https://tidyr.tidyverse.org/reference/gather.html">gather</a></span>(<span class="st">"Antibiotic"</span>, <span class="st">"S"</span>, <span class="op">-</span>genus) <span class="op">%&gt;%</span></a>
@ -1071,7 +1081,7 @@ Longest: 24</p>
<p>Omit the <code>translate_ab = FALSE</code> to have the antibiotic codes (amox, amcl, cipr, gent) translated to official WHO names (amoxicillin, amoxicillin and betalactamase inhibitor, ciprofloxacin, gentamicin).</p>
<p>If we group on e.g. the <code>genus</code> column and add some additional functions from our package, we can create this:</p>
<div class="sourceCode" id="cb32"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb32-1" data-line-number="1"><span class="co"># group the data on `genus`</span></a>
<a class="sourceLine" id="cb32-2" data-line-number="2"><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/ggplot.html">ggplot</a></span>(data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/group_by">group_by</a></span>(genus)) <span class="op">+</span><span class="st"> </span></a>
<a class="sourceLine" id="cb32-2" data-line-number="2"><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/ggplot.html">ggplot</a></span>(data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(genus)) <span class="op">+</span><span class="st"> </span></a>
<a class="sourceLine" id="cb32-3" data-line-number="3"><span class="st"> </span><span class="co"># create bars with genus on x axis</span></a>
<a class="sourceLine" id="cb32-4" data-line-number="4"><span class="st"> </span><span class="co"># it looks for variables with class `rsi`,</span></a>
<a class="sourceLine" id="cb32-5" data-line-number="5"><span class="st"> </span><span class="co"># of which we have 4 (earlier created with `as.rsi`)</span></a>
@ -1093,7 +1103,7 @@ Longest: 24</p>
<p><img src="AMR_files/figure-html/plot%204-1.png" width="720"></p>
<p>To simplify this, we also created the <code><a href="../reference/ggplot_rsi.html">ggplot_rsi()</a></code> function, which combines almost all above functions:</p>
<div class="sourceCode" id="cb33"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb33-1" data-line-number="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb33-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/group_by">group_by</a></span>(genus) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb33-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(genus) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb33-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="../reference/ggplot_rsi.html">ggplot_rsi</a></span>(<span class="dt">x =</span> <span class="st">"genus"</span>,</a>
<a class="sourceLine" id="cb33-4" data-line-number="4"> <span class="dt">facet =</span> <span class="st">"Antibiotic"</span>,</a>
<a class="sourceLine" id="cb33-5" data-line-number="5"> <span class="dt">breaks =</span> <span class="dv">0</span><span class="op">:</span><span class="dv">4</span> <span class="op">*</span><span class="st"> </span><span class="dv">25</span>,</a>
@ -1127,12 +1137,12 @@ Longest: 24</p>
</table>
<p>We can transform the data and apply the test in only a couple of lines:</p>
<div class="sourceCode" id="cb34"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb34-1" data-line-number="1">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb34-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/filter">filter</a></span>(hospital_id <span class="op">%in%</span><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="st">"A"</span>, <span class="st">"D"</span>)) <span class="op">%&gt;%</span><span class="st"> </span><span class="co"># filter on only hospitals A and D</span></a>
<a class="sourceLine" id="cb34-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/select">select</a></span>(hospital_id, fosf) <span class="op">%&gt;%</span><span class="st"> </span><span class="co"># select the hospitals and fosfomycin</span></a>
<a class="sourceLine" id="cb34-4" data-line-number="4"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/group_by">group_by</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span><span class="co"># group on the hospitals</span></a>
<a class="sourceLine" id="cb34-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(hospital_id <span class="op">%in%</span><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="st">"A"</span>, <span class="st">"D"</span>)) <span class="op">%&gt;%</span><span class="st"> </span><span class="co"># filter on only hospitals A and D</span></a>
<a class="sourceLine" id="cb34-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(hospital_id, fosf) <span class="op">%&gt;%</span><span class="st"> </span><span class="co"># select the hospitals and fosfomycin</span></a>
<a class="sourceLine" id="cb34-4" data-line-number="4"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span><span class="co"># group on the hospitals</span></a>
<a class="sourceLine" id="cb34-5" data-line-number="5"><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_df</a></span>(<span class="dt">combine_IR =</span> <span class="ot">TRUE</span>) <span class="op">%&gt;%</span><span class="st"> </span><span class="co"># count all isolates per group (hospital_id)</span></a>
<a class="sourceLine" id="cb34-6" data-line-number="6"><span class="st"> </span>tidyr<span class="op">::</span><span class="kw"><a href="https://tidyr.tidyverse.org/reference/spread.html">spread</a></span>(hospital_id, Value) <span class="op">%&gt;%</span><span class="st"> </span><span class="co"># transform output so A and D are columns</span></a>
<a class="sourceLine" id="cb34-7" data-line-number="7"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/select">select</a></span>(A, D) <span class="op">%&gt;%</span><span class="st"> </span><span class="co"># and select these only</span></a>
<a class="sourceLine" id="cb34-7" data-line-number="7"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(A, D) <span class="op">%&gt;%</span><span class="st"> </span><span class="co"># and select these only</span></a>
<a class="sourceLine" id="cb34-8" data-line-number="8"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/matrix">as.matrix</a></span>() <span class="op">%&gt;%</span><span class="st"> </span><span class="co"># transform to good old matrix for fisher.test()</span></a>
<a class="sourceLine" id="cb34-9" data-line-number="9"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/stats/topics/fisher.test">fisher.test</a></span>() <span class="co"># do Fisher's Exact Test</span></a>
<a class="sourceLine" id="cb34-10" data-line-number="10"><span class="co"># </span></a>

Binary file not shown.

Before

Width:  |  Height:  |  Size: 31 KiB

After

Width:  |  Height:  |  Size: 31 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 24 KiB

After

Width:  |  Height:  |  Size: 24 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 65 KiB

After

Width:  |  Height:  |  Size: 65 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 48 KiB

After

Width:  |  Height:  |  Size: 48 KiB

View File

@ -178,7 +178,7 @@
<h1>How to apply EUCAST rules</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">25 January 2019</h4>
<h4 class="date">26 January 2019</h4>
<div class="hidden name"><code>EUCAST.Rmd</code></div>

View File

@ -178,7 +178,7 @@
<h1>How to use the <em>G</em>-test</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">25 January 2019</h4>
<h4 class="date">26 January 2019</h4>
<div class="hidden name"><code>G_test.Rmd</code></div>

View File

@ -178,7 +178,7 @@
<h1>How to predict antimicrobial resistance</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">25 January 2019</h4>
<h4 class="date">26 January 2019</h4>
<div class="hidden name"><code>Predict.Rmd</code></div>

View File

@ -178,7 +178,7 @@
<h1>How to get properties of an antibiotic</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">25 January 2019</h4>
<h4 class="date">26 January 2019</h4>
<div class="hidden name"><code>ab_property.Rmd</code></div>

View File

@ -178,7 +178,7 @@
<h1>Benchmarks</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">25 January 2019</h4>
<h4 class="date">26 January 2019</h4>
<div class="hidden name"><code>benchmarks.Rmd</code></div>
@ -240,15 +240,15 @@
<div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb4-1" data-line-number="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/library">library</a></span>(dplyr)</a>
<a class="sourceLine" id="cb4-2" data-line-number="2"><span class="co"># take 500,000 random MO codes from the septic_patients data set</span></a>
<a class="sourceLine" id="cb4-3" data-line-number="3">x =<span class="st"> </span>septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb4-4" data-line-number="4"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/sample">sample_n</a></span>(<span class="dv">500000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb4-5" data-line-number="5"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/pull">pull</a></span>(mo)</a>
<a class="sourceLine" id="cb4-4" data-line-number="4"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/sample.html">sample_n</a></span>(<span class="dv">500000</span>, <span class="dt">replace =</span> <span class="ot">TRUE</span>) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb4-5" data-line-number="5"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/pull.html">pull</a></span>(mo)</a>
<a class="sourceLine" id="cb4-6" data-line-number="6"> </a>
<a class="sourceLine" id="cb4-7" data-line-number="7"><span class="co"># got the right length?</span></a>
<a class="sourceLine" id="cb4-8" data-line-number="8"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/length">length</a></span>(x)</a>
<a class="sourceLine" id="cb4-9" data-line-number="9"><span class="co"># [1] 500000</span></a>
<a class="sourceLine" id="cb4-10" data-line-number="10"></a>
<a class="sourceLine" id="cb4-11" data-line-number="11"><span class="co"># and how many unique values do we have?</span></a>
<a class="sourceLine" id="cb4-12" data-line-number="12"><span class="kw"><a href="https://www.rdocumentation.org/packages/dplyr/topics/n_distinct">n_distinct</a></span>(x)</a>
<a class="sourceLine" id="cb4-12" data-line-number="12"><span class="kw"><a href="https://dplyr.tidyverse.org/reference/n_distinct.html">n_distinct</a></span>(x)</a>
<a class="sourceLine" id="cb4-13" data-line-number="13"><span class="co"># [1] 96</span></a>
<a class="sourceLine" id="cb4-14" data-line-number="14"></a>
<a class="sourceLine" id="cb4-15" data-line-number="15"><span class="co"># only 96, but distributed in 500,000 results. now let's see:</span></a>

View File

@ -178,7 +178,7 @@
<h1>How to create frequency tables</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">25 January 2019</h4>
<h4 class="date">26 January 2019</h4>
<div class="hidden name"><code>freq.Rmd</code></div>

View File

@ -178,7 +178,7 @@
<h1>How to get properties of a microorganism</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">25 January 2019</h4>
<h4 class="date">26 January 2019</h4>
<div class="hidden name"><code>mo_property.Rmd</code></div>

View File

@ -71,7 +71,7 @@ pre, code {
font-family: 'Courier New', monospace;
font-size: 100% !important;
font-weight: bold;
background-color: transparent;
background-color: #f4f4f4;
}
pre {
font-size: 90% !important;
@ -84,7 +84,7 @@ kbd {
font-size: small;
vertical-align: text-bottom;
color: #2c3e50;
background: #eee;
background: #eeeeee;
font-weight: bold;
}

View File

@ -178,14 +178,26 @@
<div class="contents col-md-9">
<div id="amr-for-r" class="section level1">
<div class="page-header"><h1 class="hasAnchor">
<a href="#amr-for-r" class="anchor"></a><code>AMR</code> (for R) <img src="reference/figures/logo.png" align="right" height="120px">
<a href="#amr-for-r" class="anchor"></a><code>AMR</code> (for R) <img src="./logo.png" align="right" height="120px">
</h1></div>
<p><em>(<help title="Too Long, Didn't Read">TLDR</help> - to find out how to conduct AMR analysis, please <a href="./articles/AMR.html">continue reading here to get started</a>.</em></p>
<hr>
<p><code>AMR</code> is a free and open-source <a href="https://www.r-project.org">R package</a> to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial properties by using evidence-based methods.</p>
<p>We created this package for academic research at the Faculty of Medical Sciences of the University of Groningen and the Medical Microbiology &amp; Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG). This R package is free software; you can freely use and distribute it for both personal and commercial (but <strong>not</strong> patent) purposes under the terms of the GNU General Public License version 2.0 (GPL-2), as published by the Free Software Foundation. Read further about our GPL-2 licence <a href="./LICENSE-text.html">here</a>.</p>
<p>We created this package for both academic research and routine analysis at the Faculty of Medical Sciences of the University of Groningen and the Medical Microbiology &amp; Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG). This R package is actively maintained and free software; you can freely use and distribute it for both personal and commercial (but <strong>not</strong> patent) purposes under the terms of the GNU General Public Licence version 2.0 (GPL-2), as published by the Free Software Foundation. Read the full licence <a href="./LICENSE-text.html">here</a>.</p>
<p>This package can be used for:</p>
<ul>
<li>Calculating antimicrobial resistance</li>
<li>Predicting antimicrobial resistance using regression models</li>
<li>Getting properties for any microorganism (like Gram stain, species, genus or family)</li>
<li>Getting properties for any antibiotic (like name, ATC code, defined daily dose or trade name)</li>
<li>Plotting antimicrobial resistance</li>
<li>Determining first isolates to be used for AMR analysis</li>
<li>Applying EUCAST rules</li>
<li>Determining multi-drug resistance organisms (MDRO)</li>
<li>Descriptive statistics: frequency tables, kurtosis and skewness</li>
</ul>
<p>This package is ready-to-use for a professional environment by specialists in the following fields:</p>
<p>Medical Microbiology:</p>
<p>Medical Microbiology</p>
<ul>
<li>Epidemiologists (both clinical microbiological and research)</li>
<li>Research Microbiologists</li>
@ -193,18 +205,18 @@
<li>Research Pharmacologists</li>
<li>Data Scientists / Data Analysts</li>
</ul>
<p>Veterinary Microbiology:</p>
<p>Veterinary Microbiology</p>
<ul>
<li>Research Veterinarians</li>
<li>Veterinary Epidemiologists</li>
</ul>
<p>Microbial Ecology:</p>
<p>Microbial Ecology</p>
<ul>
<li>Soil Microbiologists</li>
<li>Extremophile Researchers</li>
<li>Astrobiologists</li>
</ul>
<p>Developers:</p>
<p>Developers</p>
<ul>
<li>Package developers for R</li>
<li>Software developers</li>
@ -267,7 +279,7 @@
</li>
<li>Use <code><a href="reference/mdro.html">mdro()</a></code> (abbreviation of Multi Drug Resistant Organisms) to check your isolates for exceptional resistance with country-specific guidelines or EUCAST rules. Currently, national guidelines for Germany and the Netherlands are supported.</li>
<li>The data set <code>microorganisms</code> contains the complete taxonomic tree of more than 18,000 microorganisms (bacteria, fungi/yeasts and protozoa). Furthermore, the colloquial name and Gram stain are available, which enables resistance analysis of e.g. different antibiotics per Gram stain. The package also contains functions to look up values in this data set like <code><a href="reference/mo_property.html">mo_genus()</a></code>, <code><a href="reference/mo_property.html">mo_family()</a></code>, <code><a href="reference/mo_property.html">mo_gramstain()</a></code> or even <code><a href="reference/mo_property.html">mo_phylum()</a></code>. As they use <code><a href="reference/as.mo.html">as.mo()</a></code> internally, they also use artificial intelligence. For example, <code><a href="reference/mo_property.html">mo_genus("MRSA")</a></code> and <code><a href="reference/mo_property.html">mo_genus("S. aureus")</a></code> will both return <code>"Staphylococcus"</code>. They also come with support for German, Dutch, Spanish, Italian, French and Portuguese. These functions can be used to add new variables to your data.</li>
<li>The data set <code>antibiotics</code> contains the ATC code, LIS codes, official name, trivial name and DDD of both oral and parenteral administration. It also contains a total of 298 trade names. Use functions like <code><a href="reference/ab_property.html">ab_name()</a></code> and <code><a href="reference/ab_property.html">ab_tradenames()</a></code> to look up values. The <code>ab_*</code> functions use <code><a href="reference/as.atc.html">as.atc()</a></code> internally so they support AI to guess your expected result. For example, <code><a href="reference/ab_property.html">ab_name("Fluclox")</a></code>, <code><a href="reference/ab_property.html">ab_name("Floxapen")</a></code> and <code><a href="reference/ab_property.html">ab_name("J01CF05")</a></code> will all return <code>"Flucloxacillin"</code>. These functions can again be used to add new variables to your data.</li>
<li>The data set <code>antibiotics</code> contains the ATC code, LIS codes, official name, trivial name and DDD of both oral and parenteral administration. It also contains a total of 298 trade names. Use functions like <code><a href="reference/AMR-deprecated.html">ab_name()</a></code> and <code><a href="reference/AMR-deprecated.html">ab_tradenames()</a></code> to look up values. The <code>ab_*</code> functions use <code><a href="reference/as.atc.html">as.atc()</a></code> internally so they support AI to guess your expected result. For example, <code><a href="reference/AMR-deprecated.html">ab_name("Fluclox")</a></code>, <code><a href="reference/AMR-deprecated.html">ab_name("Floxapen")</a></code> and <code><a href="reference/AMR-deprecated.html">ab_name("J01CF05")</a></code> will all return <code>"Flucloxacillin"</code>. These functions can again be used to add new variables to your data.</li>
</ul>
</li>
<li>

BIN
docs/logo.png Normal file

Binary file not shown.

After

Width:  |  Height:  |  Size: 56 KiB

View File

@ -229,6 +229,16 @@
<ul>
<li>
<strong>BREAKING</strong>: removed deprecated functions, parameters and references to bactid. Use <code><a href="../reference/as.mo.html">as.mo()</a></code> to identify an MO code.</li>
<li>
<p>All <code>ab_*</code> functions are deprecated and replaced by <code>atc_*</code> functions:</p>
<div class="sourceCode" id="cb1"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb1-1" data-line-number="1">ab_property -&gt;<span class="st"> </span><span class="kw"><a href="../reference/atc_property.html">atc_property</a></span>()</a>
<a class="sourceLine" id="cb1-2" data-line-number="2">ab_name -&gt;<span class="st"> </span><span class="kw"><a href="../reference/atc_property.html">atc_name</a></span>()</a>
<a class="sourceLine" id="cb1-3" data-line-number="3">ab_official -&gt;<span class="st"> </span><span class="kw"><a href="../reference/atc_property.html">atc_official</a></span>()</a>
<a class="sourceLine" id="cb1-4" data-line-number="4">ab_trivial_nl -&gt;<span class="st"> </span><span class="kw"><a href="../reference/atc_property.html">atc_trivial_nl</a></span>()</a>
<a class="sourceLine" id="cb1-5" data-line-number="5">ab_certe -&gt;<span class="st"> </span><span class="kw"><a href="../reference/atc_property.html">atc_certe</a></span>()</a>
<a class="sourceLine" id="cb1-6" data-line-number="6">ab_umcg -&gt;<span class="st"> </span><span class="kw"><a href="../reference/atc_property.html">atc_umcg</a></span>()</a>
<a class="sourceLine" id="cb1-7" data-line-number="7">ab_tradenames -&gt;<span class="st"> </span><span class="kw"><a href="../reference/atc_property.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>
<li>New website: <a href="https://msberends.gitlab.io/AMR" class="uri">https://msberends.gitlab.io/AMR</a> (built with the great <a href="https://pkgdown.r-lib.org/"><code>pkgdown</code></a>)
<ul>
<li>Contains the complete manual of this package and all of its functions with an explanation of their parameters</li>
@ -244,20 +254,20 @@
<li>New function <code><a href="../reference/age_groups.html">age_groups()</a></code> to split ages into custom or predefined groups (like children or elderly). This allows for easier demographic antimicrobial resistance analysis per age group.</li>
<li>
<p>New function <code><a href="../reference/resistance_predict.html">ggplot_rsi_predict()</a></code> as well as the base R <code><a href="https://www.rdocumentation.org/packages/graphics/topics/plot">plot()</a></code> function can now be used for resistance prediction calculated with <code><a href="../reference/resistance_predict.html">resistance_predict()</a></code>:</p>
<div class="sourceCode" id="cb1"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb1-1" data-line-number="1">x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/resistance_predict.html">resistance_predict</a></span>(septic_patients, <span class="dt">col_ab =</span> <span class="st">"amox"</span>)</a>
<a class="sourceLine" id="cb1-2" data-line-number="2"><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/plot">plot</a></span>(x)</a>
<a class="sourceLine" id="cb1-3" data-line-number="3"><span class="kw"><a href="../reference/resistance_predict.html">ggplot_rsi_predict</a></span>(x)</a></code></pre></div>
<div class="sourceCode" id="cb2"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb2-1" data-line-number="1">x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/resistance_predict.html">resistance_predict</a></span>(septic_patients, <span class="dt">col_ab =</span> <span class="st">"amox"</span>)</a>
<a class="sourceLine" id="cb2-2" data-line-number="2"><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/plot">plot</a></span>(x)</a>
<a class="sourceLine" id="cb2-3" data-line-number="3"><span class="kw"><a href="../reference/resistance_predict.html">ggplot_rsi_predict</a></span>(x)</a></code></pre></div>
</li>
<li>
<p>Functions <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> and <code><a href="../reference/first_isolate.html">filter_first_weighted_isolate()</a></code> to shorten and fasten filtering on data sets with antimicrobial results, e.g.:</p>
<div class="sourceCode" id="cb2"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb2-1" data-line-number="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(...)</a>
<a class="sourceLine" id="cb2-2" data-line-number="2"><span class="co"># or</span></a>
<a class="sourceLine" id="cb2-3" data-line-number="3"><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(septic_patients, ...)</a></code></pre></div>
<div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb3-1" data-line-number="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(...)</a>
<a class="sourceLine" id="cb3-2" data-line-number="2"><span class="co"># or</span></a>
<a class="sourceLine" id="cb3-3" data-line-number="3"><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(septic_patients, ...)</a></code></pre></div>
<p>is equal to:</p>
<div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb3-1" data-line-number="1">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb3-2" data-line-number="2"><span class="st"> </span><span class="kw">mutate</span>(<span class="dt">only_firsts =</span> <span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(septic_patients, ...)) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb3-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/stats/topics/filter">filter</a></span>(only_firsts <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb3-4" data-line-number="4"><span class="st"> </span><span class="kw">select</span>(<span class="op">-</span>only_firsts)</a></code></pre></div>
<div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb4-1" data-line-number="1">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb4-2" data-line-number="2"><span class="st"> </span><span class="kw">mutate</span>(<span class="dt">only_firsts =</span> <span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(septic_patients, ...)) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb4-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/stats/topics/filter">filter</a></span>(only_firsts <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb4-4" data-line-number="4"><span class="st"> </span><span class="kw">select</span>(<span class="op">-</span>only_firsts)</a></code></pre></div>
</li>
<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>
@ -268,6 +278,10 @@
<ul>
<li>Added 65 antibiotics to the <code>antibiotics</code> data set, from the <a href="http://ec.europa.eu/health/documents/community-register/html/atc.htm">Pharmaceuticals Community Register</a> of the European Commission</li>
<li>Removed columns <code>atc_group1_nl</code> and <code>atc_group2_nl</code> from the <code>antibiotics</code> data set</li>
<li>Function <code>atc_ddd</code> has been renamed <code><a href="../reference/atc_online.html">atc_online_ddd()</a></code>
</li>
<li>Function <code>atc_groups</code> has been renamed <code><a href="../reference/atc_online.html">atc_online_groups()</a></code>
</li>
<li>Function <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code>:
<ul>
<li>Updated EUCAST Clinical breakpoints to <a href="http://www.eucast.org/clinical_breakpoints/">version 9.0 of 1 January 2019</a>
@ -383,10 +397,10 @@
<li>Fewer than 3 characters as input for <code>as.mo</code> will return NA</li>
<li>
<p>Function <code>as.mo</code> (and all <code>mo_*</code> wrappers) now supports genus abbreviations with “species” attached</p>
<div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb4-1" data-line-number="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. species"</span>) <span class="co"># B_ESCHR</span></a>
<a class="sourceLine" id="cb4-2" data-line-number="2"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"E. spp."</span>) <span class="co"># "Escherichia species"</span></a>
<a class="sourceLine" id="cb4-3" data-line-number="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S. spp"</span>) <span class="co"># B_STPHY</span></a>
<a class="sourceLine" id="cb4-4" data-line-number="4"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. species"</span>) <span class="co"># "Staphylococcus species"</span></a></code></pre></div>
<div class="sourceCode" id="cb5"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb5-1" data-line-number="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. species"</span>) <span class="co"># B_ESCHR</span></a>
<a class="sourceLine" id="cb5-2" data-line-number="2"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"E. spp."</span>) <span class="co"># "Escherichia species"</span></a>
<a class="sourceLine" id="cb5-3" data-line-number="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S. spp"</span>) <span class="co"># B_STPHY</span></a>
<a class="sourceLine" id="cb5-4" data-line-number="4"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. species"</span>) <span class="co"># "Staphylococcus species"</span></a></code></pre></div>
</li>
<li>Added parameter <code>combine_IR</code> (TRUE/FALSE) to functions <code>portion_df</code> and <code>count_df</code>, to indicate that all values of I and R must be merged into one, so the output only consists of S vs. IR (susceptible vs. non-susceptible)</li>
<li>Fix for <code>portion_*(..., as_percent = TRUE)</code> when minimal number of isolates would not be met</li>
@ -399,15 +413,15 @@
<ul>
<li>
<p>Support for grouping variables, test with:</p>
<div class="sourceCode" id="cb5"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb5-1" data-line-number="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb5-2" data-line-number="2"><span class="st"> </span><span class="kw">group_by</span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb5-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(gender)</a></code></pre></div>
<div class="sourceCode" id="cb6"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb6-1" data-line-number="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb6-2" data-line-number="2"><span class="st"> </span><span class="kw">group_by</span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb6-3" data-line-number="3"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(gender)</a></code></pre></div>
</li>
<li>
<p>Support for (un)selecting columns:</p>
<div class="sourceCode" id="cb6"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb6-1" data-line-number="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb6-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb6-3" data-line-number="3"><span class="st"> </span><span class="kw">select</span>(<span class="op">-</span>count, <span class="op">-</span>cum_count) <span class="co"># only get item, percent, cum_percent</span></a></code></pre></div>
<div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb7-1" data-line-number="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb7-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb7-3" data-line-number="3"><span class="st"> </span><span class="kw">select</span>(<span class="op">-</span>count, <span class="op">-</span>cum_count) <span class="co"># only get item, percent, cum_percent</span></a></code></pre></div>
</li>
<li>Check for <code><a href="https://www.rdocumentation.org/packages/hms/topics/hms">hms::is.hms</a></code>
</li>
@ -487,18 +501,18 @@
</li>
</ul>
<p>They also come with support for German, Dutch, French, Italian, Spanish and Portuguese:</p>
<div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb7-1" data-line-number="1"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>)</a>
<a class="sourceLine" id="cb7-2" data-line-number="2"><span class="co"># [1] "Gram negative"</span></a>
<a class="sourceLine" id="cb7-3" data-line-number="3"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"de"</span>) <span class="co"># German</span></a>
<a class="sourceLine" id="cb7-4" data-line-number="4"><span class="co"># [1] "Gramnegativ"</span></a>
<a class="sourceLine" id="cb7-5" data-line-number="5"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"es"</span>) <span class="co"># Spanish</span></a>
<a class="sourceLine" id="cb7-6" data-line-number="6"><span class="co"># [1] "Gram negativo"</span></a>
<a class="sourceLine" id="cb7-7" data-line-number="7"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. group A"</span>, <span class="dt">language =</span> <span class="st">"pt"</span>) <span class="co"># Portuguese</span></a>
<a class="sourceLine" id="cb7-8" data-line-number="8"><span class="co"># [1] "Streptococcus grupo A"</span></a></code></pre></div>
<div class="sourceCode" id="cb8"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb8-1" data-line-number="1"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>)</a>
<a class="sourceLine" id="cb8-2" data-line-number="2"><span class="co"># [1] "Gram negative"</span></a>
<a class="sourceLine" id="cb8-3" data-line-number="3"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"de"</span>) <span class="co"># German</span></a>
<a class="sourceLine" id="cb8-4" data-line-number="4"><span class="co"># [1] "Gramnegativ"</span></a>
<a class="sourceLine" id="cb8-5" data-line-number="5"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"es"</span>) <span class="co"># Spanish</span></a>
<a class="sourceLine" id="cb8-6" data-line-number="6"><span class="co"># [1] "Gram negativo"</span></a>
<a class="sourceLine" id="cb8-7" data-line-number="7"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. group A"</span>, <span class="dt">language =</span> <span class="st">"pt"</span>) <span class="co"># Portuguese</span></a>
<a class="sourceLine" id="cb8-8" data-line-number="8"><span class="co"># [1] "Streptococcus grupo A"</span></a></code></pre></div>
<p>Furthermore, former taxonomic names will give a note about the current taxonomic name:</p>
<div class="sourceCode" id="cb8"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb8-1" data-line-number="1"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"Esc blattae"</span>)</a>
<a class="sourceLine" id="cb8-2" data-line-number="2"><span class="co"># Note: 'Escherichia blattae' (Burgess et al., 1973) was renamed 'Shimwellia blattae' (Priest and Barker, 2010)</span></a>
<a class="sourceLine" id="cb8-3" data-line-number="3"><span class="co"># [1] "Gram negative"</span></a></code></pre></div>
<div class="sourceCode" id="cb9"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb9-1" data-line-number="1"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"Esc blattae"</span>)</a>
<a class="sourceLine" id="cb9-2" data-line-number="2"><span class="co"># Note: 'Escherichia blattae' (Burgess et al., 1973) was renamed 'Shimwellia blattae' (Priest and Barker, 2010)</span></a>
<a class="sourceLine" id="cb9-3" data-line-number="3"><span class="co"># [1] "Gram negative"</span></a></code></pre></div>
</li>
<li>Functions <code>count_R</code>, <code>count_IR</code>, <code>count_I</code>, <code>count_SI</code> and <code>count_S</code> to selectively count resistant or susceptible isolates
<ul>
@ -509,18 +523,18 @@
</li>
<li>
<p>Functions <code>as.mo</code> and <code>is.mo</code> as replacements for <code>as.bactid</code> and <code>is.bactid</code> (since the <code>microoganisms</code> data set not only contains bacteria). These last two functions are deprecated and will be removed in a future release. The <code>as.mo</code> function determines microbial IDs using Artificial Intelligence (AI):</p>
<div class="sourceCode" id="cb9"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb9-1" data-line-number="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. coli"</span>)</a>
<a class="sourceLine" id="cb9-2" data-line-number="2"><span class="co"># [1] B_ESCHR_COL</span></a>
<a class="sourceLine" id="cb9-3" data-line-number="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"MRSA"</span>)</a>
<a class="sourceLine" id="cb9-4" data-line-number="4"><span class="co"># [1] B_STPHY_AUR</span></a>
<a class="sourceLine" id="cb9-5" data-line-number="5"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S group A"</span>)</a>
<a class="sourceLine" id="cb9-6" data-line-number="6"><span class="co"># [1] B_STRPTC_GRA</span></a></code></pre></div>
<div class="sourceCode" id="cb10"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb10-1" data-line-number="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. coli"</span>)</a>
<a class="sourceLine" id="cb10-2" data-line-number="2"><span class="co"># [1] B_ESCHR_COL</span></a>
<a class="sourceLine" id="cb10-3" data-line-number="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"MRSA"</span>)</a>
<a class="sourceLine" id="cb10-4" data-line-number="4"><span class="co"># [1] B_STPHY_AUR</span></a>
<a class="sourceLine" id="cb10-5" data-line-number="5"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S group A"</span>)</a>
<a class="sourceLine" id="cb10-6" data-line-number="6"><span class="co"># [1] B_STRPTC_GRA</span></a></code></pre></div>
<p>And with great speed too - on a quite regular Linux server from 2007 it takes us less than 0.02 seconds to transform 25,000 items:</p>
<div class="sourceCode" id="cb10"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb10-1" data-line-number="1">thousands_of_E_colis &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/rep">rep</a></span>(<span class="st">"E. coli"</span>, <span class="dv">25000</span>)</a>
<a class="sourceLine" id="cb10-2" data-line-number="2">microbenchmark<span class="op">::</span><span class="kw"><a href="https://www.rdocumentation.org/packages/microbenchmark/topics/microbenchmark">microbenchmark</a></span>(<span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(thousands_of_E_colis), <span class="dt">unit =</span> <span class="st">"s"</span>)</a>
<a class="sourceLine" id="cb10-3" data-line-number="3"><span class="co"># Unit: seconds</span></a>
<a class="sourceLine" id="cb10-4" data-line-number="4"><span class="co"># min median max neval</span></a>
<a class="sourceLine" id="cb10-5" data-line-number="5"><span class="co"># 0.01817717 0.01843957 0.03878077 100</span></a></code></pre></div>
<div class="sourceCode" id="cb11"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb11-1" data-line-number="1">thousands_of_E_colis &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/rep">rep</a></span>(<span class="st">"E. coli"</span>, <span class="dv">25000</span>)</a>
<a class="sourceLine" id="cb11-2" data-line-number="2">microbenchmark<span class="op">::</span><span class="kw"><a href="https://www.rdocumentation.org/packages/microbenchmark/topics/microbenchmark">microbenchmark</a></span>(<span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(thousands_of_E_colis), <span class="dt">unit =</span> <span class="st">"s"</span>)</a>
<a class="sourceLine" id="cb11-3" data-line-number="3"><span class="co"># Unit: seconds</span></a>
<a class="sourceLine" id="cb11-4" data-line-number="4"><span class="co"># min median max neval</span></a>
<a class="sourceLine" id="cb11-5" data-line-number="5"><span class="co"># 0.01817717 0.01843957 0.03878077 100</span></a></code></pre></div>
</li>
<li>Added parameter <code>reference_df</code> for <code>as.mo</code>, so users can supply their own microbial IDs, name or codes as a reference table</li>
<li>Renamed all previous references to <code>bactid</code> to <code>mo</code>, like:
@ -548,12 +562,12 @@
<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="cb11"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb11-1" data-line-number="1"><span class="kw"><a href="../reference/ab_property.html">ab_official</a></span>(<span class="st">"Bactroban"</span>)</a>
<a class="sourceLine" id="cb11-2" data-line-number="2"><span class="co"># [1] "Mupirocin"</span></a>
<a class="sourceLine" id="cb11-3" data-line-number="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="cb11-4" data-line-number="4"><span class="co"># [1] "Mupirocin" "Amoxicillin" "Azithromycin" "Flucloxacillin"</span></a>
<a class="sourceLine" id="cb11-5" data-line-number="5"><span class="kw"><a href="../reference/ab_property.html">ab_atc</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="cb11-6" data-line-number="6"><span class="co"># [1] "R01AX06" "J01CA04" "J01FA10" "J01CF05"</span></a></code></pre></div>
<div class="sourceCode" id="cb12"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb12-1" data-line-number="1"><span class="kw"><a href="../reference/AMR-deprecated.html">ab_official</a></span>(<span class="st">"Bactroban"</span>)</a>
<a class="sourceLine" id="cb12-2" data-line-number="2"><span class="co"># [1] "Mupirocin"</span></a>
<a class="sourceLine" id="cb12-3" data-line-number="3"><span class="kw"><a href="../reference/AMR-deprecated.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="cb12-4" data-line-number="4"><span class="co"># [1] "Mupirocin" "Amoxicillin" "Azithromycin" "Flucloxacillin"</span></a>
<a class="sourceLine" id="cb12-5" data-line-number="5"><span class="kw"><a href="../reference/AMR-deprecated.html">ab_atc</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="cb12-6" data-line-number="6"><span class="co"># [1] "R01AX06" "J01CA04" "J01FA10" "J01CF05"</span></a></code></pre></div>
</li>
<li>For <code>first_isolate</code>, rows will be ignored when theres no species available</li>
<li>Function <code>ratio</code> is now deprecated and will be removed in a future release, as it is not really the scope of this package</li>
@ -564,13 +578,13 @@
</li>
<li>
<p>Support for quasiquotation in the functions series <code>count_*</code> and <code>portions_*</code>, and <code>n_rsi</code>. This allows to check for more than 2 vectors or columns.</p>
<div class="sourceCode" id="cb12"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb12-1" data-line-number="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw">select</span>(amox, cipr) <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>()</a>
<a class="sourceLine" id="cb12-2" data-line-number="2"><span class="co"># which is the same as:</span></a>
<a class="sourceLine" id="cb12-3" data-line-number="3">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>(amox, cipr)</a>
<a class="sourceLine" id="cb12-4" data-line-number="4"></a>
<a class="sourceLine" id="cb12-5" data-line-number="5">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl)</a>
<a class="sourceLine" id="cb12-6" data-line-number="6">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent)</a>
<a class="sourceLine" id="cb12-7" data-line-number="7">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent, pita)</a></code></pre></div>
<div class="sourceCode" id="cb13"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb13-1" data-line-number="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw">select</span>(amox, cipr) <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>()</a>
<a class="sourceLine" id="cb13-2" data-line-number="2"><span class="co"># which is the same as:</span></a>
<a class="sourceLine" id="cb13-3" data-line-number="3">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>(amox, cipr)</a>
<a class="sourceLine" id="cb13-4" data-line-number="4"></a>
<a class="sourceLine" id="cb13-5" data-line-number="5">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl)</a>
<a class="sourceLine" id="cb13-6" data-line-number="6">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent)</a>
<a class="sourceLine" id="cb13-7" data-line-number="7">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent, pita)</a></code></pre></div>
</li>
<li>Edited <code>ggplot_rsi</code> and <code>geom_rsi</code> so they can cope with <code>count_df</code>. The new <code>fun</code> parameter has value <code>portion_df</code> at default, but can be set to <code>count_df</code>.</li>
<li>Fix for <code>ggplot_rsi</code> when the <code>ggplot2</code> package was not loaded</li>
@ -584,12 +598,12 @@
</li>
<li>
<p>Support for types (classes) list and matrix for <code>freq</code></p>
<div class="sourceCode" id="cb13"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb13-1" data-line-number="1">my_matrix =<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/with">with</a></span>(septic_patients, <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/matrix">matrix</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(age, gender), <span class="dt">ncol =</span> <span class="dv">2</span>))</a>
<a class="sourceLine" id="cb13-2" data-line-number="2"><span class="kw"><a href="../reference/freq.html">freq</a></span>(my_matrix)</a></code></pre></div>
<div class="sourceCode" id="cb14"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb14-1" data-line-number="1">my_matrix =<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/with">with</a></span>(septic_patients, <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/matrix">matrix</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(age, gender), <span class="dt">ncol =</span> <span class="dv">2</span>))</a>
<a class="sourceLine" id="cb14-2" data-line-number="2"><span class="kw"><a href="../reference/freq.html">freq</a></span>(my_matrix)</a></code></pre></div>
<p>For lists, subsetting is possible:</p>
<div class="sourceCode" id="cb14"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb14-1" data-line-number="1">my_list =<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/list">list</a></span>(<span class="dt">age =</span> septic_patients<span class="op">$</span>age, <span class="dt">gender =</span> septic_patients<span class="op">$</span>gender)</a>
<a class="sourceLine" id="cb14-2" data-line-number="2">my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age)</a>
<a class="sourceLine" id="cb14-3" data-line-number="3">my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(gender)</a></code></pre></div>
<div class="sourceCode" id="cb15"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb15-1" data-line-number="1">my_list =<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/list">list</a></span>(<span class="dt">age =</span> septic_patients<span class="op">$</span>age, <span class="dt">gender =</span> septic_patients<span class="op">$</span>gender)</a>
<a class="sourceLine" id="cb15-2" data-line-number="2">my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age)</a>
<a class="sourceLine" id="cb15-3" data-line-number="3">my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(gender)</a></code></pre></div>
</li>
</ul>
</div>

View File

@ -47,7 +47,7 @@
<script src="../extra.js"></script>
<meta property="og:title" content="Deprecated functions — AMR-deprecated" />
<meta property="og:description" content="These functions are 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." />
<meta property="og:description" content="These functions are so-called '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)." />
<meta property="og:image" content="https://msberends.gitlab.io/AMR/logo.png" />
<meta name="twitter:card" content="summary" />
@ -223,13 +223,29 @@
<div class="ref-description">
<p>These functions are <a href='https://www.rdocumentation.org/packages/base/topics/Deprecated'>Deprecated</a>. 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.</p>
<p>These functions are so-called '<a href='https://www.rdocumentation.org/packages/base/topics/Deprecated'>Deprecated</a>'. 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).</p>
</div>
<pre class="usage"><span class='fu'>ratio</span>(<span class='no'>x</span>, <span class='no'>ratio</span>)
<span class='fu'>guess_mo</span>(<span class='no'>...</span>)</pre>
<span class='fu'>guess_mo</span>(<span class='no'>...</span>)
<span class='fu'>ab_property</span>(<span class='no'>...</span>)
<span class='fu'>ab_atc</span>(<span class='no'>...</span>)
<span class='fu'>ab_official</span>(<span class='no'>...</span>)
<span class='fu'>ab_name</span>(<span class='no'>...</span>)
<span class='fu'>ab_trivial_nl</span>(<span class='no'>...</span>)
<span class='fu'>ab_certe</span>(<span class='no'>...</span>)
<span class='fu'>ab_umcg</span>(<span class='no'>...</span>)
<span class='fu'>ab_tradenames</span>(<span class='no'>...</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

@ -231,7 +231,7 @@
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p>This package was intended to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial properties by using evidence-based methods.</p>
<p>This package was created for academic research by PhD students of the Faculty of Medical Sciences of the University of Groningen and the Medical Microbiology &amp; Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG).</p>
<p>This package was created for both academic research and routine analysis by PhD students of the Faculty of Medical Sciences of the University of Groningen and the Medical Microbiology &amp; Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG).</p>
<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

@ -246,9 +246,9 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2>
<pre class="examples"><span class='co'># NOT RUN {</span>
<span class='fu'><a href='as.atc.html'>as.atc</a></span>(<span class='st'>"meropenem"</span>)
<span class='fu'><a href='ab_property.html'>ab_name</a></span>(<span class='st'>"J01DH02"</span>)
<span class='fu'><a href='AMR-deprecated.html'>ab_name</a></span>(<span class='st'>"J01DH02"</span>)
<span class='fu'><a href='ab_property.html'>ab_tradenames</a></span>(<span class='st'>"flucloxacillin"</span>)
<span class='fu'><a href='AMR-deprecated.html'>ab_tradenames</a></span>(<span class='st'>"flucloxacillin"</span>)
<span class='co'># }</span></pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="sidebar">

View File

@ -257,7 +257,7 @@
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p><strong>The <code><a href='ab_property.html'>ab_property</a></code> functions are faster and more concise</strong>, but do not support concatenated strings, like <code>abname("AMCL+GENT"</code>.</p>
<p><strong>The <code><a href='AMR-deprecated.html'>ab_property</a></code> functions are faster and more concise</strong>, but do not support concatenated strings, like <code>abname("AMCL+GENT"</code>.</p>
<h2 class="hasAnchor" id="whocc"><a class="anchor" href="#whocc"></a>WHOCC</h2>

View File

@ -296,11 +296,11 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='co'># resistance of ciprofloxacine per age group</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/library'>library</a></span>(<span class='no'>dplyr</span>)
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/mutate'>mutate</a></span>(<span class='kw'>first_isolate</span> <span class='kw'>=</span> <span class='fu'><a href='first_isolate.html'>first_isolate</a></span>(<span class='no'>.</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/filter'>filter</a></span>(<span class='no'>first_isolate</span> <span class='kw'>==</span> <span class='fl'>TRUE</span>,
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(<span class='kw'>first_isolate</span> <span class='kw'>=</span> <span class='fu'><a href='first_isolate.html'>first_isolate</a></span>(<span class='no'>.</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span>(<span class='no'>first_isolate</span> <span class='kw'>==</span> <span class='fl'>TRUE</span>,
<span class='no'>mo</span> <span class='kw'>==</span> <span class='fu'><a href='as.mo.html'>as.mo</a></span>(<span class='st'>"E. coli"</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/group_by'>group_by</a></span>(<span class='kw'>age_group</span> <span class='kw'>=</span> <span class='fu'>age_groups</span>(<span class='no'>age</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>age_group</span>,
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/group_by.html'>group_by</a></span>(<span class='kw'>age_group</span> <span class='kw'>=</span> <span class='fu'>age_groups</span>(<span class='no'>age</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>age_group</span>,
<span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='ggplot_rsi.html'>ggplot_rsi</a></span>(<span class='kw'>x</span> <span class='kw'>=</span> <span class='st'>"age_group"</span>)
<span class='co'># }</span></pre>

View File

@ -248,7 +248,7 @@
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p>Use the <code><a href='ab_property.html'>ab_property</a></code> functions to get properties based on the returned ATC code, see Examples.</p>
<p>Use the <code><a href='AMR-deprecated.html'>ab_property</a></code> functions to get properties based on the returned ATC code, see Examples.</p>
<p>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: <a href='https://www.whocc.no/atc/structure_and_principles/'>https://www.whocc.no/atc/structure_and_principles/</a></p>
@ -286,8 +286,8 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='co'># Use ab_* functions to get a specific property based on an ATC code</span>
<span class='no'>Cipro</span> <span class='kw'>&lt;-</span> <span class='fu'>as.atc</span>(<span class='st'>"cipro"</span>) <span class='co'># returns `J01MA02`</span>
<span class='fu'><a href='ab_property.html'>ab_official</a></span>(<span class='no'>Cipro</span>) <span class='co'># returns "Ciprofloxacin"</span>
<span class='fu'><a href='ab_property.html'>ab_umcg</a></span>(<span class='no'>Cipro</span>) <span class='co'># returns "CIPR", the code used in the UMCG</span>
<span class='fu'><a href='AMR-deprecated.html'>ab_official</a></span>(<span class='no'>Cipro</span>) <span class='co'># returns "Ciprofloxacin"</span>
<span class='fu'><a href='AMR-deprecated.html'>ab_umcg</a></span>(<span class='no'>Cipro</span>) <span class='co'># returns "CIPR", the code used in the UMCG</span>
<span class='co'># }</span></pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="sidebar">

View File

@ -277,11 +277,11 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='co'># using dplyr's mutate</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/library'>library</a></span>(<span class='no'>dplyr</span>)
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/summarise_all'>mutate_at</a></span>(<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/vars'>vars</a></span>(<span class='no'>peni</span>:<span class='no'>rifa</span>), <span class='no'>as.rsi</span>)
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise_all.html'>mutate_at</a></span>(<span class='fu'><a href='https://dplyr.tidyverse.org/reference/vars.html'>vars</a></span>(<span class='no'>peni</span>:<span class='no'>rifa</span>), <span class='no'>as.rsi</span>)
<span class='co'># fastest way to transform all columns with already valid AB results to class `rsi`:</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/summarise_all'>mutate_if</a></span>(<span class='no'>is.rsi.eligible</span>,
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise_all.html'>mutate_if</a></span>(<span class='no'>is.rsi.eligible</span>,
<span class='no'>as.rsi</span>)
<span class='co'># }</span></pre>
</div>

View File

@ -0,0 +1,353 @@
<!-- Generated by pkgdown: do not edit by hand -->
<!DOCTYPE html>
<html lang="en">
<head>
<meta charset="utf-8">
<meta http-equiv="X-UA-Compatible" content="IE=edge">
<meta name="viewport" content="width=device-width, initial-scale=1.0">
<title>Properties of an ATC code — atc_online_property • AMR (for R)</title>
<!-- favicons -->
<link rel="icon" type="image/png" sizes="16x16" href="../favicon-16x16.png">
<link rel="icon" type="image/png" sizes="32x32" href="../favicon-32x32.png">
<link rel="apple-touch-icon" type="image/png" sizes="180x180" href="../apple-touch-icon.png" />
<link rel="apple-touch-icon" type="image/png" sizes="120x120" href="../apple-touch-icon-120x120.png" />
<link rel="apple-touch-icon" type="image/png" sizes="76x76" href="../apple-touch-icon-76x76.png" />
<link rel="apple-touch-icon" type="image/png" sizes="60x60" href="../apple-touch-icon-60x60.png" />
<!-- jquery -->
<script src="https://cdnjs.cloudflare.com/ajax/libs/jquery/3.3.1/jquery.min.js" integrity="sha256-FgpCb/KJQlLNfOu91ta32o/NMZxltwRo8QtmkMRdAu8=" crossorigin="anonymous"></script>
<!-- Bootstrap -->
<link href="https://cdnjs.cloudflare.com/ajax/libs/bootswatch/3.3.7/flatly/bootstrap.min.css" rel="stylesheet" crossorigin="anonymous" />
<script src="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.3.7/js/bootstrap.min.js" integrity="sha256-U5ZEeKfGNOja007MMD3YBI0A3OSZOQbeG6z2f2Y0hu8=" crossorigin="anonymous"></script>
<!-- Font Awesome icons -->
<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/4.7.0/css/font-awesome.min.css" integrity="sha256-eZrrJcwDc/3uDhsdt61sL2oOBY362qM3lon1gyExkL0=" crossorigin="anonymous" />
<!-- clipboard.js -->
<script src="https://cdnjs.cloudflare.com/ajax/libs/clipboard.js/2.0.4/clipboard.min.js" integrity="sha256-FiZwavyI2V6+EXO1U+xzLG3IKldpiTFf3153ea9zikQ=" crossorigin="anonymous"></script>
<!-- sticky kit -->
<script src="https://cdnjs.cloudflare.com/ajax/libs/sticky-kit/1.1.3/sticky-kit.min.js" integrity="sha256-c4Rlo1ZozqTPE2RLuvbusY3+SU1pQaJC0TjuhygMipw=" crossorigin="anonymous"></script>
<!-- pkgdown -->
<link href="../pkgdown.css" rel="stylesheet">
<script src="../pkgdown.js"></script>
<!-- docsearch -->
<script src="../docsearch.js"></script>
<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/docsearch.js/2.6.1/docsearch.min.css" integrity="sha256-QOSRU/ra9ActyXkIBbiIB144aDBdtvXBcNc3OTNuX/Q=" crossorigin="anonymous" />
<link href="../docsearch.css" rel="stylesheet">
<script src="https://cdnjs.cloudflare.com/ajax/libs/mark.js/8.11.1/jquery.mark.min.js" integrity="sha256-4HLtjeVgH0eIB3aZ9mLYF6E8oU5chNdjU6p6rrXpl9U=" crossorigin="anonymous"></script>
<link href="../extra.css" rel="stylesheet">
<script src="../extra.js"></script>
<meta property="og:title" content="Properties of an ATC code — atc_online_property" />
<meta property="og:description" content="Gets data from the WHO to determine properties of an ATC (e.g. an antibiotic) like name, defined daily dose (DDD) or standard unit. This function requires an internet connection." />
<meta property="og:image" content="https://msberends.gitlab.io/AMR/logo.png" />
<meta name="twitter:card" content="summary" />
<!-- mathjax -->
<script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script>
<script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script>
<!--[if lt IE 9]>
<script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script>
<script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script>
<![endif]-->
</head>
<body>
<div class="container template-reference-topic">
<header>
<div class="navbar navbar-default navbar-fixed-top" role="navigation">
<div class="container">
<div class="navbar-header">
<button type="button" class="navbar-toggle collapsed" data-toggle="collapse" data-target="#navbar" aria-expanded="false">
<span class="sr-only">Toggle navigation</span>
<span class="icon-bar"></span>
<span class="icon-bar"></span>
<span class="icon-bar"></span>
</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="Released version">0.5.0.9012</span>
</span>
</div>
<div id="navbar" class="navbar-collapse collapse">
<ul class="nav navbar-nav">
<li>
<a href="../index.html">
<span class="fa fa-home"></span>
Home
</a>
</li>
<li class="dropdown">
<a href="#" class="dropdown-toggle" data-toggle="dropdown" role="button" aria-expanded="false">
<span class="fa fa-question-circle"></span>
How to
<span class="caret"></span>
</a>
<ul class="dropdown-menu" role="menu">
<li>
<a href="../articles/AMR.html">
<span class="fa fa-directions"></span>
Conduct AMR analysis
</a>
</li>
<li>
<a href="../articles/Predict.html">
<span class="fa fa-dice"></span>
Predict antimicrobial resistance
</a>
</li>
<li>
<a href="../articles/EUCAST.html">
<span class="fa fa-exchange-alt"></span>
Apply EUCAST rules
</a>
</li>
<li>
<a href="../articles/mo_property.html">
<span class="fa fa-bug"></span>
Get properties of a microorganism
</a>
</li>
<li>
<a href="../articles/ab_property.html">
<span class="fa fa-capsules"></span>
Get properties of an antibiotic
</a>
</li>
<li>
<a href="../articles/freq.html">
<span class="fa fa-sort-amount-down"></span>
Create frequency tables
</a>
</li>
<li>
<a href="../articles/G_test.html">
<span class="fa fa-clipboard-check"></span>
Use the G-test
</a>
</li>
<li>
<a href="../articles/benchmarks.html">
<span class="fa fa-shipping-fast"></span>
Other: benchmarks
</a>
</li>
</ul>
</li>
<li>
<a href="../reference/">
<span class="fa fa-book-open"></span>
Manual
</a>
</li>
<li>
<a href="../authors.html">
<span class="fa fa-users"></span>
Authors
</a>
</li>
<li>
<a href="../news/">
<span class="far fa far fa-newspaper"></span>
Changelog
</a>
</li>
</ul>
<ul class="nav navbar-nav navbar-right">
<li>
<a href="https://gitlab.com/msberends/AMR">
<span class="fab fa fab fa-gitlab"></span>
Source Code
</a>
</li>
<li>
<a href="../LICENSE-text.html">
<span class="fa fa-book"></span>
Licence
</a>
</li>
</ul>
<form class="navbar-form navbar-right" role="search">
<div class="form-group">
<input type="search" class="form-control" name="search-input" id="search-input" placeholder="Search..." aria-label="Search for..." autocomplete="off">
</div>
</form>
</div><!--/.nav-collapse -->
</div><!--/.container -->
</div><!--/.navbar -->
</header>
<div class="row">
<div class="col-md-9 contents">
<div class="page-header">
<h1>Properties of an ATC code</h1>
<div class="hidden name"><code>atc_online.Rd</code></div>
</div>
<div class="ref-description">
<p>Gets data from the WHO to determine properties of an ATC (e.g. an antibiotic) like name, defined daily dose (DDD) or standard unit. <br /> <strong>This function requires an internet connection.</strong></p>
</div>
<pre class="usage"><span class='fu'>atc_online_property</span>(<span class='no'>atc_code</span>, <span class='no'>property</span>, <span class='kw'>administration</span> <span class='kw'>=</span> <span class='st'>"O"</span>,
<span class='kw'>url</span> <span class='kw'>=</span> <span class='st'>"https://www.whocc.no/atc_ddd_index/?code=%s&amp;showdescription=no"</span>)
<span class='fu'>atc_online_groups</span>(<span class='no'>atc_code</span>, <span class='no'>...</span>)
<span class='fu'>atc_online_ddd</span>(<span class='no'>atc_code</span>, <span class='no'>...</span>)</pre>
<h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2>
<table class="ref-arguments">
<colgroup><col class="name" /><col class="desc" /></colgroup>
<tr>
<th>atc_code</th>
<td><p>a character or character vector with ATC code(s) of antibiotic(s)</p></td>
</tr>
<tr>
<th>property</th>
<td><p>property of an ATC code. Valid values are <code>"ATC"</code>, <code>"Name"</code>, <code>"DDD"</code>, <code>"U"</code> (<code>"unit"</code>), <code>"Adm.R"</code>, <code>"Note"</code> and <code>groups</code>. For this last option, all hierarchical groups of an ATC code will be returned, see Examples.</p></td>
</tr>
<tr>
<th>administration</th>
<td><p>type of administration when using <code>property = "Adm.R"</code>, see Details</p></td>
</tr>
<tr>
<th>url</th>
<td><p>url of website of the WHO. The sign <code>%s</code> can be used as a placeholder for ATC codes.</p></td>
</tr>
<tr>
<th>...</th>
<td><p>parameters to pass on to <code>atc_property</code></p></td>
</tr>
</table>
<h2 class="hasAnchor" id="source"><a class="anchor" href="#source"></a>Source</h2>
<p><a href='https://www.whocc.no/atc_ddd_alterations__cumulative/ddd_alterations/abbrevations/'>https://www.whocc.no/atc_ddd_alterations__cumulative/ddd_alterations/abbrevations/</a></p>
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p>Options for parameter <code>administration</code>:</p><ul>
<li><p><code>"Implant"</code> = Implant</p></li>
<li><p><code>"Inhal"</code> = Inhalation</p></li>
<li><p><code>"Instill"</code> = Instillation</p></li>
<li><p><code>"N"</code> = nasal</p></li>
<li><p><code>"O"</code> = oral</p></li>
<li><p><code>"P"</code> = parenteral</p></li>
<li><p><code>"R"</code> = rectal</p></li>
<li><p><code>"SL"</code> = sublingual/buccal</p></li>
<li><p><code>"TD"</code> = transdermal</p></li>
<li><p><code>"V"</code> = vaginal</p></li>
</ul>
<p>Abbreviations of return values when using <code>property = "U"</code> (unit):</p><ul>
<li><p><code>"g"</code> = gram</p></li>
<li><p><code>"mg"</code> = milligram</p></li>
<li><p><code>"mcg"</code> = microgram</p></li>
<li><p><code>"U"</code> = unit</p></li>
<li><p><code>"TU"</code> = thousand units</p></li>
<li><p><code>"MU"</code> = million units</p></li>
<li><p><code>"mmol"</code> = millimole</p></li>
<li><p><code>"ml"</code> = milliliter (e.g. eyedrops)</p></li>
</ul>
<h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2>
<pre class="examples"><span class='co'># NOT RUN {</span>
<span class='co'># oral DDD (Defined Daily Dose) of amoxicillin</span>
<span class='fu'>atc_online_property</span>(<span class='st'>"J01CA04"</span>, <span class='st'>"DDD"</span>, <span class='st'>"O"</span>)
<span class='co'># parenteral DDD (Defined Daily Dose) of amoxicillin</span>
<span class='fu'>atc_online_property</span>(<span class='st'>"J01CA04"</span>, <span class='st'>"DDD"</span>, <span class='st'>"P"</span>)
<span class='fu'>atc_online_property</span>(<span class='st'>"J01CA04"</span>, <span class='kw'>property</span> <span class='kw'>=</span> <span class='st'>"groups"</span>) <span class='co'># search hierarchical groups of amoxicillin</span>
<span class='co'># [1] "ANTIINFECTIVES FOR SYSTEMIC USE"</span>
<span class='co'># [2] "ANTIBACTERIALS FOR SYSTEMIC USE"</span>
<span class='co'># [3] "BETA-LACTAM ANTIBACTERIALS, PENICILLINS"</span>
<span class='co'># [4] "Penicillins with extended spectrum"</span>
<span class='co'># }</span></pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="sidebar">
<h2>Contents</h2>
<ul class="nav nav-pills nav-stacked">
<li><a href="#arguments">Arguments</a></li>
<li><a href="#source">Source</a></li>
<li><a href="#details">Details</a></li>
<li><a href="#examples">Examples</a></li>
</ul>
</div>
</div>
<footer>
<div class="copyright">
<p>Developed by <a href='https://www.rug.nl/staff/m.s.berends/'>Matthijs S. Berends</a>, <a href='https://www.rug.nl/staff/c.f.luz/'>Christian F. Luz</a>, <a href='https://www.rug.nl/staff/c.glasner/'>Corinna Glasner</a>, <a href='https://www.rug.nl/staff/a.w.friedrich/'>Alex W. Friedrich</a>, <a href='https://www.rug.nl/staff/b.sinha/'>Bhanu N. M. Sinha</a>.</p>
</div>
<div class="pkgdown">
<p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.3.0.</p>
</div>
</footer>
</div>
<script src="https://cdnjs.cloudflare.com/ajax/libs/docsearch.js/2.6.1/docsearch.min.js" integrity="sha256-GKvGqXDznoRYHCwKXGnuchvKSwmx9SRMrZOTh2g4Sb0=" crossorigin="anonymous"></script>
<script>
docsearch({
apiKey: 'f737050abfd4d726c63938e18f8c496e',
indexName: 'amr',
inputSelector: 'input#search-input.form-control',
transformData: function(hits) {
return hits.map(function (hit) {
hit.url = updateHitURL(hit);
return hit;
});
}
});
</script>
</body>
</html>

View File

@ -6,7 +6,7 @@
<meta http-equiv="X-UA-Compatible" content="IE=edge">
<meta name="viewport" content="width=device-width, initial-scale=1.0">
<title>Properties of an ATC code — atc_property • AMR (for R)</title>
<title>Property of an antibiotic — atc_property • AMR (for R)</title>
<!-- favicons -->
<link rel="icon" type="image/png" sizes="16x16" href="../favicon-16x16.png">
@ -45,9 +45,9 @@
<link href="../extra.css" rel="stylesheet">
<script src="../extra.js"></script>
<meta property="og:title" content="Properties of an ATC code — atc_property" />
<meta property="og:title" content="Property of an antibiotic — atc_property" />
<meta property="og:description" content="Gets data from the WHO to determine properties of an ATC (e.g. an antibiotic) like name, defined daily dose (DDD) or standard unit. This function requires an internet connection." />
<meta property="og:description" content="Use these functions to return a specific property of an antibiotic from the antibiotics data set, based on their ATC code. Get such a code with as.atc." />
<meta property="og:image" content="https://msberends.gitlab.io/AMR/logo.png" />
<meta name="twitter:card" content="summary" />
@ -216,95 +216,71 @@
<div class="row">
<div class="col-md-9 contents">
<div class="page-header">
<h1>Properties of an ATC code</h1>
<h1>Property of an antibiotic</h1>
<div class="hidden name"><code>atc_property.Rd</code></div>
</div>
<div class="ref-description">
<p>Gets data from the WHO to determine properties of an ATC (e.g. an antibiotic) like name, defined daily dose (DDD) or standard unit. <br /> <strong>This function requires an internet connection.</strong></p>
<p>Use these functions to return a specific property of an antibiotic from the <code><a href='antibiotics.html'>antibiotics</a></code> data set, based on their ATC code. Get such a code with <code><a href='as.atc.html'>as.atc</a></code>.</p>
</div>
<pre class="usage"><span class='fu'>atc_property</span>(<span class='no'>atc_code</span>, <span class='no'>property</span>, <span class='kw'>administration</span> <span class='kw'>=</span> <span class='st'>"O"</span>,
<span class='kw'>url</span> <span class='kw'>=</span> <span class='st'>"https://www.whocc.no/atc_ddd_index/?code=%s&amp;showdescription=no"</span>)
<pre class="usage"><span class='fu'>atc_property</span>(<span class='no'>x</span>, <span class='kw'>property</span> <span class='kw'>=</span> <span class='st'>"official"</span>)
<span class='fu'>atc_groups</span>(<span class='no'>atc_code</span>, <span class='no'>...</span>)
<span class='fu'>atc_official</span>(<span class='no'>x</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='kw'>NULL</span>)
<span class='fu'>atc_ddd</span>(<span class='no'>atc_code</span>, <span class='no'>...</span>)</pre>
<span class='fu'>atc_name</span>(<span class='no'>x</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='kw'>NULL</span>)
<span class='fu'>atc_trivial_nl</span>(<span class='no'>x</span>)
<span class='fu'>atc_certe</span>(<span class='no'>x</span>)
<span class='fu'>atc_umcg</span>(<span class='no'>x</span>)
<span class='fu'>atc_tradenames</span>(<span class='no'>x</span>)</pre>
<h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2>
<table class="ref-arguments">
<colgroup><col class="name" /><col class="desc" /></colgroup>
<tr>
<th>atc_code</th>
<td><p>a character or character vector with ATC code(s) of antibiotic(s)</p></td>
<th>x</th>
<td><p>a (vector of a) valid <code><a href='as.atc.html'>atc</a></code> code or any text that can be coerced to a valid atc with <code><a href='as.atc.html'>as.atc</a></code></p></td>
</tr>
<tr>
<th>property</th>
<td><p>property of an ATC code. Valid values are <code>"ATC"</code>, <code>"Name"</code>, <code>"DDD"</code>, <code>"U"</code> (<code>"unit"</code>), <code>"Adm.R"</code>, <code>"Note"</code> and <code>groups</code>. For this last option, all hierarchical groups of an ATC code will be returned, see Examples.</p></td>
<td><p>one of the column names of one of the <code><a href='antibiotics.html'>antibiotics</a></code> data set, like <code>"atc"</code> and <code>"official"</code></p></td>
</tr>
<tr>
<th>administration</th>
<td><p>type of administration when using <code>property = "Adm.R"</code>, see Details</p></td>
</tr>
<tr>
<th>url</th>
<td><p>url of website of the WHO. The sign <code>%s</code> can be used as a placeholder for ATC codes.</p></td>
</tr>
<tr>
<th>...</th>
<td><p>parameters to pass on to <code>atc_property</code></p></td>
<th>language</th>
<td><p>language of the returned text, defaults to English (<code>"en"</code>) and can be set with <code><a href='https://www.rdocumentation.org/packages/base/topics/options'>getOption</a>("AMR_locale")</code>. Either one of <code>"en"</code> (English) or <code>"nl"</code> (Dutch).</p></td>
</tr>
</table>
<h2 class="hasAnchor" id="source"><a class="anchor" href="#source"></a>Source</h2>
<h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2>
<p><a href='https://www.whocc.no/atc_ddd_alterations__cumulative/ddd_alterations/abbrevations/'>https://www.whocc.no/atc_ddd_alterations__cumulative/ddd_alterations/abbrevations/</a></p>
<p>A vector of values. In case of <code>atc_tradenames</code>, if <code>x</code> is of length one, a vector will be returned. Otherwise a <code><a href='https://www.rdocumentation.org/packages/base/topics/list'>list</a></code>, with <code>x</code> as names.</p>
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<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>
<p>Options for parameter <code>administration</code>:</p><ul>
<li><p><code>"Implant"</code> = Implant</p></li>
<li><p><code>"Inhal"</code> = Inhalation</p></li>
<li><p><code>"Instill"</code> = Instillation</p></li>
<li><p><code>"N"</code> = nasal</p></li>
<li><p><code>"O"</code> = oral</p></li>
<li><p><code>"P"</code> = parenteral</p></li>
<li><p><code>"R"</code> = rectal</p></li>
<li><p><code>"SL"</code> = sublingual/buccal</p></li>
<li><p><code>"TD"</code> = transdermal</p></li>
<li><p><code>"V"</code> = vaginal</p></li>
</ul>
<p>Abbreviations of return values when using <code>property = "U"</code> (unit):</p><ul>
<li><p><code>"g"</code> = gram</p></li>
<li><p><code>"mg"</code> = milligram</p></li>
<li><p><code>"mcg"</code> = microgram</p></li>
<li><p><code>"U"</code> = unit</p></li>
<li><p><code>"TU"</code> = thousand units</p></li>
<li><p><code>"MU"</code> = million units</p></li>
<li><p><code>"mmol"</code> = millimole</p></li>
<li><p><code>"ml"</code> = milliliter (e.g. eyedrops)</p></li>
</ul>
<p><img src='figures/logo.png' height=40px style=margin-bottom:5px /> <br />
On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitlab.io/AMR</a> you can find <a href='https://msberends.gitlab.io/AMR/articles/AMR.html'>a omprehensive tutorial</a> about how to conduct AMR analysis and find <a href='https://msberends.gitlab.io/AMR/reference'>the complete documentation of all functions</a>, which reads a lot easier than in R.</p>
<h2 class="hasAnchor" id="see-also"><a class="anchor" href="#see-also"></a>See also</h2>
<div class='dont-index'><p><code><a href='antibiotics.html'>antibiotics</a></code></p></div>
<h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2>
<pre class="examples"><span class='co'># NOT RUN {</span>
<span class='co'># What's the ATC of amoxicillin?</span>
<span class='fu'><a href='as.atc.html'>guess_atc</a></span>(<span class='st'>"Amoxicillin"</span>)
<span class='co'># [1] "J01CA04"</span>
<span class='co'># oral DDD (Defined Daily Dose) of amoxicillin</span>
<span class='fu'>atc_property</span>(<span class='st'>"J01CA04"</span>, <span class='st'>"DDD"</span>, <span class='st'>"O"</span>)
<span class='co'># parenteral DDD (Defined Daily Dose) of amoxicillin</span>
<span class='fu'>atc_property</span>(<span class='st'>"J01CA04"</span>, <span class='st'>"DDD"</span>, <span class='st'>"P"</span>)
<span class='fu'>atc_property</span>(<span class='st'>"J01CA04"</span>, <span class='kw'>property</span> <span class='kw'>=</span> <span class='st'>"groups"</span>) <span class='co'># search hierarchical groups of amoxicillin</span>
<span class='co'># [1] "ANTIINFECTIVES FOR SYSTEMIC USE"</span>
<span class='co'># [2] "ANTIBACTERIALS FOR SYSTEMIC USE"</span>
<span class='co'># [3] "BETA-LACTAM ANTIBACTERIALS, PENICILLINS"</span>
<span class='co'># [4] "Penicillins with extended spectrum"</span>
<span class='fu'><a href='as.atc.html'>as.atc</a></span>(<span class='st'>"amcl"</span>) <span class='co'># J01CR02</span>
<span class='fu'>atc_name</span>(<span class='st'>"amcl"</span>) <span class='co'># Amoxicillin and beta-lactamase inhibitor</span>
<span class='fu'>atc_name</span>(<span class='st'>"amcl"</span>, <span class='st'>"nl"</span>) <span class='co'># Amoxicilline met enzymremmer</span>
<span class='fu'>atc_trivial_nl</span>(<span class='st'>"amcl"</span>) <span class='co'># Amoxicilline/clavulaanzuur</span>
<span class='fu'>atc_certe</span>(<span class='st'>"amcl"</span>) <span class='co'># amcl</span>
<span class='fu'>atc_umcg</span>(<span class='st'>"amcl"</span>) <span class='co'># AMCL</span>
<span class='co'># }</span></pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="sidebar">
@ -312,9 +288,11 @@
<ul class="nav nav-pills nav-stacked">
<li><a href="#arguments">Arguments</a></li>
<li><a href="#source">Source</a></li>
<li><a href="#value">Value</a></li>
<li><a href="#details">Details</a></li>
<li><a href="#read-more-on-our-website-">Read more on our website!</a></li>
<li><a href="#see-also">See also</a></li>
<li><a href="#examples">Examples</a></li>
</ul>

View File

@ -282,7 +282,7 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p>These functions are meant to count isolates. Use the <code><a href='portion.html'>portion</a>_*</code> functions to calculate microbial resistance.</p>
<p><code>n_rsi</code> is an alias of <code>count_all</code>. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to <code><a href='https://www.rdocumentation.org/packages/dplyr/topics/n_distinct'>n_distinct</a></code>. Their function is equal to <code>count_S(...) + count_IR(...)</code>.</p>
<p><code>n_rsi</code> is an alias of <code>count_all</code>. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to <code><a href='https://dplyr.tidyverse.org/reference/n_distinct.html'>n_distinct</a></code>. Their function is equal to <code>count_S(...) + count_IR(...)</code>.</p>
<p><code>count_df</code> takes any variable from <code>data</code> that has an <code>"rsi"</code> class (created with <code><a href='as.rsi.html'>as.rsi</a></code>) and counts the amounts of R, I and S. The resulting <em>tidy data</em> (see Source) <code>data.frame</code> will have three rows (S/I/R) and a column for each variable with class <code>"rsi"</code>.</p>
<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>
@ -321,13 +321,13 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/library'>library</a></span>(<span class='no'>dplyr</span>)
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/group_by'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/summarise'>summarise</a></span>(<span class='kw'>R</span> <span class='kw'>=</span> <span class='fu'>count_R</span>(<span class='no'>cipr</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>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>R</span> <span class='kw'>=</span> <span class='fu'>count_R</span>(<span class='no'>cipr</span>),
<span class='kw'>I</span> <span class='kw'>=</span> <span class='fu'>count_I</span>(<span class='no'>cipr</span>),
<span class='kw'>S</span> <span class='kw'>=</span> <span class='fu'>count_S</span>(<span class='no'>cipr</span>),
<span class='kw'>n1</span> <span class='kw'>=</span> <span class='fu'>count_all</span>(<span class='no'>cipr</span>), <span class='co'># the actual total; sum of all three</span>
<span class='kw'>n2</span> <span class='kw'>=</span> <span class='fu'>n_rsi</span>(<span class='no'>cipr</span>), <span class='co'># same - analogous to n_distinct</span>
<span class='kw'>total</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/n'>n</a></span>()) <span class='co'># NOT the amount of tested isolates!</span>
<span class='kw'>total</span> <span class='kw'>=</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/n.html'>n</a></span>()) <span class='co'># NOT the amount of tested isolates!</span>
<span class='co'># Count co-resistance between amoxicillin/clav acid and gentamicin,</span>
<span class='co'># so we can see that combination therapy does a lot more than mono therapy.</span>
@ -345,13 +345,13 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='co'># Get portions S/I/R immediately of all rsi columns</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>amox</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>amox</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>count_df</span>(<span class='kw'>translate</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='co'># It also supports grouping variables</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>hospital_id</span>, <span class='no'>amox</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/group_by'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>hospital_id</span>, <span class='no'>amox</span>, <span class='no'>cipr</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>
<span class='fu'>count_df</span>(<span class='kw'>translate</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='co'># }</span></pre>

View File

@ -368,11 +368,11 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/library'>library</a></span>(<span class='no'>dplyr</span>)
<span class='co'># Filter on first isolates:</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/mutate'>mutate</a></span>(<span class='kw'>first_isolate</span> <span class='kw'>=</span> <span class='fu'>first_isolate</span>(<span class='no'>.</span>,
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(<span class='kw'>first_isolate</span> <span class='kw'>=</span> <span class='fu'>first_isolate</span>(<span class='no'>.</span>,
<span class='kw'>col_date</span> <span class='kw'>=</span> <span class='st'>"date"</span>,
<span class='kw'>col_patient_id</span> <span class='kw'>=</span> <span class='st'>"patient_id"</span>,
<span class='kw'>col_mo</span> <span class='kw'>=</span> <span class='st'>"mo"</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/filter'>filter</a></span>(<span class='no'>first_isolate</span> <span class='kw'>==</span> <span class='fl'>TRUE</span>)
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span>(<span class='no'>first_isolate</span> <span class='kw'>==</span> <span class='fl'>TRUE</span>)
<span class='co'># Which can be shortened to:</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
@ -383,14 +383,14 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='co'># Now let's see if first isolates matter:</span>
<span class='no'>A</span> <span class='kw'>&lt;-</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/group_by'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/summarise'>summarise</a></span>(<span class='kw'>count</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>n_rsi</a></span>(<span class='no'>gent</span>), <span class='co'># gentamicin availability</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>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>count</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>n_rsi</a></span>(<span class='no'>gent</span>), <span class='co'># gentamicin availability</span>
<span class='kw'>resistance</span> <span class='kw'>=</span> <span class='fu'><a href='portion.html'>portion_IR</a></span>(<span class='no'>gent</span>)) <span class='co'># gentamicin resistance</span>
<span class='no'>B</span> <span class='kw'>&lt;-</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'>filter_first_weighted_isolate</span>() <span class='kw'>%&gt;%</span> <span class='co'># the 1st isolate filter</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/group_by'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/summarise'>summarise</a></span>(<span class='kw'>count</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>n_rsi</a></span>(<span class='no'>gent</span>), <span class='co'># gentamicin availability</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>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>count</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>n_rsi</a></span>(<span class='no'>gent</span>), <span class='co'># gentamicin availability</span>
<span class='kw'>resistance</span> <span class='kw'>=</span> <span class='fu'><a href='portion.html'>portion_IR</a></span>(<span class='no'>gent</span>)) <span class='co'># gentamicin resistance</span>
<span class='co'># Have a look at A and B.</span>

View File

@ -385,34 +385,34 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='co'># you could also use `select` or `pull` to get your variables</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/filter'>filter</a></span>(<span class='no'>hospital_id</span> <span class='kw'>==</span> <span class='st'>"A"</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>mo</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span>(<span class='no'>hospital_id</span> <span class='kw'>==</span> <span class='st'>"A"</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>mo</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>freq</span>()
<span class='co'># multiple selected variables will be pasted together</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='no'>left_join_microorganisms</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/filter'>filter</a></span>(<span class='no'>hospital_id</span> <span class='kw'>==</span> <span class='st'>"A"</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span>(<span class='no'>hospital_id</span> <span class='kw'>==</span> <span class='st'>"A"</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>freq</span>(<span class='no'>genus</span>, <span class='no'>species</span>)
<span class='co'># group a variable and analyse another</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/group_by'>group_by</a></span>(<span class='no'>hospital_id</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>
<span class='fu'>freq</span>(<span class='no'>gender</span>)
<span class='co'># get top 10 bugs of hospital A as a vector</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/filter'>filter</a></span>(<span class='no'>hospital_id</span> <span class='kw'>==</span> <span class='st'>"A"</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span>(<span class='no'>hospital_id</span> <span class='kw'>==</span> <span class='st'>"A"</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>freq</span>(<span class='no'>mo</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>top_freq</span>(<span class='fl'>10</span>)
<span class='co'># save frequency table to an object</span>
<span class='no'>years</span> <span class='kw'>&lt;-</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/mutate'>mutate</a></span>(<span class='kw'>year</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/format'>format</a></span>(<span class='no'>date</span>, <span class='st'>"%Y"</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(<span class='kw'>year</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/format'>format</a></span>(<span class='no'>date</span>, <span class='st'>"%Y"</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'>freq</span>(<span class='no'>year</span>)
@ -463,11 +463,11 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='co'># only get selected columns</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'>freq</span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>item</span>, <span class='no'>percent</span>)
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>item</span>, <span class='no'>percent</span>)
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'>freq</span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(-<span class='no'>count</span>, -<span class='no'>cum_count</span>)
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(-<span class='no'>count</span>, -<span class='no'>cum_count</span>)
<span class='co'># check differences between frequency tables</span>

View File

@ -334,7 +334,7 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/library'>library</a></span>(<span class='no'>ggplot2</span>)
<span class='co'># get antimicrobial results for drugs against a UTI:</span>
<span class='fu'><a href='https://ggplot2.tidyverse.org/reference/ggplot.html'>ggplot</a></span>(<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>amox</span>, <span class='no'>nitr</span>, <span class='no'>fosf</span>, <span class='no'>trim</span>, <span class='no'>cipr</span>)) +
<span class='fu'><a href='https://ggplot2.tidyverse.org/reference/ggplot.html'>ggplot</a></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'>amox</span>, <span class='no'>nitr</span>, <span class='no'>fosf</span>, <span class='no'>trim</span>, <span class='no'>cipr</span>)) +
<span class='fu'>geom_rsi</span>()
<span class='co'># prettify the plot using some additional functions:</span>
@ -348,17 +348,17 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='co'># or better yet, simplify this using the wrapper function - a single command:</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>amox</span>, <span class='no'>nitr</span>, <span class='no'>fosf</span>, <span class='no'>trim</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>amox</span>, <span class='no'>nitr</span>, <span class='no'>fosf</span>, <span class='no'>trim</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>ggplot_rsi</span>()
<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://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>amox</span>, <span class='no'>nitr</span>, <span class='no'>fosf</span>, <span class='no'>trim</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>amox</span>, <span class='no'>nitr</span>, <span class='no'>fosf</span>, <span class='no'>trim</span>, <span class='no'>cipr</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='co'># add other ggplot2 parameters as you like:</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>amox</span>, <span class='no'>nitr</span>, <span class='no'>fosf</span>, <span class='no'>trim</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>amox</span>, <span class='no'>nitr</span>, <span class='no'>fosf</span>, <span class='no'>trim</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>ggplot_rsi</span>(<span class='kw'>width</span> <span class='kw'>=</span> <span class='fl'>0.5</span>,
<span class='kw'>colour</span> <span class='kw'>=</span> <span class='st'>"black"</span>,
<span class='kw'>size</span> <span class='kw'>=</span> <span class='fl'>1</span>,
@ -367,25 +367,25 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='co'># resistance of ciprofloxacine per age group</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/mutate'>mutate</a></span>(<span class='kw'>first_isolate</span> <span class='kw'>=</span> <span class='fu'><a href='first_isolate.html'>first_isolate</a></span>(<span class='no'>.</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/filter'>filter</a></span>(<span class='no'>first_isolate</span> <span class='kw'>==</span> <span class='fl'>TRUE</span>,
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(<span class='kw'>first_isolate</span> <span class='kw'>=</span> <span class='fu'><a href='first_isolate.html'>first_isolate</a></span>(<span class='no'>.</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span>(<span class='no'>first_isolate</span> <span class='kw'>==</span> <span class='fl'>TRUE</span>,
<span class='no'>mo</span> <span class='kw'>==</span> <span class='fu'><a href='as.mo.html'>as.mo</a></span>(<span class='st'>"E. coli"</span>)) <span class='kw'>%&gt;%</span>
<span class='co'># `age_group` is also a function of this package:</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/group_by'>group_by</a></span>(<span class='kw'>age_group</span> <span class='kw'>=</span> <span class='fu'><a href='age_groups.html'>age_groups</a></span>(<span class='no'>age</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>age_group</span>,
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/group_by.html'>group_by</a></span>(<span class='kw'>age_group</span> <span class='kw'>=</span> <span class='fu'><a href='age_groups.html'>age_groups</a></span>(<span class='no'>age</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>age_group</span>,
<span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>ggplot_rsi</span>(<span class='kw'>x</span> <span class='kw'>=</span> <span class='st'>"age_group"</span>)
<span class='co'># }</span><span class='co'># NOT RUN {</span>
<span class='co'># for colourblind mode, use divergent colours from the viridis package:</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>amox</span>, <span class='no'>nitr</span>, <span class='no'>fosf</span>, <span class='no'>trim</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>amox</span>, <span class='no'>nitr</span>, <span class='no'>fosf</span>, <span class='no'>trim</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>ggplot_rsi</span>() + <span class='fu'><a href='https://ggplot2.tidyverse.org/reference/scale_viridis.html'>scale_fill_viridis_d</a></span>()
<span class='co'># it also supports groups (don't forget to use the group var on `x` or `facet`):</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>hospital_id</span>, <span class='no'>amox</span>, <span class='no'>nitr</span>, <span class='no'>fosf</span>, <span class='no'>trim</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/group_by'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>hospital_id</span>, <span class='no'>amox</span>, <span class='no'>nitr</span>, <span class='no'>fosf</span>, <span class='no'>trim</span>, <span class='no'>cipr</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>
<span class='fu'>ggplot_rsi</span>(<span class='kw'>x</span> <span class='kw'>=</span> <span class='no'>hospital_id</span>,
<span class='kw'>facet</span> <span class='kw'>=</span> <span class='no'>Antibiotic</span>,
<span class='kw'>nrow</span> <span class='kw'>=</span> <span class='fl'>1</span>) +
@ -395,22 +395,22 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='co'># genuine analysis: check 2 most prevalent microorganisms</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='co'># create new bacterial ID's, with all CoNS under the same group (Becker et al.)</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/mutate'>mutate</a></span>(<span class='kw'>mo</span> <span class='kw'>=</span> <span class='fu'><a href='as.mo.html'>as.mo</a></span>(<span class='no'>mo</span>, <span class='kw'>Becker</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(<span class='kw'>mo</span> <span class='kw'>=</span> <span class='fu'><a href='as.mo.html'>as.mo</a></span>(<span class='no'>mo</span>, <span class='kw'>Becker</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>)) <span class='kw'>%&gt;%</span>
<span class='co'># filter on top three bacterial ID's</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/filter'>filter</a></span>(<span class='no'>mo</span> <span class='kw'>%in%</span> <span class='fu'><a href='freq.html'>top_freq</a></span>(<span class='fu'><a href='freq.html'>freq</a></span>(<span class='no'>.</span>$<span class='no'>mo</span>), <span class='fl'>3</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span>(<span class='no'>mo</span> <span class='kw'>%in%</span> <span class='fu'><a href='freq.html'>top_freq</a></span>(<span class='fu'><a href='freq.html'>freq</a></span>(<span class='no'>.</span>$<span class='no'>mo</span>), <span class='fl'>3</span>)) <span class='kw'>%&gt;%</span>
<span class='co'># determine first isolates</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/mutate'>mutate</a></span>(<span class='kw'>first_isolate</span> <span class='kw'>=</span> <span class='fu'><a href='first_isolate.html'>first_isolate</a></span>(<span class='no'>.</span>,
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(<span class='kw'>first_isolate</span> <span class='kw'>=</span> <span class='fu'><a href='first_isolate.html'>first_isolate</a></span>(<span class='no'>.</span>,
<span class='kw'>col_date</span> <span class='kw'>=</span> <span class='st'>"date"</span>,
<span class='kw'>col_patient_id</span> <span class='kw'>=</span> <span class='st'>"patient_id"</span>,
<span class='kw'>col_mo</span> <span class='kw'>=</span> <span class='st'>"mo"</span>)) <span class='kw'>%&gt;%</span>
<span class='co'># filter on first isolates</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/filter'>filter</a></span>(<span class='no'>first_isolate</span> <span class='kw'>==</span> <span class='fl'>TRUE</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span>(<span class='no'>first_isolate</span> <span class='kw'>==</span> <span class='fl'>TRUE</span>) <span class='kw'>%&gt;%</span>
<span class='co'># get short MO names (like "E. coli")</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/mutate'>mutate</a></span>(<span class='kw'>mo</span> <span class='kw'>=</span> <span class='fu'><a href='mo_property.html'>mo_shortname</a></span>(<span class='no'>mo</span>, <span class='kw'>Becker</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(<span class='kw'>mo</span> <span class='kw'>=</span> <span class='fu'><a href='mo_property.html'>mo_shortname</a></span>(<span class='no'>mo</span>, <span class='kw'>Becker</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>)) <span class='kw'>%&gt;%</span>
<span class='co'># select this short name and some antiseptic drugs</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>mo</span>, <span class='no'>cfur</span>, <span class='no'>gent</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>mo</span>, <span class='no'>cfur</span>, <span class='no'>gent</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='co'># group by MO</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/group_by'>group_by</a></span>(<span class='no'>mo</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'>mo</span>) <span class='kw'>%&gt;%</span>
<span class='co'># plot the thing, putting MOs on the facet</span>
<span class='fu'>ggplot_rsi</span>(<span class='kw'>x</span> <span class='kw'>=</span> <span class='no'>Antibiotic</span>,
<span class='kw'>facet</span> <span class='kw'>=</span> <span class='no'>mo</span>,

View File

@ -341,13 +341,13 @@
</tr><tr>
<td>
<p><code><a href="ab_property.html">ab_property()</a></code> <code><a href="ab_property.html">ab_atc()</a></code> <code><a href="ab_property.html">ab_official()</a></code> <code><a href="ab_property.html">ab_name()</a></code> <code><a href="ab_property.html">ab_trivial_nl()</a></code> <code><a href="ab_property.html">ab_certe()</a></code> <code><a href="ab_property.html">ab_umcg()</a></code> <code><a href="ab_property.html">ab_tradenames()</a></code> </p>
<p><code><a href="atc_property.html">atc_property()</a></code> <code><a href="atc_property.html">atc_official()</a></code> <code><a href="atc_property.html">atc_name()</a></code> <code><a href="atc_property.html">atc_trivial_nl()</a></code> <code><a href="atc_property.html">atc_certe()</a></code> <code><a href="atc_property.html">atc_umcg()</a></code> <code><a href="atc_property.html">atc_tradenames()</a></code> </p>
</td>
<td><p>Property of an antibiotic</p></td>
</tr><tr>
<td>
<p><code><a href="atc_property.html">atc_property()</a></code> <code><a href="atc_property.html">atc_groups()</a></code> <code><a href="atc_property.html">atc_ddd()</a></code> </p>
<p><code><a href="atc_online.html">atc_online_property()</a></code> <code><a href="atc_online.html">atc_online_groups()</a></code> <code><a href="atc_online.html">atc_online_ddd()</a></code> </p>
</td>
<td><p>Properties of an ATC code</p></td>
</tr><tr>
@ -518,6 +518,12 @@
<p><code><a href="mo_renamed.html">mo_renamed()</a></code> </p>
</td>
<td><p>Vector of taxonomic renamed items</p></td>
</tr><tr>
<td>
<p><code><a href="AMR-deprecated.html">ratio()</a></code> <code><a href="AMR-deprecated.html">guess_mo()</a></code> <code><a href="AMR-deprecated.html">ab_property()</a></code> <code><a href="AMR-deprecated.html">ab_atc()</a></code> <code><a href="AMR-deprecated.html">ab_official()</a></code> <code><a href="AMR-deprecated.html">ab_name()</a></code> <code><a href="AMR-deprecated.html">ab_trivial_nl()</a></code> <code><a href="AMR-deprecated.html">ab_certe()</a></code> <code><a href="AMR-deprecated.html">ab_umcg()</a></code> <code><a href="AMR-deprecated.html">ab_tradenames()</a></code> </p>
</td>
<td><p>Deprecated functions</p></td>
</tr>
</tbody>
</table>

View File

@ -334,8 +334,8 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/library'>library</a></span>(<span class='no'>dplyr</span>)
<span class='co'># set key antibiotics to a new variable</span>
<span class='no'>my_patients</span> <span class='kw'>&lt;-</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/mutate'>mutate</a></span>(<span class='kw'>keyab</span> <span class='kw'>=</span> <span class='fu'>key_antibiotics</span>(<span class='no'>.</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/mutate'>mutate</a></span>(
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(<span class='kw'>keyab</span> <span class='kw'>=</span> <span class='fu'>key_antibiotics</span>(<span class='no'>.</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(
<span class='co'># now calculate first isolates</span>
<span class='kw'>first_regular</span> <span class='kw'>=</span> <span class='fu'><a href='first_isolate.html'>first_isolate</a></span>(<span class='no'>.</span>, <span class='kw'>col_keyantibiotics</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>),
<span class='co'># and first WEIGHTED isolates</span>

View File

@ -295,7 +295,7 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/library'>library</a></span>(<span class='no'>dplyr</span>)
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='join.html'>left_join_microorganisms</a></span>() <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/filter'>filter</a></span>(<span class='no'>genus</span> <span class='kw'>%like%</span> <span class='st'>'^ent'</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span>(<span class='no'>genus</span> <span class='kw'>%like%</span> <span class='st'>'^ent'</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='freq.html'>freq</a></span>(<span class='no'>genus</span>, <span class='no'>species</span>)
<span class='co'># }</span></pre>
</div>

View File

@ -618,7 +618,7 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/library'>library</a></span>(<span class='no'>dplyr</span>)
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/mutate'>mutate</a></span>(<span class='kw'>EUCAST</span> <span class='kw'>=</span> <span class='fu'>mdro</span>(<span class='no'>.</span>),
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(<span class='kw'>EUCAST</span> <span class='kw'>=</span> <span class='fu'>mdro</span>(<span class='no'>.</span>),
<span class='kw'>BRMO</span> <span class='kw'>=</span> <span class='fu'>brmo</span>(<span class='no'>.</span>))
<span class='co'># }</span></pre>
</div>

View File

@ -340,17 +340,17 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='fu'>portion_SI</span>(<span class='no'>amox</span>)
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/group_by'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/summarise'>summarise</a></span>(<span class='kw'>p</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>cipr</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>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>p</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>cipr</span>),
<span class='kw'>n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>n_rsi</a></span>(<span class='no'>cipr</span>)) <span class='co'># n_rsi works like n_distinct in dplyr</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/group_by'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/summarise'>summarise</a></span>(<span class='kw'>R</span> <span class='kw'>=</span> <span class='fu'>portion_R</span>(<span class='no'>cipr</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</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>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>R</span> <span class='kw'>=</span> <span class='fu'>portion_R</span>(<span class='no'>cipr</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>),
<span class='kw'>I</span> <span class='kw'>=</span> <span class='fu'>portion_I</span>(<span class='no'>cipr</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>),
<span class='kw'>S</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>cipr</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>),
<span class='kw'>n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>n_rsi</a></span>(<span class='no'>cipr</span>), <span class='co'># works like n_distinct in dplyr</span>
<span class='kw'>total</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/n'>n</a></span>()) <span class='co'># NOT the amount of tested isolates!</span>
<span class='kw'>total</span> <span class='kw'>=</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/n.html'>n</a></span>()) <span class='co'># NOT the amount of tested isolates!</span>
<span class='co'># Calculate co-resistance between amoxicillin/clav acid and gentamicin,</span>
<span class='co'># so we can see that combination therapy does a lot more than mono therapy:</span>
@ -365,8 +365,8 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/group_by'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/summarise'>summarise</a></span>(<span class='kw'>cipro_p</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>cipr</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</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>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>cipro_p</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>cipr</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>),
<span class='kw'>cipro_n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>cipr</span>),
<span class='kw'>genta_p</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>gent</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>),
<span class='kw'>genta_n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>gent</span>),
@ -375,22 +375,22 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='co'># Get portions S/I/R immediately of all rsi columns</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>amox</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>amox</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>portion_df</span>(<span class='kw'>translate</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='co'># It also supports grouping variables</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/select'>select</a></span>(<span class='no'>hospital_id</span>, <span class='no'>amox</span>, <span class='no'>cipr</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/group_by'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>hospital_id</span>, <span class='no'>amox</span>, <span class='no'>cipr</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>
<span class='fu'>portion_df</span>(<span class='kw'>translate</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='co'># }</span><span class='co'># NOT RUN {</span>
<span class='co'># calculate current empiric combination therapy of Helicobacter gastritis:</span>
<span class='no'>my_table</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/filter'>filter</a></span>(<span class='no'>first_isolate</span> <span class='kw'>==</span> <span class='fl'>TRUE</span>,
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span>(<span class='no'>first_isolate</span> <span class='kw'>==</span> <span class='fl'>TRUE</span>,
<span class='no'>genus</span> <span class='kw'>==</span> <span class='st'>"Helicobacter"</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/summarise'>summarise</a></span>(<span class='kw'>p</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>amox</span>, <span class='no'>metr</span>), <span class='co'># amoxicillin with metronidazole</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>p</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>amox</span>, <span class='no'>metr</span>), <span class='co'># amoxicillin with metronidazole</span>
<span class='kw'>n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>amox</span>, <span class='no'>metr</span>))
<span class='co'># }</span></pre>
</div>

View File

@ -341,7 +341,7 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/library'>library</a></span>(<span class='no'>dplyr</span>)
<span class='no'>x</span> <span class='kw'>&lt;-</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='first_isolate.html'>filter_first_isolate</a></span>() <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/filter'>filter</a></span>(<span class='fu'><a href='mo_property.html'>mo_genus</a></span>(<span class='no'>mo</span>) <span class='kw'>==</span> <span class='st'>"Staphylococcus"</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span>(<span class='fu'><a href='mo_property.html'>mo_genus</a></span>(<span class='no'>mo</span>) <span class='kw'>==</span> <span class='st'>"Staphylococcus"</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>resistance_predict</span>(<span class='st'>"peni"</span>)
<span class='fu'><a href='https://www.rdocumentation.org/packages/graphics/topics/plot'>plot</a></span>(<span class='no'>x</span>)
@ -350,7 +350,7 @@ On our website <a href='https://msberends.gitlab.io/AMR'>https://msberends.gitla
<span class='kw'>if</span> (!<span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/library'>require</a></span>(<span class='no'>ggplot2</span>)) {
<span class='no'>data</span> <span class='kw'>&lt;-</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://www.rdocumentation.org/packages/dplyr/topics/filter'>filter</a></span>(<span class='no'>mo</span> <span class='kw'>==</span> <span class='fu'><a href='as.mo.html'>as.mo</a></span>(<span class='st'>"E. coli"</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span>(<span class='no'>mo</span> <span class='kw'>==</span> <span class='fu'><a href='as.mo.html'>as.mo</a></span>(<span class='st'>"E. coli"</span>)) <span class='kw'>%&gt;%</span>
<span class='fu'>resistance_predict</span>(<span class='kw'>col_ab</span> <span class='kw'>=</span> <span class='st'>"amox"</span>,
<span class='kw'>col_date</span> <span class='kw'>=</span> <span class='st'>"date"</span>,
<span class='kw'>info</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>,

View File

@ -15,9 +15,6 @@
<url>
<loc>https://msberends.gitlab.io/AMR/reference/WHOCC.html</loc>
</url>
<url>
<loc>https://msberends.gitlab.io/AMR/reference/ab_property.html</loc>
</url>
<url>
<loc>https://msberends.gitlab.io/AMR/reference/abname.html</loc>
</url>
@ -42,6 +39,9 @@
<url>
<loc>https://msberends.gitlab.io/AMR/reference/as.rsi.html</loc>
</url>
<url>
<loc>https://msberends.gitlab.io/AMR/reference/atc_online.html</loc>
</url>
<url>
<loc>https://msberends.gitlab.io/AMR/reference/atc_property.html</loc>
</url>

View File

@ -1,4 +1,4 @@
# `AMR` (for R) <img src="man/figures/logo.png" align="right" height="120px" />
# `AMR` (for R) <img src="./logo.png" align="right" height="120px" />
*(<help title="Too Long, Didn't Read">TLDR</help> - to find out how to conduct AMR analysis, please [continue reading here to get started](./articles/AMR.html).*
@ -6,12 +6,24 @@
`AMR` is a free and open-source [R package](https://www.r-project.org) to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial properties by using evidence-based methods.
We created this package for academic research at the Faculty of Medical Sciences of the University of Groningen and the Medical Microbiology & Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG).
This R package is free software; you can freely use and distribute it for both personal and commercial (but **not** patent) purposes under the terms of the GNU General Public License version 2.0 (GPL-2), as published by the Free Software Foundation. Read further about our GPL-2 licence [here](./LICENSE-text.html).
We created this package for both academic research and routine analysis at the Faculty of Medical Sciences of the University of Groningen and the Medical Microbiology & Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG).
This R package is actively maintained and free software; you can freely use and distribute it for both personal and commercial (but **not** patent) purposes under the terms of the GNU General Public Licence version 2.0 (GPL-2), as published by the Free Software Foundation. Read the full licence [here](./LICENSE-text.html).
This package can be used for:
* Calculating antimicrobial resistance
* Predicting antimicrobial resistance using regression models
* Getting properties for any microorganism (like Gram stain, species, genus or family)
* Getting properties for any antibiotic (like name, ATC code, defined daily dose or trade name)
* Plotting antimicrobial resistance
* Determining first isolates to be used for AMR analysis
* Applying EUCAST rules
* Determining multi-drug resistance organisms (MDRO)
* Descriptive statistics: frequency tables, kurtosis and skewness
This package is ready-to-use for a professional environment by specialists in the following fields:
Medical Microbiology:
Medical Microbiology
* Epidemiologists (both clinical microbiological and research)
* Research Microbiologists
@ -19,18 +31,18 @@ Medical Microbiology:
* Research Pharmacologists
* Data Scientists / Data Analysts
Veterinary Microbiology:
Veterinary Microbiology
* Research Veterinarians
* Veterinary Epidemiologists
Microbial Ecology:
Microbial Ecology
* Soil Microbiologists
* Extremophile Researchers
* Astrobiologists
Developers:
Developers
* Package developers for R
* Software developers

View File

@ -4,14 +4,38 @@
\alias{AMR-deprecated}
\alias{ratio}
\alias{guess_mo}
\alias{ab_property}
\alias{ab_atc}
\alias{ab_official}
\alias{ab_name}
\alias{ab_trivial_nl}
\alias{ab_certe}
\alias{ab_umcg}
\alias{ab_tradenames}
\title{Deprecated functions}
\usage{
ratio(x, ratio)
guess_mo(...)
ab_property(...)
ab_atc(...)
ab_official(...)
ab_name(...)
ab_trivial_nl(...)
ab_certe(...)
ab_umcg(...)
ab_tradenames(...)
}
\description{
These functions are \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.
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).
}
\section{Read more on our website!}{

View File

@ -9,7 +9,7 @@ Welcome to the \code{AMR} package. This page gives some additional contact infor
\details{
This package was intended to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial properties by using evidence-based methods.
This package was created for academic research by PhD students of the Faculty of Medical Sciences of the University of Groningen and the Medical Microbiology & Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG).
This package was created for both academic research and routine analysis by PhD students of the Faculty of Medical Sciences of the University of Groningen and the Medical Microbiology & Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG).
}
\section{Read more on our website!}{

View File

@ -1,59 +0,0 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/ab_property.R
\name{ab_property}
\alias{ab_property}
\alias{ab_atc}
\alias{ab_official}
\alias{ab_name}
\alias{ab_trivial_nl}
\alias{ab_certe}
\alias{ab_umcg}
\alias{ab_tradenames}
\title{Property of an antibiotic}
\usage{
ab_property(x, property = "official")
ab_atc(x)
ab_official(x, language = NULL)
ab_name(x, language = NULL)
ab_trivial_nl(x)
ab_certe(x)
ab_umcg(x)
ab_tradenames(x)
}
\arguments{
\item{x}{a (vector of a) valid \code{\link{atc}} code or any text that can be coerced to a valid atc with \code{\link{as.atc}}}
\item{property}{one of the column names of one of the \code{\link{antibiotics}} data set, like \code{"atc"} and \code{"official"}}
\item{language}{language of the returned text, defaults to English (\code{"en"}) and can be set with \code{\link{getOption}("AMR_locale")}. Either one of \code{"en"} (English) or \code{"nl"} (Dutch).}
}
\value{
A vector of values. In case of \code{ab_tradenames}, if \code{x} is of length one, a vector will be returned. Otherwise a \code{\link{list}}, with \code{x} as names.
}
\description{
Use these functions to return a specific property of an antibiotic from the \code{\link{antibiotics}} data set, based on their ATC code. Get such a code with \code{\link{as.atc}}.
}
\section{Read more on our website!}{
\if{html}{\figure{logo.png}{options: height=40px style=margin-bottom:5px} \cr}
On our website \url{https://msberends.gitlab.io/AMR} you can find \href{https://msberends.gitlab.io/AMR/articles/AMR.html}{a omprehensive tutorial} about how to conduct AMR analysis and find \href{https://msberends.gitlab.io/AMR/reference}{the complete documentation of all functions}, which reads a lot easier than in R.
}
\examples{
ab_atc("amcl") # J01CR02
ab_name("amcl") # Amoxicillin and beta-lactamase inhibitor
ab_name("amcl", "nl") # Amoxicilline met enzymremmer
ab_trivial_nl("amcl") # Amoxicilline/clavulaanzuur
ab_certe("amcl") # amcl
ab_umcg("amcl") # AMCL
}
\seealso{
\code{\link{antibiotics}}
}

73
man/atc_online.Rd Normal file
View File

@ -0,0 +1,73 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/atc_online.R
\name{atc_online_property}
\alias{atc_online_property}
\alias{atc_online_groups}
\alias{atc_online_ddd}
\title{Properties of an ATC code}
\source{
\url{https://www.whocc.no/atc_ddd_alterations__cumulative/ddd_alterations/abbrevations/}
}
\usage{
atc_online_property(atc_code, property, administration = "O",
url = "https://www.whocc.no/atc_ddd_index/?code=\%s&showdescription=no")
atc_online_groups(atc_code, ...)
atc_online_ddd(atc_code, ...)
}
\arguments{
\item{atc_code}{a character or character vector with ATC code(s) of antibiotic(s)}
\item{property}{property of an ATC code. Valid values are \code{"ATC"}, \code{"Name"}, \code{"DDD"}, \code{"U"} (\code{"unit"}), \code{"Adm.R"}, \code{"Note"} and \code{groups}. For this last option, all hierarchical groups of an ATC code will be returned, see Examples.}
\item{administration}{type of administration when using \code{property = "Adm.R"}, see Details}
\item{url}{url of website of the WHO. The sign \code{\%s} can be used as a placeholder for ATC codes.}
\item{...}{parameters to pass on to \code{atc_property}}
}
\description{
Gets data from the WHO to determine properties of an ATC (e.g. an antibiotic) like name, defined daily dose (DDD) or standard unit. \cr \strong{This function requires an internet connection.}
}
\details{
Options for parameter \code{administration}:
\itemize{
\item{\code{"Implant"}}{ = Implant}
\item{\code{"Inhal"}}{ = Inhalation}
\item{\code{"Instill"}}{ = Instillation}
\item{\code{"N"}}{ = nasal}
\item{\code{"O"}}{ = oral}
\item{\code{"P"}}{ = parenteral}
\item{\code{"R"}}{ = rectal}
\item{\code{"SL"}}{ = sublingual/buccal}
\item{\code{"TD"}}{ = transdermal}
\item{\code{"V"}}{ = vaginal}
}
Abbreviations of return values when using \code{property = "U"} (unit):
\itemize{
\item{\code{"g"}}{ = gram}
\item{\code{"mg"}}{ = milligram}
\item{\code{"mcg"}}{ = microgram}
\item{\code{"U"}}{ = unit}
\item{\code{"TU"}}{ = thousand units}
\item{\code{"MU"}}{ = million units}
\item{\code{"mmol"}}{ = millimole}
\item{\code{"ml"}}{ = milliliter (e.g. eyedrops)}
}
}
\examples{
\donttest{
# oral DDD (Defined Daily Dose) of amoxicillin
atc_online_property("J01CA04", "DDD", "O")
# parenteral DDD (Defined Daily Dose) of amoxicillin
atc_online_property("J01CA04", "DDD", "P")
atc_online_property("J01CA04", property = "groups") # search hierarchical groups of amoxicillin
# [1] "ANTIINFECTIVES FOR SYSTEMIC USE"
# [2] "ANTIBACTERIALS FOR SYSTEMIC USE"
# [3] "BETA-LACTAM ANTIBACTERIALS, PENICILLINS"
# [4] "Penicillins with extended spectrum"
}
}

View File

@ -1,77 +1,56 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/atc.R
% Please edit documentation in R/atc_property.R
\name{atc_property}
\alias{atc_property}
\alias{atc_groups}
\alias{atc_ddd}
\title{Properties of an ATC code}
\source{
\url{https://www.whocc.no/atc_ddd_alterations__cumulative/ddd_alterations/abbrevations/}
}
\alias{atc_official}
\alias{atc_name}
\alias{atc_trivial_nl}
\alias{atc_certe}
\alias{atc_umcg}
\alias{atc_tradenames}
\title{Property of an antibiotic}
\usage{
atc_property(atc_code, property, administration = "O",
url = "https://www.whocc.no/atc_ddd_index/?code=\%s&showdescription=no")
atc_property(x, property = "official")
atc_groups(atc_code, ...)
atc_official(x, language = NULL)
atc_ddd(atc_code, ...)
atc_name(x, language = NULL)
atc_trivial_nl(x)
atc_certe(x)
atc_umcg(x)
atc_tradenames(x)
}
\arguments{
\item{atc_code}{a character or character vector with ATC code(s) of antibiotic(s)}
\item{x}{a (vector of a) valid \code{\link{atc}} code or any text that can be coerced to a valid atc with \code{\link{as.atc}}}
\item{property}{property of an ATC code. Valid values are \code{"ATC"}, \code{"Name"}, \code{"DDD"}, \code{"U"} (\code{"unit"}), \code{"Adm.R"}, \code{"Note"} and \code{groups}. For this last option, all hierarchical groups of an ATC code will be returned, see Examples.}
\item{property}{one of the column names of one of the \code{\link{antibiotics}} data set, like \code{"atc"} and \code{"official"}}
\item{administration}{type of administration when using \code{property = "Adm.R"}, see Details}
\item{url}{url of website of the WHO. The sign \code{\%s} can be used as a placeholder for ATC codes.}
\item{...}{parameters to pass on to \code{atc_property}}
\item{language}{language of the returned text, defaults to English (\code{"en"}) and can be set with \code{\link{getOption}("AMR_locale")}. Either one of \code{"en"} (English) or \code{"nl"} (Dutch).}
}
\value{
A vector of values. In case of \code{atc_tradenames}, if \code{x} is of length one, a vector will be returned. Otherwise a \code{\link{list}}, with \code{x} as names.
}
\description{
Gets data from the WHO to determine properties of an ATC (e.g. an antibiotic) like name, defined daily dose (DDD) or standard unit. \cr \strong{This function requires an internet connection.}
Use these functions to return a specific property of an antibiotic from the \code{\link{antibiotics}} data set, based on their ATC code. Get such a code with \code{\link{as.atc}}.
}
\details{
Options for parameter \code{administration}:
\itemize{
\item{\code{"Implant"}}{ = Implant}
\item{\code{"Inhal"}}{ = Inhalation}
\item{\code{"Instill"}}{ = Instillation}
\item{\code{"N"}}{ = nasal}
\item{\code{"O"}}{ = oral}
\item{\code{"P"}}{ = parenteral}
\item{\code{"R"}}{ = rectal}
\item{\code{"SL"}}{ = sublingual/buccal}
\item{\code{"TD"}}{ = transdermal}
\item{\code{"V"}}{ = vaginal}
\section{Read more on our website!}{
\if{html}{\figure{logo.png}{options: height=40px style=margin-bottom:5px} \cr}
On our website \url{https://msberends.gitlab.io/AMR} you can find \href{https://msberends.gitlab.io/AMR/articles/AMR.html}{a omprehensive tutorial} about how to conduct AMR analysis and find \href{https://msberends.gitlab.io/AMR/reference}{the complete documentation of all functions}, which reads a lot easier than in R.
}
Abbreviations of return values when using \code{property = "U"} (unit):
\itemize{
\item{\code{"g"}}{ = gram}
\item{\code{"mg"}}{ = milligram}
\item{\code{"mcg"}}{ = microgram}
\item{\code{"U"}}{ = unit}
\item{\code{"TU"}}{ = thousand units}
\item{\code{"MU"}}{ = million units}
\item{\code{"mmol"}}{ = millimole}
\item{\code{"ml"}}{ = milliliter (e.g. eyedrops)}
}
}
\examples{
\donttest{
# What's the ATC of amoxicillin?
guess_atc("Amoxicillin")
# [1] "J01CA04"
# oral DDD (Defined Daily Dose) of amoxicillin
atc_property("J01CA04", "DDD", "O")
# parenteral DDD (Defined Daily Dose) of amoxicillin
atc_property("J01CA04", "DDD", "P")
atc_property("J01CA04", property = "groups") # search hierarchical groups of amoxicillin
# [1] "ANTIINFECTIVES FOR SYSTEMIC USE"
# [2] "ANTIBACTERIALS FOR SYSTEMIC USE"
# [3] "BETA-LACTAM ANTIBACTERIALS, PENICILLINS"
# [4] "Penicillins with extended spectrum"
as.atc("amcl") # J01CR02
atc_name("amcl") # Amoxicillin and beta-lactamase inhibitor
atc_name("amcl", "nl") # Amoxicilline met enzymremmer
atc_trivial_nl("amcl") # Amoxicilline/clavulaanzuur
atc_certe("amcl") # amcl
atc_umcg("amcl") # AMCL
}
\seealso{
\code{\link{antibiotics}}
}

View File

@ -71,7 +71,7 @@ pre, code {
font-family: 'Courier New', monospace;
font-size: 100% !important;
font-weight: bold;
background-color: transparent;
background-color: #f4f4f4;
}
pre {
font-size: 90% !important;
@ -84,7 +84,7 @@ kbd {
font-size: small;
vertical-align: text-bottom;
color: #2c3e50;
background: #eee;
background: #eeeeee;
font-weight: bold;
}

BIN
pkgdown/logos/logo.png Normal file

Binary file not shown.

After

Width:  |  Height:  |  Size: 56 KiB

View File

@ -21,27 +21,6 @@
context("atc.R")
# test_that("atc_property works", {
# skip_on_cran() # relies on internet connection of server, don't test
# skip_on_appveyor() # security error on AppVeyor
#
# if (!is.null(curl::nslookup("www.whocc.no", error = FALSE))) {
# expect_equal(tolower(atc_property("J01CA04", property = "Name")), "amoxicillin")
# expect_equal(atc_property("J01CA04", property = "unit"), "g")
# expect_equal(atc_property("J01CA04", property = "DDD"),
# atc_ddd("J01CA04"))
#
# expect_identical(atc_property("J01CA04", property = "Groups"),
# atc_groups("J01CA04"))
#
# expect_warning(atc_property("ABCDEFG", property = "DDD"))
#
# expect_error(atc_property("J01CA04", property = c(1:5)))
# expect_error(atc_property("J01CA04", property = "test"))
# expect_error(atc_property("J01CA04", property = "test", administration = c(1:5)))
# }
# })
test_that("guess_atc works", {
expect_equal(as.character(guess_atc(c("J01FA01",
"Erythromycin",
@ -55,7 +34,7 @@ test_that("guess_atc works", {
expect_identical(class(as.atc("amox")), "atc")
expect_identical(class(pull(antibiotics, atc)), "atc")
expect_identical(ab_trivial_nl("Cefmenoxim"), "Cefmenoxim")
expect_identical(atc_trivial_nl("Cefmenoxim"), "Cefmenoxim")
expect_warning(as.atc("Z00ZZ00")) # not yet available in data set
expect_warning(as.atc("UNKNOWN"))

View File

@ -19,20 +19,19 @@
# Visit our website for more info: https://msberends.gitab.io/AMR. #
# ==================================================================== #
context("ab_property.R")
context("atc_property.R")
test_that("ab_property works", {
expect_equal(ab_certe("amox"), "amox")
expect_equal(ab_name("amox", language = "en"), "Amoxicillin")
expect_equal(ab_name("amox", language = "nl"), "Amoxicilline")
expect_equal(ab_official("amox", language = "en"), "Amoxicillin")
expect_equal(ab_trivial_nl("amox"), "Amoxicilline")
expect_equal(ab_umcg("amox"), "AMOX")
expect_equal(class(ab_tradenames("amox")), "character")
expect_equal(class(ab_tradenames(c("amox", "amox"))), "list")
expect_equal(ab_atc("amox"), as.character(as.atc("amox")))
test_that("atc_property works", {
expect_equal(atc_certe("amox"), "amox")
expect_equal(atc_name("amox", language = "en"), "Amoxicillin")
expect_equal(atc_name("amox", language = "nl"), "Amoxicilline")
expect_equal(atc_official("amox", language = "en"), "Amoxicillin")
expect_equal(atc_trivial_nl("amox"), "Amoxicilline")
expect_equal(atc_umcg("amox"), "AMOX")
expect_equal(class(atc_tradenames("amox")), "character")
expect_equal(class(atc_tradenames(c("amox", "amox"))), "list")
expect_error(ab_property("amox", "invalid property"))
expect_error(ab_name("amox", language = "INVALID"))
expect_output(print(ab_name("amox", language = NULL)))
expect_error(atc_property("amox", "invalid property"))
expect_error(atc_name("amox", language = "INVALID"))
expect_output(print(atc_name("amox", language = NULL)))
})

View File

@ -41,14 +41,17 @@ knitr::kable(dplyr::tibble(date = Sys.Date(),
```
## Needed R packages
As with many uses in R, we need some additional packages for AMR analysis. The most important one is [`dplyr`](https://dplyr.tidyverse.org/), which tremendously improves the way we work with data - it allows for a very natural way of writing syntaxes in R. Another important dependency is [`ggplot2`](https://ggplot2.tidyverse.org/). This package can be used to create beautiful plots in R.
As with many uses in R, we need some additional packages for AMR analysis. Our package works closely together with the [tidyverse packages](https://www.tidyverse.org) [`dplyr`](https://dplyr.tidyverse.org/) and [`ggplot2`](https://ggplot2.tidyverse.org) by [Dr Hadley Wickham](https://www.linkedin.com/in/hadleywickham/). The tidyverse tremendously improves the way we conduct data science - it allows for a very natural way of writing syntaxes and creating beautiful plots in R.
Our `AMR` package depends on these packages and even extends their use and functions.
Our `AMR` package depends on these packages and even extends their use and functions.
```{r lib packages, message = FALSE}
library(dplyr) # the data science package
library(AMR) # this package, to simplify and automate AMR analysis
library(ggplot2) # for appealing plots
library(dplyr)
library(ggplot2)
library(AMR)
# (if not yet installed, install with:)
# install.packages(c("tidyverse", "AMR"))
```
## Creation of data