ab_* functions, mo_* functions, 180 new microorganisms, speed improvement for bactid

This commit is contained in:
dr. M.S. (Matthijs) Berends 2018-08-28 13:51:13 +02:00
parent 2acdb1981c
commit 972fc4f6c7
24 changed files with 571 additions and 306 deletions

View File

@ -1,6 +1,6 @@
Package: AMR
Version: 0.3.0.9004
Date: 2018-08-23
Version: 0.3.0.9005
Date: 2018-08-28
Title: Antimicrobial Resistance Analysis
Authors@R: c(
person(

View File

@ -36,30 +36,22 @@ export(EUCAST_exceptional_phenotypes)
export(EUCAST_rules)
export(MDRO)
export(MRGN)
export(ab_atc)
export(ab_certe)
export(ab_official)
export(ab_official_nl)
export(ab_property)
export(ab_trivial_nl)
export(ab_umcg)
export(abname)
export(anti_join_microorganisms)
export(as.atc)
export(as.bactid)
export(as.mic)
export(as.rsi)
export(atc.certe)
export(atc.official)
export(atc.official_nl)
export(atc.trivial_nl)
export(atc.umcg)
export(atc_ddd)
export(atc_groups)
export(atc_property)
export(bactid.aerobic)
export(bactid.family)
export(bactid.fullname)
export(bactid.genus)
export(bactid.gramstain)
export(bactid.gramstain_nl)
export(bactid.species)
export(bactid.subspecies)
export(bactid.type)
export(bactid.type_nl)
export(clipboard_export)
export(clipboard_import)
export(count_I)
@ -90,6 +82,17 @@ export(key_antibiotics_equal)
export(kurtosis)
export(left_join_microorganisms)
export(like)
export(mo_aerobic)
export(mo_family)
export(mo_fullname)
export(mo_genus)
export(mo_gramstain)
export(mo_gramstain_nl)
export(mo_property)
export(mo_species)
export(mo_subspecies)
export(mo_type)
export(mo_type_nl)
export(n_rsi)
export(p.symbol)
export(portion_I)

18
NEWS.md
View File

@ -5,17 +5,22 @@
* New function `count_df` to get all counts of S, I and R of a data set with antibiotic columns, with support for grouped variables
* Function `is.rsi.eligible` to check for columns that have valid antimicrobial results, but do not have the `rsi` class yet. Transform the columns of your raw data with: `data %>% mutate_if(is.rsi.eligible, as.rsi)`
* Functions `as.atc` and `is.atc` to transform/look up antibiotic ATC codes as defined by the WHO. The existing function `guess_atc` is now an alias of `as.atc`.
* Function `mo_property` removed in favour of functions `bactid.family`, `bactid.genus`, `bactid.species`, `bactid.subspecies`, `bactid.fullname`, `bactid.type`, `bactid.gramstain`, `bactid.aerobic` to get a property of a microorganism based on their 'bactid'.
* Aliases for existing function `mo_property`: `mo_aerobic`, `mo_family`, `mo_fullname`, `mo_genus`, `mo_gramstain`, `mo_gramstain_nl`, `mo_property`, `mo_species`, `mo_subspecies`, `mo_type`, `mo_type_nl`
* Function `ab_property` and its aliases: `ab_certe`, `ab_official`, `ab_official_nl`, `ab_property`, `ab_trivial_nl`, `ab_umcg`
#### Changed
* Removed function `ratio`
* Added 182 microorganisms to the `microorganisms` data set, now n = 2,646 (2,207 bacteria, 285 fungi/yeasts, 153 parasites, 1 other)
* Removed function `ratio` as it is not really the scope of this package
* Fix in `as.mic` for values ending in zeroes after a real number
* Huge speed improvement for `as.bactid`
* Added parameters `minimum` and `as_percent` to `portion_df`
* Support for quasiquotation in the functions series `count_*` and `portions_*`, and `n_rsi`. This allows to check for more than 2 vectors or columns.
* `septic_patients %>% select(amox, cipr) %>% count_R()`
* `septic_patients %>% portion_S(amcl)`
* `septic_patients %>% portion_S(amcl, gent)`
* `septic_patients %>% portion_S(amcl, gent, pita)`
```r
septic_patients %>% select(amox, cipr) %>% count_R()
septic_patients %>% portion_S(amcl)
septic_patients %>% portion_S(amcl, gent)
septic_patients %>% portion_S(amcl, gent, pita)
```
* Edited `ggplot_rsi` and `geom_rsi` so they can cope with `count_df`. The new `fun` parameter has value `portion_df` at default, but can be set to `count_df`.
* Fix for `ggplot_rsi` when the `ggplot2` package was not loaded
* Added possibility to set any parameter to `geom_rsi` (and `ggplot_rsi`) so you can set your own preferences
@ -30,6 +35,7 @@
my_list %>% freq(age)
my_list %>% freq(sex)
```
* Added "Furabid" as a trade name to Nitrofurantoine in the `antibiotics` data set
#### Other
* More unit tests to ensure better integrity of functions

84
R/ab_property.R Normal file
View File

@ -0,0 +1,84 @@
# ==================================================================== #
# TITLE #
# Antimicrobial Resistance (AMR) Analysis #
# #
# AUTHORS #
# Berends MS (m.s.berends@umcg.nl), Luz CF (c.f.luz@umcg.nl) #
# #
# LICENCE #
# This program is free software; you can redistribute it and/or modify #
# it under the terms of the GNU General Public License version 2.0, #
# as published by the Free Software Foundation. #
# #
# This program is distributed in the hope that it will be useful, #
# but WITHOUT ANY WARRANTY; without even the implied warranty of #
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the #
# GNU General Public License for more details. #
# ==================================================================== #
#' Property of an antibiotic
#'
#' 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}}.
#' @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"}
#' @rdname ab_property
#' @export
#' @importFrom dplyr %>% left_join pull
#' @seealso \code{\link{antibiotics}}
#' @examples
#' ab_atc("amcl") # J01CR02
#' ab_official("amcl") # Amoxicillin and beta-lactamase inhibitor
#' ab_official_nl("amcl") # Amoxicilline met enzymremmer
#' ab_trivial_nl("amcl") # Amoxicilline/clavulaanzuur
#' ab_certe("amcl") # amcl
#' ab_umcg("amcl") # AMCL
ab_property <- function(x, property = 'official') {
property <- property[1]
if (!property %in% colnames(antibiotics)) {
stop("invalid property: ", property, " - use a column name of `antibiotics`")
}
if (!is.atc(x)) {
x <- as.atc(x) # this will give a warning if x cannot be coerced
}
suppressWarnings(
data.frame(atc = x, stringsAsFactors = FALSE) %>%
left_join(AMR::antibiotics, by = "atc") %>%
pull(property)
)
}
#' @rdname ab_property
#' @export
ab_atc <- function(x) {
as.character(as.atc(x))
}
#' @rdname ab_property
#' @export
ab_official <- function(x) {
ab_property(x, "official")
}
#' @rdname ab_property
#' @export
ab_official_nl <- function(x) {
ab_property(x, "official_nl")
}
#' @rdname ab_property
#' @export
ab_trivial_nl <- function(x) {
ab_property(x, "trivial_nl")
}
#' @rdname ab_property
#' @export
ab_certe <- function(x) {
ab_property(x, "certe")
}
#' @rdname ab_property
#' @export
ab_umcg <- function(x) {
ab_property(x, "umcg")
}

64
R/atc.R
View File

@ -26,7 +26,9 @@
#' @keywords atc
#' @export
#' @importFrom dplyr %>% filter slice pull
#' @details 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.
#' @details Use the \code{\link{ab_property}} functions to get properties based on the returned ATC code, see Examples.
#'
#' In the ATC classification system, the active substances are classified in a hierarchy with five different levels. The system has fourteen main anatomical/pharmacological groups or 1st levels. Each ATC main group is divided into 2nd levels which could be either pharmacological or therapeutic groups. The 3rd and 4th levels are chemical, pharmacological or therapeutic subgroups and the 5th level is the chemical substance. The 2nd, 3rd and 4th levels are often used to identify pharmacological subgroups when that is considered more appropriate than therapeutic or chemical subgroups.
#' Source: \url{https://www.whocc.no/atc/structure_and_principles/}
#' @return Character (vector) with class \code{"act"}. Unknown values will return \code{NA}.
#' @seealso \code{\link{antibiotics}} for the dataframe that is being used to determine ATC's.
@ -40,6 +42,11 @@
#' as.atc("Erythrocin") # Trade name
#' as.atc("Eryzole") # Trade name
#' as.atc("Pediamycin") # Trade name
#'
#' # Use ab_* functions to get a specific property based on an ATC code
#' Cipro <- as.atc("cipro") # returns `J01MA02`
#' ab_official(Cipro) # returns "Ciprofloxacin"
#' ab_umcg(Cipro) # returns "CIPR", the code used in the UMCG
as.atc <- function(x) {
x.new <- rep(NA_character_, length(x))
@ -90,6 +97,15 @@ as.atc <- function(x) {
x.new[is.na(x.new) & x.bak == x[i]] <- found[1L]
}
# nothing helped, try first chars of official name, but only if nchar > 4 (cipro, nitro, fosfo)
if (nchar(x[i]) > 4) {
found <- AMR::antibiotics[which(AMR::antibiotics$official %like% paste0("^", substr(x[i], 1, 5))),]$atc
if (length(found) > 0) {
fail <- FALSE
x.new[is.na(x.new) & x.bak == x[i]] <- found[1L]
}
}
# not found
if (fail == TRUE) {
failures <- c(failures, x[i])
@ -149,52 +165,6 @@ pull.atc <- function(.data, ...) {
pull(as.data.frame(.data), ...)
}
atc_get_property <- function(atc, param) {
if (!is.atc(atc)) {
atc <- as.atc(atc)
}
suppressWarnings(
data.frame(atc = atc, stringsAsFactors = FALSE) %>%
left_join(AMR::antibiotics, by = "atc") %>%
pull(param)
)
}
#' Get antibiotic property based on ATC
#'
#' Use these functions to return a specific property of an antibiotic from the \code{\link{antibiotics}} data set, based on their ATC code.
#' @param atc a valid ATC code, created with \code{\link{as.atc}}
#' @rdname atc.property
#' @name atc.property
#' @export
atc.official <- function(atc) {
atc_get_property(atc, "official")
}
#' @rdname atc.property
#' @export
atc.official_nl <- function(atc) {
atc_get_property(atc, "official_nl")
}
#' @rdname atc.property
#' @export
atc.trivial_nl <- function(atc) {
atc_get_property(atc, "trivial_nl")
}
#' @rdname atc.property
#' @export
atc.certe <- function(atc) {
atc_get_property(atc, "certe")
}
#' @rdname atc.property
#' @export
atc.umcg <- function(atc) {
atc_get_property(atc, "umcg")
}
#' 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.}

View File

@ -23,9 +23,12 @@
#' @param Becker a logical to indicate whether \emph{Staphylococci} should be categorised into Coagulase Negative \emph{Staphylococci} ("CoNS") and Coagulase Positive \emph{Staphylococci} ("CoPS") instead of their own species, according to Karsten Becker \emph{et al.} [1]. This excludes \emph{Staphylococcus aureus} at default, use \code{Becker = "all"} to also categorise \emph{S. aureus} as "CoPS".
#' @param Lancefield a logical to indicate whether beta-haemolytic \emph{Streptococci} should be categorised into Lancefield groups instead of their own species, according to Rebecca C. Lancefield [2]. These \emph{Streptococci} will be categorised in their first group, i.e. \emph{Streptococcus dysgalactiae} will be group C, although officially it was also categorised into groups G and L. Groups D and E will be ignored, since they are \emph{Enterococci}.
#' @rdname as.bactid
#' @aliases bactid
#' @keywords bactid Becker becker Lancefield lancefield guess
#' @details \code{guess_bactid} is an alias of \code{as.bactid}.
#'
#' Use the \code{\link{mo_property}} functions to get properties based on the returned bactid, see Examples.
#'
#' Some exceptions have been built in to get more logical results, based on prevalence of human pathogens. These are:
#' \itemize{
#' \item{\code{"E. coli"} will return the ID of \emph{Escherichia coli} and not \emph{Entamoeba coli}, although the latter would alphabetically come first}
@ -41,7 +44,7 @@
#' [2] Lancefield RC \strong{A serological differentiation of human and other groups of hemolytic streptococci}. 1933. J Exp Med. 57(4): 57195. \cr
#' \url{https://dx.doi.org/10.1084/jem.57.4.571}
#' @export
#' @importFrom dplyr %>% filter pull
#' @importFrom dplyr %>% pull left_join
#' @return Character (vector) with class \code{"bactid"}. Unknown values will return \code{NA}.
#' @seealso \code{\link{microorganisms}} for the dataframe that is being used to determine ID's.
#' @examples
@ -56,12 +59,18 @@
#' as.bactid("VISA") # Vancomycin Intermediate S. aureus
#' as.bactid("VRSA") # Vancomycin Resistant S. aureus
#'
#' # guess_bactid is an alias of as.bactid and works the same
#' guess_bactid("S. epidermidis") # will remain species: STAEPI
#' guess_bactid("S. epidermidis", Becker = TRUE) # will not remain species: STACNS
#'
#' guess_bactid("S. pyogenes") # will remain species: STCAGA
#' guess_bactid("S. pyogenes", Lancefield = TRUE) # will not remain species: STCGRA
#'
#' # Use mo_* functions to get a specific property based on a bactid
#' Ecoli <- as.bactid("E. coli") # returns `ESCCOL`
#' mo_genus(Ecoli) # returns "Escherichia"
#' mo_gramstain(Ecoli) # returns "Negative rods"
#'
#' \dontrun{
#' df$bactid <- as.bactid(df$microorganism_name)
#'
@ -82,7 +91,6 @@
#' }
as.bactid <- function(x, Becker = FALSE, Lancefield = FALSE) {
failures <- character(0)
if (NCOL(x) == 2) {
# support tidyverse selection like: df %>% select(colA, colB)
@ -103,12 +111,19 @@ as.bactid <- function(x, Becker = FALSE, Lancefield = FALSE) {
}
}
x.fullbackup <- x
MOs <- AMR::microorganisms %>% filter(!bactid %like% '^_FAM') # dont search in those
failures <- character(0)
x_input <- x
# only check the uniques, which is way faster
x <- unique(x)
x_backup <- x
# remove dots and other non-text in case of "E. coli" except spaces
x <- gsub("[^a-zA-Z0-9 ]+", "", x)
# but spaces before and after should be omitted
x <- trimws(x, which = "both")
x.backup <- x
x_trimmed <- x
# replace space by regex sign
x_withspaces <- gsub(" ", ".* ", x, fixed = TRUE)
x <- gsub(" ", ".*", x, fixed = TRUE)
@ -121,7 +136,7 @@ as.bactid <- function(x, Becker = FALSE, Lancefield = FALSE) {
for (i in 1:length(x)) {
if (Becker == TRUE | Becker == "all") {
mo <- suppressWarnings(guess_bactid(x.fullbackup[i]))
mo <- suppressWarnings(guess_bactid(x_backup[i]))
if (mo %like% '^STA') {
# See Source. It's this figure:
# https://www.ncbi.nlm.nih.gov/pmc/articles/PMC4187637/figure/F3/
@ -152,7 +167,7 @@ as.bactid <- function(x, Becker = FALSE, Lancefield = FALSE) {
}
if (Lancefield == TRUE) {
mo <- suppressWarnings(guess_bactid(x.fullbackup[i]))
mo <- suppressWarnings(guess_bactid(x_backup[i]))
if (mo %like% '^STC') {
# See Source
species <- left_join_microorganisms(mo)$species
@ -184,20 +199,20 @@ as.bactid <- function(x, Becker = FALSE, Lancefield = FALSE) {
}
}
if (identical(x.backup[i], "")) {
if (identical(x_trimmed[i], "")) {
# empty values
x[i] <- NA
failures <- c(failures, x.fullbackup[i])
failures <- c(failures, x_backup[i])
next
}
if (x.fullbackup[i] %in% AMR::microorganisms$bactid) {
if (x_backup[i] %in% MOs$bactid) {
# is already a valid bactid
x[i] <- x.fullbackup[i]
x[i] <- x_backup[i]
next
}
if (x.backup[i] %in% AMR::microorganisms$bactid) {
if (x_trimmed[i] %in% MOs$bactid) {
# is already a valid bactid
x[i] <- x.backup[i]
x[i] <- x_trimmed[i]
next
}
@ -232,27 +247,27 @@ as.bactid <- function(x, Becker = FALSE, Lancefield = FALSE) {
}
# translate known trivial names to genus+species
if (!is.na(x.backup[i])) {
if (toupper(x.backup[i]) == 'MRSA'
| toupper(x.backup[i]) == 'VISA'
| toupper(x.backup[i]) == 'VRSA') {
if (!is.na(x_trimmed[i])) {
if (toupper(x_trimmed[i]) == 'MRSA'
| toupper(x_trimmed[i]) == 'VISA'
| toupper(x_trimmed[i]) == 'VRSA') {
x[i] <- 'STAAUR'
next
}
if (toupper(x.backup[i]) == 'MRSE') {
if (toupper(x_trimmed[i]) == 'MRSE') {
x[i] <- 'STAEPI'
next
}
if (toupper(x.backup[i]) == 'VRE') {
if (toupper(x_trimmed[i]) == 'VRE') {
x[i] <- 'ENC'
next
}
if (toupper(x.backup[i]) == 'MRPA') {
if (toupper(x_trimmed[i]) == 'MRPA') {
# multi resistant P. aeruginosa
x[i] <- 'PSEAER'
next
}
if (toupper(x.backup[i]) %in% c('PISP', 'PRSP', 'VISP', 'VRSP')) {
if (toupper(x_trimmed[i]) %in% c('PISP', 'PRSP', 'VISP', 'VRSP')) {
# peni R, peni I, vanco I, vanco R: S. pneumoniae
x[i] <- 'STCPNE'
next
@ -260,14 +275,14 @@ as.bactid <- function(x, Becker = FALSE, Lancefield = FALSE) {
}
# try any match keeping spaces
found <- AMR::microorganisms[which(AMR::microorganisms$fullname %like% x_withspaces[i]),]$bactid
found <- MOs[which(MOs$fullname %like% x_withspaces[i]),]$bactid
if (length(found) > 0) {
x[i] <- found[1L]
next
}
# try any match diregarding spaces
found <- AMR::microorganisms[which(AMR::microorganisms$fullname %like% x[i]),]$bactid
found <- MOs[which(MOs$fullname %like% x[i]),]$bactid
if (length(found) > 0) {
x[i] <- found[1L]
next
@ -275,21 +290,21 @@ as.bactid <- function(x, Becker = FALSE, Lancefield = FALSE) {
# try exact match of only genus, with 'species' attached
# (this prevents Streptococcus from becoming Peptostreptococcus, since "p" < "s")
found <- AMR::microorganisms[which(AMR::microorganisms$fullname == x_species[i]),]$bactid
found <- MOs[which(MOs$fullname == x_species[i]),]$bactid
if (length(found) > 0) {
x[i] <- found[1L]
next
}
# try any match of only genus, with 'species' attached
found <- AMR::microorganisms[which(AMR::microorganisms$fullname %like% x_species[i]),]$bactid
found <- MOs[which(MOs$fullname %like% x_species[i]),]$bactid
if (length(found) > 0) {
x[i] <- found[1L]
next
}
# search for GLIMS code
found <- AMR::microorganisms.umcg[which(toupper(AMR::microorganisms.umcg$mocode) == toupper(x.backup[i])),]$bactid
found <- AMR::microorganisms.umcg[which(toupper(AMR::microorganisms.umcg$mocode) == toupper(x_trimmed[i])),]$bactid
if (length(found) > 0) {
x[i] <- found[1L]
next
@ -298,11 +313,11 @@ as.bactid <- function(x, Becker = FALSE, Lancefield = FALSE) {
# try splitting of characters and then find ID
# like esco = E. coli, klpn = K. pneumoniae, stau = S. aureus
x_split <- x
x_length <- nchar(x.backup[i])
x_split[i] <- paste0(x.backup[i] %>% substr(1, x_length / 2) %>% trimws(),
x_length <- nchar(x_trimmed[i])
x_split[i] <- paste0(x_trimmed[i] %>% substr(1, x_length / 2) %>% trimws(),
'.* ',
x.backup[i] %>% substr((x_length / 2) + 1, x_length) %>% trimws())
found <- AMR::microorganisms[which(AMR::microorganisms$fullname %like% paste0('^', x_split[i])),]$bactid
x_trimmed[i] %>% substr((x_length / 2) + 1, x_length) %>% trimws())
found <- MOs[which(MOs$fullname %like% paste0('^', x_split[i])),]$bactid
if (length(found) > 0) {
x[i] <- found[1L]
next
@ -310,13 +325,13 @@ as.bactid <- function(x, Becker = FALSE, Lancefield = FALSE) {
# try any match with text before and after original search string
# so "negative rods" will be "GNR"
if (x.backup[i] %like% "^Gram") {
x.backup[i] <- gsub("^Gram", "", x.backup[i], ignore.case = TRUE)
if (x_trimmed[i] %like% "^Gram") {
x_trimmed[i] <- gsub("^Gram", "", x_trimmed[i], ignore.case = TRUE)
# remove leading and trailing spaces again
x.backup[i] <- trimws(x.backup[i], which = "both")
x_trimmed[i] <- trimws(x_trimmed[i], which = "both")
}
if (!is.na(x.backup[i])) {
found <- AMR::microorganisms[which(AMR::microorganisms$fullname %like% x.backup[i]),]$bactid
if (!is.na(x_trimmed[i])) {
found <- MOs[which(MOs$fullname %like% x_trimmed[i]),]$bactid
if (length(found) > 0) {
x[i] <- found[1L]
next
@ -325,7 +340,7 @@ as.bactid <- function(x, Becker = FALSE, Lancefield = FALSE) {
# not found
x[i] <- NA_character_
failures <- c(failures, x.fullbackup[i])
failures <- c(failures, x_backup[i])
}
@ -336,6 +351,19 @@ as.bactid <- function(x, Becker = FALSE, Lancefield = FALSE) {
".",
call. = FALSE)
}
# left join the found results to the original input values (x_input)
df_found <- data.frame(input = as.character(unique(x_input)),
found = x,
stringsAsFactors = FALSE)
df_input <- data.frame(input = as.character(x_input),
stringsAsFactors = FALSE)
x <- df_input %>%
left_join(df_found,
by = "input") %>%
pull(found)
class(x) <- "bactid"
attr(x, 'package') <- 'AMR'
x
@ -380,79 +408,3 @@ as.data.frame.bactid <- function (x, ...) {
pull.bactid <- function(.data, ...) {
pull(as.data.frame(.data), ...)
}
bactid_get_property <- function(bactid, param) {
if (!is.bactid(bactid)) {
bactid <- as.bactid(bactid)
}
suppressWarnings(
data.frame(bactid = bactid, stringsAsFactors = FALSE) %>%
left_join(AMR::microorganisms, by = "bactid") %>%
pull(param)
)
}
#' Get microbial property based on `bactid`
#'
#' Use these functions to return a specific property of a microorganism from the \code{\link{microorganisms}} data set, based on their \code{bactid}. Get such an ID with \code{\link{as.bactid}}.
#' @param bactid a valid bactid code, created with \code{\link{as.bactid}}
#' @rdname bactid.property
#' @name bactid.property
#' @export
bactid.family <- function(bactid) {
bactid_get_property(bactid, "family")
}
#' @rdname bactid.property
#' @export
bactid.genus <- function(bactid) {
bactid_get_property(bactid, "genus")
}
#' @rdname bactid.property
#' @export
bactid.species <- function(bactid) {
bactid_get_property(bactid, "species")
}
#' @rdname bactid.property
#' @export
bactid.subspecies <- function(bactid) {
bactid_get_property(bactid, "subspecies")
}
#' @rdname bactid.property
#' @export
bactid.fullname <- function(bactid) {
bactid_get_property(bactid, "fullname")
}
#' @rdname bactid.property
#' @export
bactid.type <- function(bactid) {
bactid_get_property(bactid, "type")
}
#' @rdname bactid.property
#' @export
bactid.gramstain <- function(bactid) {
bactid_get_property(bactid, "gramstain")
}
#' @rdname bactid.property
#' @export
bactid.aerobic <- function(bactid) {
bactid_get_property(bactid, "aerobic")
}
#' @rdname bactid.property
#' @export
bactid.type_nl <- function(bactid) {
bactid_get_property(bactid, "type_nl")
}
#' @rdname bactid.property
#' @export
bactid.gramstain_nl <- function(bactid) {
bactid_get_property(bactid, "gramstain_nl")
}

View File

@ -24,11 +24,11 @@
#' \item{\code{atc}}{ATC code, like \code{J01CR02}}
#' \item{\code{certe}}{Certe code, like \code{amcl}}
#' \item{\code{umcg}}{UMCG code, like \code{AMCL}}
#' \item{\code{abbr}}{Abbreviation as used by many countries, to be used for \code{\link{guess_atc}}}
#' \item{\code{official}}{Official name by the WHO, like \code{"Amoxicillin and enzyme inhibitor"}}
#' \item{\code{abbr}}{Abbreviation as used by many countries, used internally by \code{\link{as.atc}}}
#' \item{\code{official}}{Official name by the WHO, like \code{"Amoxicillin and beta-lactamase inhibitor"}}
#' \item{\code{official_nl}}{Official name in the Netherlands, like \code{"Amoxicilline met enzymremmer"}}
#' \item{\code{trivial_nl}}{Trivial name in Dutch, like \code{"Amoxicilline/clavulaanzuur"}}
#' \item{\code{trade_name}}{Trade name as used by many countries, to be used for \code{\link{guess_atc}}}
#' \item{\code{trade_name}}{Trade name as used by many countries, used internally by \code{\link{as.atc}}}
#' \item{\code{oral_ddd}}{Defined Daily Dose (DDD), oral treatment}
#' \item{\code{oral_units}}{Units of \code{ddd_units}}
#' \item{\code{iv_ddd}}{Defined Daily Dose (DDD), parenteral treatment}
@ -252,11 +252,25 @@
# )
# )
"antibiotics"
antibiotics_add_to_property <- function(antibiotics, atc, property, value) {
if (length(atc) > 1L) {
stop("only one atc at a time")
}
if (!property %in% c("abbr", "trade_name")) {
stop("only possible for abbr and trade_name")
}
if (atc %in% antibiotics$atc) {
current <- antibiotics[which(antibiotics$atc == atc), property]
antibiotics[which(antibiotics$atc == atc), property] <- paste(current, value, sep = "|")
message("done")
}
antibiotics
}
#' Dataset with ~2500 microorganisms
#' Dataset with ~2650 microorganisms
#'
#' A dataset containing 2464 microorganisms. MO codes of the UMCG can be looked up using \code{\link{microorganisms.umcg}}.
#' @format A data.frame with 2464 observations and 12 variables:
#' A dataset containing 2,646 microorganisms. MO codes of the UMCG can be looked up using \code{\link{microorganisms.umcg}}.
#' @format A data.frame with 2,646 observations and 12 variables:
#' \describe{
#' \item{\code{bactid}}{ID of microorganism}
#' \item{\code{bactsys}}{Bactsyscode of microorganism}

139
R/mo_property.R Normal file
View File

@ -0,0 +1,139 @@
# ==================================================================== #
# TITLE #
# Antimicrobial Resistance (AMR) Analysis #
# #
# AUTHORS #
# Berends MS (m.s.berends@umcg.nl), Luz CF (c.f.luz@umcg.nl) #
# #
# LICENCE #
# This program is free software; you can redistribute it and/or modify #
# it under the terms of the GNU General Public License version 2.0, #
# as published by the Free Software Foundation. #
# #
# This program is distributed in the hope that it will be useful, #
# but WITHOUT ANY WARRANTY; without even the implied warranty of #
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the #
# GNU General Public License for more details. #
# ==================================================================== #
#' Property of a microorganism
#'
#' Use these functions to return a specific property of a microorganism from the \code{\link{microorganisms}} data set, based on their \code{bactid}. Get such an ID with \code{\link{as.bactid}}.
#' @param x a (vector of a) valid \code{\link{bactid}} or any text that can be coerced to a valid bactid with \code{\link{as.bactid}}
#' @param property one of the column names of one of the \code{\link{microorganisms}} data set, like \code{"bactid"}, \code{"bactsys"}, \code{"family"}, \code{"genus"}, \code{"species"}, \code{"fullname"}, \code{"gramstain"} and \code{"aerobic"}
#' @rdname mo_property
#' @export
#' @importFrom dplyr %>% left_join pull
#' @seealso \code{\link{microorganisms}}
#' @examples
#' # All properties
#' mo_family("E. coli") # Enterobacteriaceae
#' mo_genus("E. coli") # Escherichia
#' mo_species("E. coli") # coli
#' mo_subspecies("E. coli") # <NA>
#' mo_fullname("E. coli") # Escherichia coli
#' mo_type("E. coli") # Bacteria
#' mo_gramstain("E. coli") # Negative rods
#' mo_aerobic("E. coli") # TRUE
#' mo_type_nl("E. coli") # Bacterie
#' mo_gramstain_nl("E. coli") # Negatieve staven
#'
#'
#' # Abbreviations known in the field
#' mo_genus("EHEC") # Escherichia
#' mo_species("EHEC") # coli
#' mo_subspecies("EHEC") # EHEC
#' mo_fullname("EHEC") # Escherichia coli (EHEC)
#'
#' mo_genus("MRSA") # Staphylococcus
#' mo_species("MRSA") # aureus
#' mo_gramstain("MRSA") # Positive cocci
#'
#' mo_genus("VISA") # Staphylococcus
#' mo_species("VISA") # aureus
#'
#'
#' # Known subspecies
#' mo_genus("doylei") # Campylobacter
#' mo_species("doylei") # jejuni
#' mo_fullname("doylei") # Campylobacter jejuni (doylei)
#'
#'
#' # Anaerobic bacteria
#' mo_genus("B. fragilis") # Bacteroides
#' mo_species("B. fragilis") # fragilis
#' mo_aerobic("B. fragilis") # FALSE
mo_property <- function(x, property = 'fullname') {
property <- property[1]
if (!property %in% colnames(microorganisms)) {
stop("invalid property: ", property, " - use a column name of `microorganisms`")
}
if (!is.bactid(x)) {
x <- as.bactid(x) # this will give a warning if x cannot be coerced
}
suppressWarnings(
data.frame(bactid = x, stringsAsFactors = FALSE) %>%
left_join(AMR::microorganisms, by = "bactid") %>%
pull(property)
)
}
#' @rdname mo_property
#' @export
mo_family <- function(x) {
mo_property(x, "family")
}
#' @rdname mo_property
#' @export
mo_genus <- function(x) {
mo_property(x, "genus")
}
#' @rdname mo_property
#' @export
mo_species <- function(x) {
mo_property(x, "species")
}
#' @rdname mo_property
#' @export
mo_subspecies <- function(x) {
mo_property(x, "subspecies")
}
#' @rdname mo_property
#' @export
mo_fullname <- function(x) {
mo_property(x, "fullname")
}
#' @rdname mo_property
#' @export
mo_type <- function(x) {
mo_property(x, "type")
}
#' @rdname mo_property
#' @export
mo_gramstain <- function(x) {
mo_property(x, "gramstain")
}
#' @rdname mo_property
#' @export
mo_aerobic <- function(x) {
mo_property(x, "aerobic")
}
#' @rdname mo_property
#' @export
mo_type_nl <- function(x) {
mo_property(x, "type_nl")
}
#' @rdname mo_property
#' @export
mo_gramstain_nl <- function(x) {
mo_property(x, "gramstain_nl")
}

View File

@ -42,29 +42,36 @@ This R package was intended to make microbial epidemiology easier. Most function
This `AMR` package basically does four important things:
1. It **cleanses existing data**, by transforming it to reproducible and profound *classes*, making the most efficient use of R. These function all use artificial intelligence to get expected results:
1. It **cleanses existing data**, by transforming it to reproducible and profound *classes*, making the most efficient use of R. These functions all use artificial intelligence to get 'more expected' results:
* Use `as.bactid` to get an ID of a microorganism. It takes almost any text as input that looks like the name or code of a microorganism like "E. coli", "esco" and "esccol". Moreover, it can group all coagulase negative and positive *Staphylococci*, and can transform *Streptococci* into Lancefield groups. This package has a database of ~2500 different (potential) human pathogenic microorganisms.
* Use `as.bactid` to get an ID of a microorganism. The IDs are quite obvious - the ID of *E. coli* is "ESCCOL" and the ID of *S. aureus* is "STAAUR". This `as.bactid` function takes almost any text as input that looks like the name or code of a microorganism like "E. coli", "esco" and "esccol". Even `as.bactid("MRSA")` will return the ID of *S. aureus*. Moreover, it can group all coagulase negative and positive *Staphylococci*, and can transform *Streptococci* into Lancefield groups. To find bacteria based on your input, this package contains a freely available database of ~2,650 different (potential) human pathogenic microorganisms.
* Use `as.rsi` to transform values to valid antimicrobial results. It produces just S, I or R based on your input and warns about invalid values. Even values like "<=0.002; S" (combined MIC/RSI) will result in "S".
* Use `as.mic` to cleanse your MIC values. It produces a so-called factor (in SPSS calls this *ordinal*) with valid MIC values as levels. A value like "<=0.002; S" (combined MIC/RSI) will result in "<=0.002".
* Use `as.atc` to get the ATC code of an antibiotic as defined by the WHO. This package contains a database with most LIS codes, official names, DDDs and even trade names of antibiotics. For example, the values "Furabid", "Furadantine", "nitro" will return the ATC code of Nitrofurantoine.
* Use `as.mic` to cleanse your MIC values. It produces a so-called factor (called *ordinal* in SPSS) with valid MIC values as levels. A value like "<=0.002; S" (combined MIC/RSI) will result in "<=0.002".
* Use `as.atc` to get the ATC code of an antibiotic as defined by the WHO. This package contains a database with most LIS codes, official names, DDDs and even trade names of antibiotics. For example, the values "Furabid", "Furadantine", "nitro" all return the ATC code of Nitrofurantoine.
2. It **enhances existing data** and **adds new data** from data sets included in this package.
* Use `EUCAST_rules` to apply [EUCAST expert rules to isolates](http://www.eucast.org/expert_rules_and_intrinsic_resistance/).
* Use `MDRO` (abbreviation of Multi Drug Resistant Organisms) to check your isolates for exceptional resistance with country-specific guidelines with or EUCAST rules. Currently, national guidelines for Germany and the Netherlands are supported.
* Data set `microorganisms` contains the family, genus, species, subspecies, colloqual name and Gram stain of almost 2500 microorganisms. This enables e.g. resistance analysis of different antibiotics per Gram stain.
* Data set `antibiotics` contains the ATC code, LIS codes, official name, trivial name, trade name and DDD of both oral and parenteral administration.
* Use `first_isolate` to identify the first isolates of every patient [using guidelines from the CLSI](https://clsi.org/standards/products/microbiology/documents/m39/) (Clinical and Laboratory Standards Institute). * You can also identify first *weighted* isolates of every patient, an adjusted version of the CLSI guideline. This takes into account key antibiotics of every strain and compares them.
* Use `first_isolate` to identify the first isolates of every patient [using guidelines from the CLSI](https://clsi.org/standards/products/microbiology/documents/m39/) (Clinical and Laboratory Standards Institute).
* You can also identify first *weighted* isolates of every patient, an adjusted version of the CLSI guideline. This takes into account key antibiotics of every strain and compares them.
* Use `MDRO` (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.
* The data set `microorganisms` contains the family, genus, species, subspecies, colloquial name and Gram stain of almost 2,650 microorganisms (2,207 bacteria, 285 fungi/yeasts, 153 parasites, 1 other). This enables resistance analysis of e.g. different antibiotics per Gram stain. The package also contains functions to look up values in this data set. For example, to get properties of a bacteria ID, use `mo_genus`, `mo_family` or `mo_gramstain`. These functions can be used to add new variables to your data.
* The data set `antibiotics` contains the ATC code, LIS codes, official name, trivial name, trade name and DDD of both oral and parenteral administration.
3. It **analyses the data** with convenient functions that use well-known methods.
* Calculate the resistance (and even co-resistance) of microbial isolates with the `portion_R`, `portion_IR`, `portion_I`, `portion_SI` and `portion_S` functions, that can also be used with the `dplyr` package (e.g. in conjunction with `summarise`)
* Calculate the resistance (and even co-resistance) of microbial isolates with the `portion_R`, `portion_IR`, `portion_I`, `portion_SI` and `portion_S` functions. Similarly, the *amount* of isolates can be determined with the `count_R`, `count_IR`, `count_I`, `count_SI` and `count_S` functions. All these functions can be used [with the `dplyr` package](https://dplyr.tidyverse.org/#usage) (e.g. in conjunction with [`summarise`](https://dplyr.tidyverse.org/reference/summarise.html))
* Plot AMR results with `geom_rsi`, a function made for the `ggplot2` package
* Predict antimicrobial resistance for the nextcoming years using logistic regression models with the `resistance_predict` function
* Conduct descriptive statistics to enhance base R: calculate kurtosis, skewness and create frequency tables
4. It **teaches the user** how to use all the above actions, by showing many examples in the help pages. The package contains an example data set called `septic_patients`. This data set, consisting of 2000 blood culture isolates from anonymised septic patients between 2001 and 2017 in the Northern Netherlands, is real and genuine data.
4. It **teaches the user** how to use all the above actions.
* The package contains extensive help pages with many examples.
* It also contains an example data set called `septic_patients`. This data set contains:
* 2,000 blood culture isolates from anonymised septic patients between 2001 and 2017 in the Northern Netherlands
* Results of 40 antibiotics (each antibiotic in its own column) with a total of 38,414 antimicrobial results
* Real and genuine data
## How to get it?
All versions of this package [are published on CRAN](http://cran.r-project.org/package=AMR), the official R network with a peer-reviewed submission process.
@ -82,13 +89,17 @@ All versions of this package [are published on CRAN](http://cran.r-project.org/p
- `install.packages("AMR")`
### Install from GitHub
This is the latest development version. Although it may contain bugfixes and even new functions compared to the latest released version on CRAN, it is also subject to change and may be unstable or behave unexpectedly. Always consider this a beta version.
[![Travis_Build](https://travis-ci.org/msberends/AMR.svg?branch=master)](https://travis-ci.org/msberends/AMR)
[![AppVeyor_Build](https://ci.appveyor.com/api/projects/status/github/msberends/AMR?branch=master&svg=true)](https://ci.appveyor.com/project/msberends/AMR)
[![Last_Commit](https://img.shields.io/github/last-commit/msberends/AMR.svg)](https://github.com/msberends/AMR/commits/master)
[![Code_Coverage](https://codecov.io/gh/msberends/AMR/branch/master/graph/badge.svg)](https://codecov.io/gh/msberends/AMR)
This is the latest development version. Although it may contain bugfixes and even new functions compared to the latest released version on CRAN, it is also subject to change and may be unstable or behave unexpectedly. Always consider this a beta version. All below 'badges' should be green.
Development Test | Result
--- | :---:
Works on Linux and macOS | [![Travis_Build](https://travis-ci.org/msberends/AMR.svg?branch=master)](https://travis-ci.org/msberends/AMR)
Works on Windows | [![AppVeyor_Build](https://ci.appveyor.com/api/projects/status/github/msberends/AMR?branch=master&svg=true)](https://ci.appveyor.com/project/msberends/AMR)
Syntax lines checked | [![Code_Coverage](https://codecov.io/gh/msberends/AMR/branch/master/graph/badge.svg)](https://codecov.io/gh/msberends/AMR)
If so, try it with:
```r
install.packages("devtools")
devtools::install_github("msberends/AMR")
@ -210,7 +221,7 @@ before
# 4 KLEPNE - - - - -
# 5 PSEAER - - - - -
# Now apply those rules; just need a column with bacteria ID's and antibiotic results:
# Now apply those rules; just need a column with bacteria IDs and antibiotic results:
after <- EUCAST_rules(before)
after
# bactid vanc amox coli cfta cfur
@ -221,7 +232,7 @@ after
# 5 PSEAER R R - - R
```
Bacteria ID's can be retrieved with the `guess_bactid` function. It uses any type of info about a microorganism as input. For example, all these will return value `STAAUR`, the ID of *S. aureus*:
Bacteria IDs can be retrieved with the `guess_bactid` function. It uses any type of info about a microorganism as input. For example, all these will return value `STAAUR`, the ID of *S. aureus*:
```r
guess_bactid("stau")
guess_bactid("STAU")
@ -371,7 +382,7 @@ Datasets to work with antibiotics and bacteria properties.
septic_patients # A tibble: 2,000 x 49
# Dataset with ATC antibiotics codes, official names, trade names
# and DDD's (oral and parenteral)
# and DDDs (oral and parenteral)
antibiotics # A tibble: 420 x 18
# Dataset with bacteria codes and properties like gram stain and

Binary file not shown.

Binary file not shown.

45
man/ab_property.Rd Normal file
View File

@ -0,0 +1,45 @@
% 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_official_nl}
\alias{ab_trivial_nl}
\alias{ab_certe}
\alias{ab_umcg}
\title{Property of an antibiotic}
\usage{
ab_property(x, property = "official")
ab_atc(x)
ab_official(x)
ab_official_nl(x)
ab_trivial_nl(x)
ab_certe(x)
ab_umcg(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"}}
}
\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}}.
}
\examples{
ab_atc("amcl") # J01CR02
ab_official("amcl") # Amoxicillin and beta-lactamase inhibitor
ab_official_nl("amcl") # Amoxicilline met enzymremmer
ab_trivial_nl("amcl") # Amoxicilline/clavulaanzuur
ab_certe("amcl") # amcl
ab_umcg("amcl") # AMCL
}
\seealso{
\code{\link{antibiotics}}
}

