diff --git a/.Rbuildignore b/.Rbuildignore index 51c54326..fad9f2b1 100755 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -4,3 +4,4 @@ .zenodo.json ^cran-comments\.md$ ^appveyor\.yml$ +_noinclude diff --git a/.gitignore b/.gitignore index 304c2613..eba10c58 100755 --- a/.gitignore +++ b/.gitignore @@ -9,6 +9,7 @@ inst/doc /src/*.o-* /src/*.d /src/*.so +_noinclude *.dll vignettes/*.R .DS_Store diff --git a/DESCRIPTION b/DESCRIPTION index 8003e2cf..3c5f55ad 100755 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR Version: 0.3.0.9005 -Date: 2018-08-28 +Date: 2018-08-29 Title: Antimicrobial Resistance Analysis Authors@R: c( person( diff --git a/NAMESPACE b/NAMESPACE index 267b9542..6f5d359c 100755 --- a/NAMESPACE +++ b/NAMESPACE @@ -41,6 +41,7 @@ export(ab_certe) export(ab_official) export(ab_official_nl) export(ab_property) +export(ab_tradenames) export(ab_trivial_nl) export(ab_umcg) export(abname) diff --git a/NEWS.md b/NEWS.md index 59a41c6d..1d940162 100755 --- a/NEWS.md +++ b/NEWS.md @@ -2,14 +2,25 @@ #### New * Functions `count_R`, `count_IR`, `count_I`, `count_SI` and `count_S` to selectively count resistant or susceptible isolates - * 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 + * Extra function `count_df` (which works like `portion_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`. * 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` +* Introduction to AMR as a vignette #### Changed -* Added 182 microorganisms to the `microorganisms` data set, now n = 2,646 (2,207 bacteria, 285 fungi/yeasts, 153 parasites, 1 other) +* Added 182 microorganisms to the `microorganisms` data set, now *n* = 2,646 (2,207 bacteria, 285 fungi/yeasts, 153 parasites, 1 other) +* Added three antimicrobial agents to the `antibiotics` data set: Terbinafine (D01BA02), Rifaximin (A07AA11) and Isoconazole (D01AC05) +* Added 163 trade names to the `antibiotics` data set, it now contains 298 different trade names in total, e.g.: + ```r + ab_official("Bactroban") + # [1] "Mupirocin" + ab_official(c("Bactroban", "Amoxil", "Zithromax", "Floxapen")) + # [1] "Mupirocin" "Amoxicillin" "Azithromycin" "Flucloxacillin" + ab_atc(c("Bactroban", "Amoxil", "Zithromax", "Floxapen")) + # [1] "R01AX06" "J01CA04" "J01FA10" "J01CF05" + ``` * 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` diff --git a/R/ab_property.R b/R/ab_property.R index 963e4916..a29ca321 100644 --- a/R/ab_property.R +++ b/R/ab_property.R @@ -22,6 +22,7 @@ #' @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 +#' @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. #' @export #' @importFrom dplyr %>% left_join pull #' @seealso \code{\link{antibiotics}} @@ -82,3 +83,16 @@ ab_certe <- function(x) { ab_umcg <- function(x) { ab_property(x, "umcg") } + +#' @rdname ab_property +#' @export +ab_tradenames <- function(x) { + res <- ab_property(x, "trade_name") + res <- strsplit(res, "|", fixed = TRUE) + if (length(x) == 1) { + res <- unlist(res) + } else { + names(res) <- x + } + res +} diff --git a/R/abname.R b/R/abname.R index 2086b035..7105ba75 100644 --- a/R/abname.R +++ b/R/abname.R @@ -23,6 +23,7 @@ #' @param from,to type to transform from and to. See \code{\link{antibiotics}} for its column names. WIth \code{from = "guess"} the from will be guessed from \code{"atc"}, \code{"certe"} and \code{"umcg"}. When using \code{to = "atc"}, the ATC code will be searched using \code{\link{as.atc}}. #' @param textbetween text to put between multiple returned texts #' @param tolower return output as lower case with function \code{\link{tolower}}. +#' @details \strong{The \code{\link{ab_property}} functions are faster and more concise}, but do not support concatenated strings, like \code{abname("AMCL+GENT"}. #' @keywords ab antibiotics #' @source \code{\link{antibiotics}} #' @export @@ -100,29 +101,29 @@ abname <- function(abcode, } if (from %in% c("atc", "guess")) { if (abcode[i] %in% abx$atc) { - abcode[i] <- abx[which(abx$atc == abcode[i]),] %>% pull(to) + abcode[i] <- abx[which(abx$atc == abcode[i]),] %>% pull(to) %>% .[1] next } } if (from %in% c("certe", "guess")) { if (abcode[i] %in% abx$certe) { - abcode[i] <- abx[which(abx$certe == abcode[i]),] %>% pull(to) + abcode[i] <- abx[which(abx$certe == abcode[i]),] %>% pull(to) %>% .[1] next } } if (from %in% c("umcg", "guess")) { if (abcode[i] %in% abx$umcg) { - abcode[i] <- abx[which(abx$umcg == abcode[i]),] %>% pull(to) + abcode[i] <- abx[which(abx$umcg == abcode[i]),] %>% pull(to) %>% .[1] next } } if (from %in% c("trade_name", "guess")) { if (abcode[i] %in% abx$trade_name) { - abcode[i] <- abx[which(abx$trade_name == abcode[i]),] %>% pull(to) + abcode[i] <- abx[which(abx$trade_name == abcode[i]),] %>% pull(to) %>% .[1] next } if (sum(abx$trade_name %like% abcode[i]) > 0) { - abcode[i] <- abx[which(abx$trade_name %like% abcode[i]),] %>% pull(to) + abcode[i] <- abx[which(abx$trade_name %like% abcode[i]),] %>% pull(to) %>% .[1] next } } diff --git a/R/atc.R b/R/atc.R index f1396104..dd1a41a9 100755 --- a/R/atc.R +++ b/R/atc.R @@ -64,6 +64,13 @@ as.atc <- function(x) { x.new[is.na(x.new) & x.bak == x[i]] <- found[1L] } + # try ATC in code form, even if it does not exist in the antibiotics data set YET + if (length(found) == 0 & x[i] %like% '[A-Z][0-9][0-9][A-Z][A-Z][0-9][0-9]') { + warning("ATC code ", x[i], " is not yet in the `antibiotics` data set.") + fail <- FALSE + x.new[is.na(x.new) & x.bak == x[i]] <- x[i] + } + # try abbreviation of certe and glims found <- AMR::antibiotics[which(tolower(AMR::antibiotics$certe) == tolower(x[i])),]$atc if (length(found) > 0) { @@ -83,6 +90,13 @@ as.atc <- function(x) { x.new[is.na(x.new) & x.bak == x[i]] <- found[1L] } + # try exact official Dutch + found <- AMR::antibiotics[which(tolower(AMR::antibiotics$official_nl) == tolower(x[i])),]$atc + if (length(found) > 0) { + fail <- FALSE + x.new[is.na(x.new) & x.bak == x[i]] <- found[1L] + } + # try trade name found <- AMR::antibiotics[which(paste0("(", AMR::antibiotics$trade_name, ")") %like% x[i]),]$atc if (length(found) > 0) { diff --git a/R/bactid.R b/R/bactid.R index b94b7173..410a1a66 100644 --- a/R/bactid.R +++ b/R/bactid.R @@ -205,12 +205,12 @@ as.bactid <- function(x, Becker = FALSE, Lancefield = FALSE) { failures <- c(failures, x_backup[i]) next } - if (x_backup[i] %in% MOs$bactid) { + if (x_backup[i] %in% AMR::microorganisms$bactid) { # is already a valid bactid x[i] <- x_backup[i] next } - if (x_trimmed[i] %in% MOs$bactid) { + if (x_trimmed[i] %in% AMR::microorganisms$bactid) { # is already a valid bactid x[i] <- x_trimmed[i] next diff --git a/R/data.R b/R/data.R index 3b322e68..2193704b 100755 --- a/R/data.R +++ b/R/data.R @@ -16,10 +16,10 @@ # GNU General Public License for more details. # # ==================================================================== # -#' Dataset with 420 antibiotics +#' Dataset with 423 antibiotics #' -#' A dataset containing all antibiotics with a J0 code, with their DDD's. Properties were downloaded from the WHO, see Source. -#' @format A data.frame with 420 observations and 18 variables: +#' A dataset containing all antibiotics with a J0 code and some other antimicrobial agents, with their DDD's. Except for trade names and abbreviations, all properties were downloaded from the WHO, see Source. +#' @format A data.frame with 423 observations and 18 variables: #' \describe{ #' \item{\code{atc}}{ATC code, like \code{J01CR02}} #' \item{\code{certe}}{Certe code, like \code{amcl}} @@ -28,7 +28,7 @@ #' \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, used internally by \code{\link{as.atc}}} +#' \item{\code{trade_name}}{Trade name as used by many countries (a total of 294), 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} @@ -61,177 +61,7 @@ # paste() %>% # .[. %like% "StringValueList"] %>% # gsub("[]", "", .) -# abbr and trade_name created with: -# https://hs.unr.edu/Documents/dhs/chs/NVPHTC/antibiotic_refeference_guide.pdf -# antibiotics %>% -# mutate(abbr = -# case_when( -# official == 'Amikacin' ~ 'Ak|AN|AMI|AMK', -# official == 'Amoxicillin' ~ 'AMX|AMOX|AC', -# official == 'Amoxicillin and beta-lactamase inhibitor' ~ 'AUG|A/C|XL|AML', -# official == 'Ampicillin' ~ 'AM|AMP', -# official == 'Ampicillin and beta-lactamase inhibitor' ~ 'A/S|SAM|AMS|AB', -# official == 'Azithromycin' ~ 'Azi|AZM|AZ', -# official == 'Azlocillin' ~ 'AZ|AZL', -# official == 'Aztreonam' ~ 'Azt|ATM|AT|AZM', -# official == 'Carbenicillin' ~ 'Cb|BAR', -# official == 'Cefaclor' ~ 'Ccl|CEC|Cfr|FAC|CF', -# official == 'Cefadroxil' ~ 'CFR|FAD', -# official == 'Cefazolin' ~ 'Cfz|CZ|FAZ|KZ', -# official == 'Cefdinir' ~ 'Cdn|CDR|DIN|CD|CFD', -# official == 'Cefditoren' ~ 'CDN', -# official == 'Cefepime' ~ 'Cpe|FEP|PM|CPM', -# official == 'Cefixime' ~ 'Cfe|DCFM|FIX|IX', -# official == 'Cefoperazone' ~ 'Cfp|CPZ|PER|FOP|CP', -# official == 'Cefotaxime' ~ 'Cft|CTX|TAX|FOT|CT', -# official == 'Cefotetan' ~ 'Ctn|CTT|CTE|TANS|CN', -# official == 'Cefoxitin' ~ 'Cfx|FOX|CX|FX', -# official == 'Cefpodoxime' ~ 'Cpd|POD|PX', -# official == 'Cefprozil' ~ 'Cpz|CPR|FP', -# official == 'Ceftaroline' ~ 'CPT', -# official == 'Ceftazidime' ~ 'Caz|TAZ|TZ', -# official == 'Ceftibuten' ~ 'CTB|TIB|CB', -# official == 'Ceftizoxime' ~ 'Cz|ZOX|CZX|CZ|CTZ|TIZ', -# official == 'Ceftriaxone' ~ 'Cax|CRO|CTR|FRX|AXO|TX', -# official == 'Cefuroxime' ~ 'Crm|CXM|CFX|ROX|FUR|XM', -# official == 'Cephalexin' ~ 'CN|LX|CFL', -# official == 'Cephalothin' ~ 'Cf', -# official == 'Chloramphenicol' ~ 'C|CHL|CL', -# official == 'Ciprofloxacin' ~ 'Cp|CIP|CI', -# official == 'Clarithromycin' ~ 'Cla|CLR|CLM|CH', -# official == 'Clindamycin' ~ 'Cd|CC|CM|CLI|DA', -# official == 'Colistin' ~ 'CL|CS|CT', -# official == 'Daptomycin' ~ 'Dap', -# official == 'Doxycycline' ~ 'Dox', -# official == 'Doripenem' ~ 'DOR|Dor', -# official == 'Ertapenem' ~ 'Etp', -# official == 'Erythromycin' ~ 'E|ERY|EM', -# official == 'Fosfomycin' ~ 'FOS|FF|FO|FM', -# official == 'Flucloxacillin' ~ 'CLOX', -# official == 'Gentamicin' ~ 'Gm|CN|GEN', -# official == 'Imipenem' ~ 'Imp|IPM|IMI|IP', -# official == 'Kanamycin' ~ 'K|KAN|HLK|KM', -# official == 'Levofloxacin' ~ 'Lvx|LEV|LEVO|LE', -# official == 'Linezolid' ~ 'Lzd|LNZ|LZ', -# official == 'Lomefloxacin' ~ 'Lmf|LOM', -# official == 'Meropenem' ~ 'Mer|MEM|MERO|MRP|MP', -# official == 'Metronidazole' ~ 'MNZ', -# official == 'Mezlocillin' ~ 'Mz|MEZ', -# official == 'Minocycline' ~ 'Min|MI|MN|MNO|MC|MH', -# official == 'Moxifloxacin' ~ 'Mox|MXF', -# official == 'Mupirocin' ~ 'MUP', -# official == 'Nafcillin' ~ 'Naf|NF', -# official == 'Nalidixic acid' ~ 'NA|NAL', -# official == 'Nitrofurantoin' ~ 'Fd|F/M|FT|NIT|NI|F', -# official == 'Norfloxacin' ~ 'Nxn|NOR|NX', -# official == 'Ofloxacin' ~ 'Ofl|OFX|OF', -# official == 'Oxacillin' ~ 'Ox|OXS|OXA', -# official == 'Benzylpenicillin' ~ 'P|PEN|PV', -# official == 'Penicillins, combinations with other antibacterials' ~ 'P|PEN|PV', -# official == 'Piperacillin' ~ 'Pi|PIP|PP', -# official == 'Piperacillin and beta-lactamase inhibitor' ~ 'PT|TZP|PTZ|P/T|PTc', -# official == 'Polymyxin B' ~ 'PB', -# official == 'Quinupristin/dalfopristin' ~ 'Syn|Q/D|QDA|RP', -# official == 'Rifampin' ~ 'Rif|RA|RI|RD', -# official == 'Spectinomycin' ~ 'SPT|SPE|SC', -# official == 'Streptomycin' ~ 'S|STR', -# official == 'Teicoplanin' ~ 'Tei|TEC|TPN|TP|TPL', -# official == 'Telavancin' ~ 'TLV', -# official == 'Telithromcyin' ~ 'Tel', -# official == 'Tetracycline' ~ 'Te|TET|TC', -# official == 'Ticarcillin' ~ 'Ti|TIC|TC', -# official == 'Ticarcillin and beta-lactamase inhibitor' ~ 'Tim|T/C|TCC|TLc', -# official == 'Tigecycline' ~ 'TGC', -# official == 'Tobramycin' ~ 'To|NN|TM|TOB', -# official == 'Trimethoprim' ~ 'T|TMP|TR|W', -# official == 'Sulfamethoxazole and trimethoprim' ~ 'T/S|SXT|SxT|TS|COT', -# official == 'Vancomycin' ~ 'Va|VAN', -# TRUE ~ NA_character_), -# -# trade_name = -# case_when( -# official == 'Amikacin' ~ 'Amikin', -# official == 'Amoxicillin' ~ 'Amoxil|Dispermox|Larotid|Trimox', -# official == 'Amoxicillin and beta-lactamase inhibitor' ~ 'Augmentin', -# official == 'Ampicillin' ~ 'Pfizerpen-A|Principen', -# official == 'Ampicillin and beta-lactamase inhibitor' ~ 'Unasyn', -# official == 'Azithromycin' ~ 'Zithromax', -# official == 'Azlocillin' ~ 'Azlin', -# official == 'Aztreonam' ~ 'Azactam', -# official == 'Carbenicillin' ~ 'Geocillin', -# official == 'Cefaclor' ~ 'Ceclor', -# official == 'Cefadroxil' ~ 'Duricef', -# official == 'Cefazolin' ~ 'Ancef', -# official == 'Cefdinir' ~ 'Omnicef', -# official == 'Cefditoren' ~ 'Spectracef', -# official == 'Cefepime' ~ 'Maxipime', -# official == 'Cefixime' ~ 'Suprax', -# official == 'Cefoperazone' ~ 'Cefobid', -# official == 'Cefotaxime' ~ 'Claforan', -# official == 'Cefotetan' ~ 'Cefotan', -# official == 'Cefoxitin' ~ 'Mefoxin', -# official == 'Cefpodoxime' ~ 'Vantin', -# official == 'Cefprozil' ~ 'Cefzil', -# official == 'Ceftaroline' ~ 'Teflaro', -# official == 'Ceftazidime' ~ 'Fortaz|Tazicef|Tazidime', -# official == 'Ceftibuten' ~ 'Cedax', -# official == 'Ceftizoxime' ~ 'Cefizox', -# official == 'Ceftriaxone' ~ 'Rocephin', -# official == 'Cefuroxime' ~ 'Ceftin|Zinacef', -# official == 'Cephalexin' ~ 'Keflex|Panixine', -# official == 'Cephalothin' ~ 'Keflin', -# official == 'Chloramphenicol' ~ 'Chloromycetin', -# official == 'Ciprofloxacin' ~ 'Cipro|Ciloxan|Ciproxin', -# official == 'Clarithromycin' ~ 'Biaxin', -# official == 'Clindamycin' ~ 'Cleocin|Clinda-Derm|Clindagel|Clindesse|Clindets|Evoclin', -# official == 'Colistin' ~ 'Coly-Mycin', -# official == 'Daptomycin' ~ 'Cubicin', -# official == 'Doxycycline' ~ 'Doryx|Monodox|Vibramycin|Atridox|Oracea|Periostat|Vibra-Tabs', -# official == 'Doripenem' ~ 'Doribax', -# official == 'Ertapenem' ~ 'Invanz', -# official == 'Erythromycin' ~ 'Eryc|EryPed|Erythrocin|E-Base|E-Glades|E-Mycin|E.E.S.|Ery-Tab|Eryderm|Erygel|Erythra-derm|Eryzole|Pediamycin', -# official == 'Fosfomycin' ~ 'Monurol', -# official == 'Flucloxacillin' ~ 'Flopen|Floxapen|Fluclox|Sesamol|Softapen|Staphylex', -# official == 'Gentamicin' ~ 'Garamycin|Genoptic', -# official == 'Imipenem' ~ 'Primaxin', -# official == 'Kanamycin' ~ 'Kantrex', -# official == 'Levofloxacin' ~ 'Levaquin|Quixin', -# official == 'Linezolid' ~ 'Zyvox', -# official == 'Lomefloxacin' ~ 'Maxaquin', -# official == 'Meropenem' ~ 'Merrem', -# official == 'Metronidazole' ~ 'Flagyl|MetroGel|MetroCream|MetroLotion', -# official == 'Mezlocillin' ~ 'Mezlin', -# official == 'Minocycline' ~ 'Arestin|Solodyn', -# official == 'Moxifloxacin' ~ 'Avelox|Vigamox', -# official == 'Mupirocin' ~ 'Bactroban|Centany', -# official == 'Nafcillin' ~ 'Unipen', -# official == 'Nalidixic acid' ~ 'NegGram', -# official == 'Nitrofurantoin' ~ 'Furadantin|Macrobid|Macrodantin', -# official == 'Norfloxacin' ~ 'Noroxin', -# official == 'Ofloxacin' ~ 'Floxin|Ocuflox|Ophthalmic', -# official == 'Oxacillin' ~ 'Bactocill', -# official == 'Benzylpenicillin' ~ 'Permapen|Pfizerpen|Veetids', -# official == 'Penicillins, combinations with other antibacterials' ~ 'Permapen|Pfizerpen|Veetids', -# official == 'Piperacillin' ~ 'Pipracil', -# official == 'Piperacillin and beta-lactamase inhibitor' ~ 'Zosyn', -# official == 'Polymyxin B' ~ 'Poly-RX', -# official == 'Quinupristin/dalfopristin' ~ 'Synercid', -# official == 'Rifampin' ~ 'Rifadin|Rifamate|Rimactane', -# official == 'Spectinomycin' ~ 'Trobicin', -# official == 'Streptomycin' ~ 'Streptomycin Sulfate', -# official == 'Teicoplanin' ~ 'Targocid', -# official == 'Telavancin' ~ 'Vibativ', -# official == 'Telithromcyin' ~ 'Ketek', -# official == 'Tetracycline' ~ 'Sumycin|Bristacycline|Tetrex', -# official == 'Ticarcillin' ~ 'Ticar', -# official == 'Ticarcillin and beta-lactamase inhibitor' ~ 'Timentin', -# official == 'Tigecycline' ~ 'Tygacil', -# official == 'Tobramycin' ~ 'Tobi|Aktob|Tobre', -# official == 'Trimethoprim' ~ 'Primsol|Proloprim', -# official == 'Sulfamethoxazole and trimethoprim' ~ 'Bactrim|Septra|Sulfatrim', -# official == 'Vancomycin' ~ 'Vancocin|Vancomycin Hydrochloride', -# TRUE ~ NA_character_) -# ) + # last two columns created with: # antibiotics %>% # mutate(useful_gramnegative = @@ -251,21 +81,44 @@ # NA # ) # ) +# +# ADD NEW TRADE NAMES FROM OTHER DATAFRAME +# antibiotics_add_to_property <- function(ab_df, 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") +# } +# +# value <- gsub(ab_df[which(ab_df$atc == atc),] %>% pull("official"), "", value, fixed = TRUE) +# value <- gsub("||", "|", value, fixed = TRUE) +# value <- gsub("[äáàâ]", "a", value) +# value <- gsub("[ëéèê]", "e", value) +# value <- gsub("[ïíìî]", "i", value) +# value <- gsub("[öóòô]", "o", value) +# value <- gsub("[üúùû]", "u", value) +# if (!atc %in% ab_df$atc) { +# message("SKIPPING - UNKNOWN ATC: ", atc) +# } +# if (is.na(value)) { +# message("SKIPPING - VALUE MISSES: ", atc) +# } +# if (atc %in% ab_df$atc & !is.na(value)) { +# current <- ab_df[which(ab_df$atc == atc),] %>% pull(property) +# if (!is.na(current)) { +# value <- paste(current, value, sep = "|") +# } +# value <- strsplit(value, "|", fixed = TRUE) %>% unlist() %>% unique() %>% paste(collapse = "|") +# value <- gsub("||", "|", value, fixed = TRUE) +# # print(value) +# ab_df[which(ab_df$atc == atc), property] <- value +# message("Added ", value, " to ", ab_official(atc), " (", atc, ", ", ab_certe(atc), ")") +# } +# ab_df +# } +# "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 ~2650 microorganisms #' diff --git a/README.md b/README.md index 84e39005..5c3f144b 100755 --- a/README.md +++ b/README.md @@ -42,12 +42,12 @@ 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 functions all use artificial intelligence to get 'more 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 guess results that you would expect: - * 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.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". The 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 (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. + * 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", "Furadantin", "nitro" all return the ATC code of Nitrofurantoine. 2. It **enhances existing data** and **adds new data** from data sets included in this package. @@ -55,8 +55,8 @@ This `AMR` package basically does four important things: * 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. + * 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 like `mo_genus`, `mo_family` or `mo_gramstain`. Since it uses `as.bactid` internally, AI is supported. For example, `mo_genus("MRSA")` and `mo_genus("S. aureus")` will both return `"Staphylococcus"`. 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 and DDD of both oral and parenteral administration. It also contains a total of 298 trade names. Use functions like `ab_official` and `ab_tradenames` to look up values. As the `mo_*` functions use `as.bactid` internally, the `ab_*` functions use `as.atc` internally so it uses AI to guess your expected result. For example, `ab_official("Fluclox")`, `ab_official("Floxapen")` and `ab_official("J01CF05")` will all return `"Flucloxacillin"`. These functions can again be used to add new variables to your data. 3. It **analyses the data** with convenient functions that use well-known methods. diff --git a/data/antibiotics.rda b/data/antibiotics.rda index 5e5e2d51..ce7b7d6b 100755 Binary files a/data/antibiotics.rda and b/data/antibiotics.rda differ diff --git a/man/ab_property.Rd b/man/ab_property.Rd index c7eaad9d..e34fdf7d 100644 --- a/man/ab_property.Rd +++ b/man/ab_property.Rd @@ -8,6 +8,7 @@ \alias{ab_trivial_nl} \alias{ab_certe} \alias{ab_umcg} +\alias{ab_tradenames} \title{Property of an antibiotic} \usage{ ab_property(x, property = "official") @@ -23,12 +24,17 @@ 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"}} } +\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}}. } diff --git a/man/abname.Rd b/man/abname.Rd index 0b22e2e6..e01526b1 100644 --- a/man/abname.Rd +++ b/man/abname.Rd @@ -22,6 +22,9 @@ abname(abcode, from = c("guess", "atc", "certe", "umcg"), \description{ Convert antibiotic codes to a (trivial) antibiotic name or ATC code, or vice versa. This uses the data from \code{\link{antibiotics}}. } +\details{ +\strong{The \code{\link{ab_property}} functions are faster and more concise}, but do not support concatenated strings, like \code{abname("AMCL+GENT"}. +} \examples{ abname("AMCL") # "Amoxicillin and beta-lactamase inhibitor" diff --git a/man/antibiotics.Rd b/man/antibiotics.Rd index 8e413d55..598497fd 100755 --- a/man/antibiotics.Rd +++ b/man/antibiotics.Rd @@ -3,8 +3,8 @@ \docType{data} \name{antibiotics} \alias{antibiotics} -\title{Dataset with 420 antibiotics} -\format{A data.frame with 420 observations and 18 variables: +\title{Dataset with 423 antibiotics} +\format{A data.frame with 423 observations and 18 variables: \describe{ \item{\code{atc}}{ATC code, like \code{J01CR02}} \item{\code{certe}}{Certe code, like \code{amcl}} @@ -13,7 +13,7 @@ \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, used internally by \code{\link{as.atc}}} + \item{\code{trade_name}}{Trade name as used by many countries (a total of 294), 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} @@ -32,7 +32,7 @@ antibiotics } \description{ -A dataset containing all antibiotics with a J0 code, with their DDD's. Properties were downloaded from the WHO, see Source. +A dataset containing all antibiotics with a J0 code and some other antimicrobial agents, with their DDD's. Except for trade names and abbreviations, all properties were downloaded from the WHO, see Source. } \seealso{ \code{\link{microorganisms}} diff --git a/tests/testthat/test-ab_property.R b/tests/testthat/test-ab_property.R index 8d611359..9088cfbf 100644 --- a/tests/testthat/test-ab_property.R +++ b/tests/testthat/test-ab_property.R @@ -6,4 +6,6 @@ test_that("ab_property works", { expect_equal(ab_official_nl("amox"), "Amoxicilline") 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") }) diff --git a/tests/testthat/test-atc.R b/tests/testthat/test-atc.R index c47c75bd..5c09d22a 100755 --- a/tests/testthat/test-atc.R +++ b/tests/testthat/test-atc.R @@ -34,6 +34,10 @@ test_that("guess_atc works", { expect_identical(class(as.atc("amox")), "atc") + expect_identical(ab_trivial_nl("Cefmenoxim"), "Cefmenoxim") + + expect_warning(as.atc("Z00ZZ00")) # not yet available in data set + # first 5 chars of official name expect_equal(as.character(as.atc(c("nitro", "cipro"))), c("J01XE01", "J01MA02")) diff --git a/vignettes/AMR.Rmd b/vignettes/AMR.Rmd index 7cafa85e..2469a031 100755 --- a/vignettes/AMR.Rmd +++ b/vignettes/AMR.Rmd @@ -21,37 +21,42 @@ 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 guess results that you would expect: - * 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 like `mo_genus`, `mo_family` or `mo_gramstain`. Since it uses `as.bactid` internally, AI is supported. For example, `mo_genus("MRSA")` and `mo_genus("S. aureus")` will both return `"Staphylococcus"`. 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 and DDD of both oral and parenteral administration. It also contains a total of 298 trade names. Use functions like `ab_official` and `ab_tradenames` to look up values. As the `mo_*` functions use `as.bactid` internally, the `ab_*` functions use `as.atc` internally so it uses AI to guess your expected result. For example, `ab_official("Fluclox")`, `ab_official("Floxapen")` and `ab_official("J01CF05")` will all return `"Flucloxacillin"`. These functions can again be used to add new variables to your data. + 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 ---- ```{r, echo = FALSE} # this will print "2018" in 2018, and "2018-yyyy" after 2018. -yrs <- c(2018:format(Sys.Date(), "%Y")) -yrs <- c(min(yrs), max(yrs)) -yrs <- paste(unique(yrs), collapse = "-") +yrs <- paste(unique(c(2018, format(Sys.Date(), "%Y"))), collapse = "-") ``` AMR, (c) `r yrs`, `r packageDescription("AMR")$URL` diff --git a/vignettes/freq.R b/vignettes/freq.R deleted file mode 100644 index bb94ee97..00000000 --- a/vignettes/freq.R +++ /dev/null @@ -1,89 +0,0 @@ -## ----setup, include = FALSE, results = 'markup'-------------------------- -knitr::opts_chunk$set( - collapse = TRUE, - comment = "#" -) -library(dplyr) -library(AMR) - -## ---- echo = TRUE, results = 'hide'-------------------------------------- -# just using base R -freq(septic_patients$sex) - -# using base R to select the variable and pass it on with a pipe from the dplyr package -septic_patients$sex %>% freq() - -# do it all with pipes, using the `select` function from the dplyr package -septic_patients %>% - select(sex) %>% - freq() - -# or the preferred way: using a pipe to pass the variable on to the freq function -septic_patients %>% freq(sex) # this also shows 'age' in the title - - -## ---- echo = TRUE-------------------------------------------------------- -freq(septic_patients$sex) - -## ---- echo = TRUE, results = 'hide'-------------------------------------- -my_patients <- septic_patients %>% left_join_microorganisms() - -## ---- echo = TRUE-------------------------------------------------------- -colnames(microorganisms) - -## ---- echo = TRUE-------------------------------------------------------- -dim(septic_patients) -dim(my_patients) - -## ---- echo = TRUE-------------------------------------------------------- -my_patients %>% freq(genus, species) - -## ---- echo = TRUE-------------------------------------------------------- -# # get age distribution of unique patients -septic_patients %>% - distinct(patient_id, .keep_all = TRUE) %>% - freq(age, nmax = 5) - -## ---- echo = TRUE-------------------------------------------------------- -septic_patients %>% - freq(hospital_id) - -## ---- echo = TRUE-------------------------------------------------------- -septic_patients %>% - freq(hospital_id, sort.count = TRUE) - -## ---- echo = TRUE-------------------------------------------------------- -septic_patients %>% - select(amox) %>% - freq() - -## ---- echo = TRUE-------------------------------------------------------- -septic_patients %>% - select(date) %>% - freq(nmax = 5) - -## ---- echo = TRUE-------------------------------------------------------- -my_df <- septic_patients %>% freq(age) -class(my_df) - -## ---- echo = TRUE-------------------------------------------------------- -dim(my_df) - -## ---- echo = TRUE-------------------------------------------------------- -septic_patients %>% - freq(amox, na.rm = FALSE) - -## ---- echo = TRUE-------------------------------------------------------- -septic_patients %>% - freq(hospital_id, row.names = FALSE) - -## ---- echo = TRUE-------------------------------------------------------- -septic_patients %>% - freq(hospital_id, markdown = TRUE) - -## ---- echo = FALSE------------------------------------------------------- -# this will print "2018" in 2018, and "2018-yyyy" after 2018. -yrs <- c(2018:format(Sys.Date(), "%Y")) -yrs <- c(min(yrs), max(yrs)) -yrs <- paste(unique(yrs), collapse = "-") - diff --git a/vignettes/freq.Rmd b/vignettes/freq.Rmd index 0457b42d..fe3ef18a 100755 --- a/vignettes/freq.Rmd +++ b/vignettes/freq.Rmd @@ -181,9 +181,7 @@ septic_patients %>% ---- ```{r, echo = FALSE} # this will print "2018" in 2018, and "2018-yyyy" after 2018. -yrs <- c(2018:format(Sys.Date(), "%Y")) -yrs <- c(min(yrs), max(yrs)) -yrs <- paste(unique(yrs), collapse = "-") +yrs <- paste(unique(c(2018, format(Sys.Date(), "%Y"))), collapse = "-") ``` AMR, (c) `r yrs`, `r packageDescription("AMR")$URL`