View File

@ -9,11 +9,11 @@
\item{\code{atc}}{ATC code, like \code{J01CR02}}
\item{\code{certe}}{Certe code, like \code{amcl}}
\item{\code{umcg}}{UMCG code, like \code{AMCL}}
\item{\code{abbr}}{Abbreviation as used by many countries, to be used for \code{\link{guess_atc}}}
\item{\code{official}}{Official name by the WHO, like \code{"Amoxicillin and enzyme inhibitor"}}
\item{\code{abbr}}{Abbreviation as used by many countries, used internally by \code{\link{as.atc}}}
\item{\code{official}}{Official name by the WHO, like \code{"Amoxicillin and beta-lactamase inhibitor"}}
\item{\code{official_nl}}{Official name in the Netherlands, like \code{"Amoxicilline met enzymremmer"}}
\item{\code{trivial_nl}}{Trivial name in Dutch, like \code{"Amoxicilline/clavulaanzuur"}}
\item{\code{trade_name}}{Trade name as used by many countries, to be used for \code{\link{guess_atc}}}
\item{\code{trade_name}}{Trade name as used by many countries, used internally by \code{\link{as.atc}}}
\item{\code{oral_ddd}}{Defined Daily Dose (DDD), oral treatment}
\item{\code{oral_units}}{Units of \code{ddd_units}}
\item{\code{iv_ddd}}{Defined Daily Dose (DDD), parenteral treatment}

View File

@ -23,6 +23,8 @@ Character (vector) with class \code{"act"}. Unknown values will return \code{NA}
Use this function to determine the ATC code of one or more antibiotics. The dataset \code{\link{antibiotics}} will be searched for abbreviations, official names and trade names.
}
\details{
Use the \code{\link{ab_property}} functions to get properties based on the returned ATC code, see Examples.
In the ATC classification system, the active substances are classified in a hierarchy with five different levels. The system has fourteen main anatomical/pharmacological groups or 1st levels. Each ATC main group is divided into 2nd levels which could be either pharmacological or therapeutic groups. The 3rd and 4th levels are chemical, pharmacological or therapeutic subgroups and the 5th level is the chemical substance. The 2nd, 3rd and 4th levels are often used to identify pharmacological subgroups when that is considered more appropriate than therapeutic or chemical subgroups.
Source: \url{https://www.whocc.no/atc/structure_and_principles/}
}
@ -36,6 +38,11 @@ as.atc("ERY")
as.atc("Erythrocin") # Trade name
as.atc("Eryzole") # Trade name
as.atc("Pediamycin") # Trade name
# Use ab_* functions to get a specific property based on an ATC code
Cipro <- as.atc("cipro") # returns `J01MA02`
ab_official(Cipro) # returns "Ciprofloxacin"
ab_umcg(Cipro) # returns "CIPR", the code used in the UMCG
}
\seealso{
\code{\link{antibiotics}} for the dataframe that is being used to determine ATC's.

View File

@ -2,6 +2,7 @@
% Please edit documentation in R/bactid.R
\name{as.bactid}
\alias{as.bactid}
\alias{bactid}
\alias{guess_bactid}
\alias{is.bactid}
\title{Transform to bacteria ID}
@ -34,6 +35,8 @@ Use this function to determine a valid ID based on a genus (and species). This i
\details{
\code{guess_bactid} is an alias of \code{as.bactid}.
Use the \code{\link{mo_property}} functions to get properties based on the returned bactid, see Examples.
Some exceptions have been built in to get more logical results, based on prevalence of human pathogens. These are:
\itemize{
\item{\code{"E. coli"} will return the ID of \emph{Escherichia coli} and not \emph{Entamoeba coli}, although the latter would alphabetically come first}
@ -56,12 +59,18 @@ as.bactid("MRSA") # Methicillin Resistant S. aureus
as.bactid("VISA") # Vancomycin Intermediate S. aureus
as.bactid("VRSA") # Vancomycin Resistant S. aureus
# guess_bactid is an alias of as.bactid and works the same
guess_bactid("S. epidermidis") # will remain species: STAEPI
guess_bactid("S. epidermidis", Becker = TRUE) # will not remain species: STACNS
guess_bactid("S. pyogenes") # will remain species: STCAGA
guess_bactid("S. pyogenes", Lancefield = TRUE) # will not remain species: STCGRA
# Use mo_* functions to get a specific property based on a bactid
Ecoli <- as.bactid("E. coli") # returns `ESCCOL`
mo_genus(Ecoli) # returns "Escherichia"
mo_gramstain(Ecoli) # returns "Negative rods"
\dontrun{
df$bactid <- as.bactid(df$microorganism_name)

View File

@ -1,27 +0,0 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/atc.R
\name{atc.property}
\alias{atc.property}
\alias{atc.official}
\alias{atc.official_nl}
\alias{atc.trivial_nl}
\alias{atc.certe}
\alias{atc.umcg}
\title{Get antibiotic property based on ATC}
\usage{
atc.official(atc)
atc.official_nl(atc)
atc.trivial_nl(atc)
atc.certe(atc)
atc.umcg(atc)
}
\arguments{
\item{atc}{a valid ATC code, created with \code{\link{as.atc}}}
}
\description{
Use these functions to return a specific property of an antibiotic from the \code{\link{antibiotics}} data set, based on their ATC code.
}

View File

@ -1,42 +0,0 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/bactid.R
\name{bactid.property}
\alias{bactid.property}
\alias{bactid.family}
\alias{bactid.genus}
\alias{bactid.species}
\alias{bactid.subspecies}
\alias{bactid.fullname}
\alias{bactid.type}
\alias{bactid.gramstain}
\alias{bactid.aerobic}
\alias{bactid.type_nl}
\alias{bactid.gramstain_nl}
\title{Get microbial property based on `bactid`}
\usage{
bactid.family(bactid)
bactid.genus(bactid)
bactid.species(bactid)
bactid.subspecies(bactid)
bactid.fullname(bactid)
bactid.type(bactid)
bactid.gramstain(bactid)
bactid.aerobic(bactid)
bactid.type_nl(bactid)
bactid.gramstain_nl(bactid)
}
\arguments{
\item{bactid}{a valid bactid code, created with \code{\link{as.bactid}}}
}
\description{
Use these functions to return a specific property of a microorganism from the \code{\link{microorganisms}} data set, based on their \code{bactid}. Get such an ID with \code{\link{as.bactid}}.
}

View File

@ -3,8 +3,8 @@
\docType{data}
\name{microorganisms}
\alias{microorganisms}
\title{Dataset with ~2500 microorganisms}
\format{A data.frame with 2464 observations and 12 variables:
\title{Dataset with ~2650 microorganisms}
\format{A data.frame with 2,646 observations and 12 variables:
\describe{
\item{\code{bactid}}{ID of microorganism}
\item{\code{bactsys}}{Bactsyscode of microorganism}
@ -23,7 +23,7 @@
microorganisms
}
\description{
A dataset containing 2464 microorganisms. MO codes of the UMCG can be looked up using \code{\link{microorganisms.umcg}}.
A dataset containing 2,646 microorganisms. MO codes of the UMCG can be looked up using \code{\link{microorganisms.umcg}}.
}
\seealso{
\code{\link{guess_bactid}} \code{\link{antibiotics}} \code{\link{microorganisms.umcg}}

88
man/mo_property.Rd Normal file
View File

@ -0,0 +1,88 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/mo_property.R
\name{mo_property}
\alias{mo_property}
\alias{mo_family}
\alias{mo_genus}
\alias{mo_species}
\alias{mo_subspecies}
\alias{mo_fullname}
\alias{mo_type}
\alias{mo_gramstain}
\alias{mo_aerobic}
\alias{mo_type_nl}
\alias{mo_gramstain_nl}
\title{Property of a microorganism}
\usage{
mo_property(x, property = "fullname")
mo_family(x)
mo_genus(x)
mo_species(x)
mo_subspecies(x)
mo_fullname(x)
mo_type(x)
mo_gramstain(x)
mo_aerobic(x)
mo_type_nl(x)
mo_gramstain_nl(x)
}
\arguments{
\item{x}{a (vector of a) valid \code{\link{bactid}} or any text that can be coerced to a valid bactid with \code{\link{as.bactid}}}
\item{property}{one of the column names of one of the \code{\link{microorganisms}} data set, like \code{"bactid"}, \code{"bactsys"}, \code{"family"}, \code{"genus"}, \code{"species"}, \code{"fullname"}, \code{"gramstain"} and \code{"aerobic"}}
}
\description{
Use these functions to return a specific property of a microorganism from the \code{\link{microorganisms}} data set, based on their \code{bactid}. Get such an ID with \code{\link{as.bactid}}.
}
\examples{
# All properties
mo_family("E. coli") # Enterobacteriaceae
mo_genus("E. coli") # Escherichia
mo_species("E. coli") # coli
mo_subspecies("E. coli") # <NA>
mo_fullname("E. coli") # Escherichia coli
mo_type("E. coli") # Bacteria
mo_gramstain("E. coli") # Negative rods
mo_aerobic("E. coli") # TRUE
mo_type_nl("E. coli") # Bacterie
mo_gramstain_nl("E. coli") # Negatieve staven
# Abbreviations known in the field
mo_genus("EHEC") # Escherichia
mo_species("EHEC") # coli
mo_subspecies("EHEC") # EHEC
mo_fullname("EHEC") # Escherichia coli (EHEC)
mo_genus("MRSA") # Staphylococcus
mo_species("MRSA") # aureus
mo_gramstain("MRSA") # Positive cocci
mo_genus("VISA") # Staphylococcus
mo_species("VISA") # aureus
# Known subspecies
mo_genus("doylei") # Campylobacter
mo_species("doylei") # jejuni
mo_fullname("doylei") # Campylobacter jejuni (doylei)
# Anaerobic bacteria
mo_genus("B. fragilis") # Bacteroides
mo_species("B. fragilis") # fragilis
mo_aerobic("B. fragilis") # FALSE
}
\seealso{
\code{\link{microorganisms}}
}

View File

@ -0,0 +1,9 @@
context("ab_property.R")
test_that("ab_property works", {
expect_equal(ab_certe("amox"), "amox")
expect_equal(ab_official("amox"), "Amoxicillin")
expect_equal(ab_official_nl("amox"), "Amoxicilline")
expect_equal(ab_trivial_nl("amox"), "Amoxicilline")
expect_equal(ab_umcg("amox"), "AMOX")
})

View File

@ -34,13 +34,8 @@ test_that("guess_atc works", {
expect_identical(class(as.atc("amox")), "atc")
# first 5 chars of official name
expect_equal(as.character(as.atc(c("nitro", "cipro"))),
c("J01XE01", "J01MA02"))
})
test_that("atc.property works", {
expect_equal(atc.certe("J01CA04"), "amox")
expect_equal(atc.umcg("J01CA04"), "AMOX")
expect_equal(atc.official("J01CA04"), "Amoxicillin")
expect_equal(atc.official_nl("J01CA04"), "Amoxicilline")
expect_equal(atc.trivial_nl("J01CA04"), "Amoxicilline")
})

View File

@ -108,16 +108,3 @@ test_that("as.bactid works", {
NA_character_)
})
test_that("bactid.property works", {
expect_equal(bactid.family("E. coli"), "Enterobacteriaceae")
expect_equal(bactid.genus("E. coli"), "Escherichia")
expect_equal(bactid.species("E. coli"), "coli")
expect_equal(bactid.subspecies("E. coli"), NA_character_)
expect_equal(bactid.fullname("E. coli"), "Escherichia coli")
expect_equal(bactid.type("E. coli"), "Bacteria")
expect_equal(bactid.gramstain("E. coli"), "Negative rods")
expect_equal(bactid.aerobic("E. coli"), TRUE)
expect_equal(bactid.type_nl("E. coli"), "Bacterie")
expect_equal(bactid.gramstain_nl("E. coli"), "Negatieve staven")
})

View File

@ -9,10 +9,11 @@ test_that("clipboard works", {
skip_if_not(clipr::clipr_available())
clipboard_export(antibiotics)
imp <- clipboard_import()
expect_identical(as.data.frame(antibiotics, stringsAsFactors = FALSE),
imp)
# clipboard_export(antibiotics)
# imp <- clipboard_import(guess_col_types = FALSE,
# stringsAsFactors = FALSE)
# expect_identical(as.data.frame(antibiotics, stringsAsFactors = FALSE),
# imp)
clipboard_export(septic_patients[1:100,])
imp <- clipboard_import(guess_col_types = TRUE,

View File

@ -0,0 +1,14 @@
context("mo_property.R")
test_that("mo_property works", {
expect_equal(mo_family("E. coli"), "Enterobacteriaceae")
expect_equal(mo_genus("E. coli"), "Escherichia")
expect_equal(mo_species("E. coli"), "coli")
expect_equal(mo_subspecies("E. coli"), NA_character_)
expect_equal(mo_fullname("E. coli"), "Escherichia coli")
expect_equal(mo_type("E. coli"), "Bacteria")
expect_equal(mo_gramstain("E. coli"), "Negative rods")
expect_equal(mo_aerobic("E. coli"), TRUE)
expect_equal(mo_type_nl("E. coli"), "Bacterie")
expect_equal(mo_gramstain_nl("E. coli"), "Negatieve staven")
})