massive update for antivirals

This commit is contained in:
dr. M.S. (Matthijs) Berends 2022-11-12 21:34:24 +01:00
parent d2edcf51ad
commit 8fab745ab1
35 changed files with 1728 additions and 169 deletions

View File

@ -1,5 +1,5 @@
Package: AMR
Version: 1.8.2.9047
Version: 1.8.2.9049
Date: 2022-11-12
Title: Antimicrobial Resistance Data Analysis
Description: Functions to simplify and standardise antimicrobial resistance (AMR)

View File

@ -18,19 +18,23 @@ S3method("==",mic)
S3method(">",mic)
S3method(">=",mic)
S3method("[",ab)
S3method("[",av)
S3method("[",disk)
S3method("[",mic)
S3method("[",mo)
S3method("[<-",ab)
S3method("[<-",av)
S3method("[<-",disk)
S3method("[<-",mic)
S3method("[<-",mo)
S3method("[<-",rsi)
S3method("[[",ab)
S3method("[[",av)
S3method("[[",disk)
S3method("[[",mic)
S3method("[[",mo)
S3method("[[<-",ab)
S3method("[[<-",av)
S3method("[[<-",disk)
S3method("[[<-",mic)
S3method("[[<-",mo)
@ -48,6 +52,7 @@ S3method(any,ab_selector)
S3method(any,ab_selector_any_all)
S3method(any,mic)
S3method(as.data.frame,ab)
S3method(as.data.frame,av)
S3method(as.data.frame,mo)
S3method(as.double,mic)
S3method(as.list,custom_eucast_rules)
@ -67,6 +72,7 @@ S3method(barplot,mic)
S3method(barplot,rsi)
S3method(c,ab)
S3method(c,ab_selector)
S3method(c,av)
S3method(c,custom_eucast_rules)
S3method(c,custom_mdro_guideline)
S3method(c,disk)
@ -113,6 +119,7 @@ S3method(plot,mic)
S3method(plot,resistance_predict)
S3method(plot,rsi)
S3method(print,ab)
S3method(print,av)
S3method(print,bug_drug_combinations)
S3method(print,custom_eucast_rules)
S3method(print,custom_mdro_guideline)
@ -127,6 +134,7 @@ S3method(prod,mic)
S3method(quantile,mic)
S3method(range,mic)
S3method(rep,ab)
S3method(rep,av)
S3method(rep,disk)
S3method(rep,mic)
S3method(rep,mo)
@ -153,6 +161,7 @@ S3method(tanpi,mic)
S3method(trigamma,mic)
S3method(trunc,mic)
S3method(unique,ab)
S3method(unique,av)
S3method(unique,disk)
S3method(unique,mic)
S3method(unique,mo)
@ -195,6 +204,7 @@ export(antifungals)
export(antimicrobials_equal)
export(antimycobacterials)
export(as.ab)
export(as.av)
export(as.disk)
export(as.mic)
export(as.mo)
@ -203,6 +213,19 @@ export(atc_online_ddd)
export(atc_online_ddd_units)
export(atc_online_groups)
export(atc_online_property)
export(av_atc)
export(av_cid)
export(av_ddd)
export(av_ddd_units)
export(av_from_text)
export(av_group)
export(av_info)
export(av_loinc)
export(av_name)
export(av_property)
export(av_synonyms)
export(av_tradenames)
export(av_url)
export(availability)
export(betalactams)
export(brmo)
@ -246,6 +269,7 @@ export(glycopeptides)
export(guess_ab_col)
export(inner_join_microorganisms)
export(is.ab)
export(is.av)
export(is.disk)
export(is.mic)
export(is.mo)

25
NEWS.md
View File

@ -1,4 +1,4 @@
# AMR 1.8.2.9047
# AMR 1.8.2.9049
This version will eventually become v2.0! We're happy to reach a new major milestone soon!
@ -8,36 +8,39 @@ This version will eventually become v2.0! We're happy to reach a new major miles
* Chromista are not relevant when it comes to antimicrobial resistance, thus lacking the primary scope of this package
* Chromista are almost never clinically relevant, thus lacking the secondary scope of this package
* The `microorganisms` no longer relies on the Catalogue of Life, but now primarily on the List of Prokaryotic names with Standing in Nomenclature (LPSN) and is supplemented with the Global Biodiversity Information Facility (GBIF). The structure of this data set has changed to include separate LPSN and GBIF identifiers. Almost all previous MO codes were retained. It contains over 1,000 taxonomic names from 2022 already.
* The `microorganisms.old` data set was removed, and all previously accepted names are now included in the `microorganisms` data set. A new column `status` contains `"accepted"` for currently accepted names and `"synonym"` for taxonomic synonyms; currently invalid names. All previously accepted names now have a microorganisms ID and - if available - an LPSN, GBIF and SNOMED CT identifier.
* **The `microorganisms.old` data set was removed**, and all previously accepted names are now included in the `microorganisms` data set. A new column `status` contains `"accepted"` for currently accepted names and `"synonym"` for taxonomic synonyms; currently invalid names. All previously accepted names now have a microorganisms ID and - if available - an LPSN, GBIF and SNOMED CT identifier.
* The MO matching score algorithm (`mo_matching_score()`) now counts deletions and substitutions as 2 instead of 1, which impacts the outcome of `as.mo()` and any `mo_*()` function
* Argument `combine_IR` has been removed from this package (affecting functions `count_df()`, `proportion_df()`, and `rsi_df()` and some plotting functions), since it was replaced with `combine_SI` three years ago
* Removal of interpretation guidelines older than 10 years, the oldest now included guidelines of EUCAST and CLSI are from 2013
* **Argument `combine_IR` has been removed** from this package (affecting functions `count_df()`, `proportion_df()`, and `rsi_df()` and some plotting functions), since it was replaced with `combine_SI` three years ago
* Interpretation **guidelines older than 10 years were removed**, the oldest now included guidelines of EUCAST and CLSI are from 2013
### New
* EUCAST 2022 and CLSI 2022 guidelines have been added for `as.rsi()`. EUCAST 2022 is now the new default guideline for all MIC and disks diffusion interpretations.
* **EUCAST 2022 and CLSI 2022 guidelines** have been added for `as.rsi()`. EUCAST 2022 is now the new default guideline for all MIC and disks diffusion interpretations.
* Support for the following languages: Chinese, Greek, Japanese, Polish, Turkish and Ukrainian. We are very grateful for the valuable input by our colleagues from other countries. The `AMR` package is now available in 16 languages. The automatic language determination will give a note at start-up on systems in supported languages.
* All new algorithm for `as.mo()` (and thus all `mo_*()` functions) while still following our original set-up as described in our paper (DOI 10.18637/jss.v104.i03).
* **All new algorithm for `as.mo()`** (and thus all `mo_*()` functions) while still following our original set-up as described in our recently submitted JSS paper (DOI [10.18637/jss.v104.i03](https://doi.org/10.18637/jss.v104.i03)).
* A new argument `keep_synonyms` allows to *not* correct for updated taxonomy, in favour of the now deleted argument `allow_uncertain`
* It has increased tremendously in speed and returns generally more consequent results
* Sequential coercion is now extremely fast as results are stored to the package environment, although coercion of unknown values must be run once per session. Previous results can be reset/removed with the new `mo_reset_session()` function.
* Support for microorganism codes of the ASIan Antimicrobial Resistance Surveillance Network (ASIARS-Net)
* New functions!
* **Extensive support for antiviral agents!** For the first time, the `AMR` package has extensive support for antiviral drugs and to work with their names, codes and other data in any way.
* The `antivirals` data set has been extended with 18 new drugs (also from the [new J05AJ ATC group](https://www.whocc.no/atc_ddd_index/?code=J05AJ&showdescription=no)) and now also contains antiviral identifiers and LOINC codes
* A new data type `av` (*antivirals*) has been added, which is functionally similar to `ab` for antibiotics
* Functions `as.av()`, `av_name()`, `av_atc()`, `av_synonyms()`, `av_from_text()` have all been added as siblings to their `ab_*()` equivalents
* **Other new functions!**
* Function `rsi_confidence_interval()` to add confidence intervals in AMR calculation. This is also included in `rsi_df()` and `proportion_df()`
* Function `mean_amr_distance()` to calculate the mean AMR distance. The mean AMR distance is a normalised numeric value to compare AMR test results and can help to identify similar isolates, without comparing antibiograms by hand.
* Function `rsi_interpretation_history()` to view the history of previous runs of `as.rsi()`. This returns a 'logbook' with the selected guideline, reference table and specific interpretation of each row in a data set on which `as.rsi()` was run.
* Function `mo_current()` to get the currently valid taxonomic name of a microorganism
* Function `add_custom_antimicrobials()` to add custom antimicrobial codes and names to the `AMR` package
* New and updated entries for the `antibiotics` data set
* The following 20 antibiotics have been added (also includes the [new J01RA ATC group](https://www.whocc.no/atc_ddd_index/?code=J01RA&showdescription=no)): azithromycin/fluconazole/secnidazole (AFC), cefepime/amikacin (CFA), cefixime/ornidazole (CEO), ceftriaxone/beta-lactamase inhibitor (CEB), ciprofloxacin/metronidazole (CIM), ciprofloxacin/ornidazole (CIO), ciprofloxacin/tinidazole (CIT), furazidin (FUR), isoniazid/sulfamethoxazole/trimethoprim/pyridoxine (IST), lascufloxacin (LSC), levofloxacin/ornidazole (LEO), nemonoxacin (NEM), norfloxacin/metronidazole (NME), norfloxacin/tinidazole (NTI), ofloxacin/ornidazole (OOR), oteseconazole (OTE), rifampicin/ethambutol/isoniazid (REI), sarecycline (SRC), tetracycline/oleandomycin (TOL), and thioacetazone (TAT)
* The following **20 antibiotics have been added** (also includes the [new J01RA ATC group](https://www.whocc.no/atc_ddd_index/?code=J01RA&showdescription=no)): azithromycin/fluconazole/secnidazole (AFC), cefepime/amikacin (CFA), cefixime/ornidazole (CEO), ceftriaxone/beta-lactamase inhibitor (CEB), ciprofloxacin/metronidazole (CIM), ciprofloxacin/ornidazole (CIO), ciprofloxacin/tinidazole (CIT), furazidin (FUR), isoniazid/sulfamethoxazole/trimethoprim/pyridoxine (IST), lascufloxacin (LSC), levofloxacin/ornidazole (LEO), nemonoxacin (NEM), norfloxacin/metronidazole (NME), norfloxacin/tinidazole (NTI), ofloxacin/ornidazole (OOR), oteseconazole (OTE), rifampicin/ethambutol/isoniazid (REI), sarecycline (SRC), tetracycline/oleandomycin (TOL), and thioacetazone (TAT)
* Added some missing ATC codes
* Updated DDDs and PubChem Compound IDs
* Updated some antibiotic name spelling, now used by WHOCC (such as cephalexin -> cefalexin, and phenethicillin -> pheneticillin)
* Antibiotic code "CEI" for ceftolozane/tazobactam has been replaced with "CZT" to comply with EARS-Net and WHONET 2022. The old code will still work in all cases when using `as.ab()` or any of the `ab_*()` functions.
* Support for antimicrobial interpretation of anaerobic bacteria, by adding a 'placeholder' code `B_ANAER` to the `microorganisms` data set and add the breakpoints of anaerobics to the `rsi_interpretation` data set, which is used by `as.rsi()` when interpreting MIC and disk diffusion values
* Support for `data.frame`-enhancing R packages, more specifically: `data.table::data.table`, `janitor::tabyl`, `tibble::tibble`, and `tsibble::tsibble`. AMR package functions that have a data set as output (such as `rsi_df()` and `bug_drug_combinations()`), will now return the same data type as the input.
* All data sets in this package are now exported as `tibble`, instead of base R `data.frame`s. Older R versions are still supported.
* Our data sets are now also continually exported to Apache Feather and Apache Parquet formats. You can find more info [in this article on our website](https://msberends.github.io/AMR/articles/datasets.html).
* All data sets in this package are **now exported as `tibble`**, instead of base R `data.frame`s. Older R versions are still supported.
* Our data sets are now also continually exported to **Apache Feather and Apache Parquet formats**. You can find more info [in this article on our website](https://msberends.github.io/AMR/articles/datasets.html).
* Support for using antibiotic selectors in scoped `dplyr` verbs (with or without `vars()`), such as in: `... %>% summarise_at(aminoglycosides(), resistance)`, see `resistance()`
### Changed

21
R/ab.R
View File

@ -82,8 +82,8 @@
#'
#' # use ab_* functions to get a specific properties (see ?ab_property);
#' # they use as.ab() internally:
#' ab_name("J01FA01") # "Erythromycin"
#' ab_name("eryt") # "Erythromycin"
#' ab_name("J01FA01")
#' ab_name("eryt")
#'
#' \donttest{
#' if (require("dplyr")) {
@ -650,3 +650,20 @@ generalise_antibiotic_name <- function(x) {
x <- gsub("(/| AND | WITH | W/|[+]|[-])+", " ", x, perl = TRUE)
x
}
get_translate_ab <- function(translate_ab) {
translate_ab <- as.character(translate_ab)[1L]
if (translate_ab %in% c("TRUE", "official")) {
return("name")
} else if (translate_ab %in% c(NA_character_, "FALSE")) {
return(FALSE)
} else {
translate_ab <- tolower(translate_ab)
stop_ifnot(translate_ab %in% colnames(AMR::antibiotics),
"invalid value for 'translate_ab', this must be a column name of the antibiotics data set\n",
"or TRUE (equals 'name') or FALSE to not translate at all.",
call = FALSE
)
translate_ab
}
}

View File

@ -59,7 +59,7 @@
#' @examples
#' # mind the bad spelling of amoxicillin in this line,
#' # straight from a true health care record:
#' ab_from_text("28/03/2020 regular amoxicilliin 500mg po tds")
#' ab_from_text("28/03/2020 regular amoxicilliin 500mg po tid")
#'
#' ab_from_text("500 mg amoxi po and 400mg cipro iv")
#' ab_from_text("500 mg amoxi po and 400mg cipro iv", type = "dose")

View File

@ -36,7 +36,7 @@
#'
#' This work was published in the Journal of Statistical Software (Volume 104(3); \doi{10.18637/jss.v104.i03}) and formed the basis of two PhD theses (\doi{10.33612/diss.177417131} and \doi{10.33612/diss.192486375}).
#'
#' After installing this package, \R knows `r format_included_data_number(microorganisms)` distinct microbial species and all `r format_included_data_number(rbind(antibiotics[, "atc", drop = FALSE], antivirals[, "atc", drop = FALSE]))` antibiotic, antimycotic and antiviral drugs by name and code (including ATC, EARS-NET, LOINC and SNOMED CT), and knows all about valid R/SI and MIC values. It supports any data format, including WHONET/EARS-Net data.
#' After installing this package, \R knows `r format_included_data_number(microorganisms)` distinct microbial species and all `r format_included_data_number(rbind(antibiotics[, "name", drop = FALSE], antivirals[, "name", drop = FALSE]))` antibiotic, antimycotic and antiviral drugs by name and code (including ATC, EARS-NET, LOINC and SNOMED CT), and knows all about valid R/SI and MIC values. It supports any data format, including WHONET/EARS-Net data.
#'
#' This package is fully independent of any other \R package and works on Windows, macOS and Linux with all versions of \R since R-3.0.0 (April 2013). It was designed to work in any setting, including those with very limited resources. It was created for both routine data analysis and academic research at the Faculty of Medical Sciences of the University of Groningen, in collaboration with non-profit organisations Certe Medical Diagnostics and Advice and University Medical Center Groningen. This \R package is actively maintained and free software; you can freely use and distribute it for both personal and commercial (but not patent) purposes under the terms of the GNU General Public License version 2.0 (GPL-2), as published by the Free Software Foundation.
#'

617
R/av.R Executable file
View File

@ -0,0 +1,617 @@
# ==================================================================== #
# TITLE #
# AMR: An R Package for Working with Antimicrobial Resistance Data #
# #
# SOURCE #
# https://github.com/msberends/AMR #
# #
# CITE AS #
# Berends MS, Luz CF, Friedrich AW, Sinha BNM, Albers CJ, Glasner C #
# (2022). AMR: An R Package for Working with Antimicrobial Resistance #
# Data. Journal of Statistical Software, 104(3), 1-31. #
# doi:10.18637/jss.v104.i03 #
# #
# Developed at the University of Groningen, the Netherlands, in #
# collaboration with non-profit organisations Certe Medical #
# Diagnostics & Advice, and University Medical Center Groningen. #
# #
# This R package is free software; you can freely use and distribute #
# it for both personal and commercial purposes under the terms of the #
# GNU General Public License version 2.0 (GNU GPL-2), as published by #
# the Free Software Foundation. #
# We created this package for both routine data analysis and academic #
# research and it was publicly released in the hope that it will be #
# useful, but it comes WITHOUT ANY WARRANTY OR LIABILITY. #
# #
# Visit our website for the full manual and a complete tutorial about #
# how to conduct AMR data analysis: https://msberends.github.io/AMR/ #
# ==================================================================== #
#' Transform Input to an Antiviral Agent ID
#'
#' Use this function to determine the antiviral agent code of one or more antiviral agents. The data set [antivirals] will be searched for abbreviations, official names and synonyms (brand names).
#' @param x a [character] vector to determine to antiviral agent ID
#' @param flag_multiple_results a [logical] to indicate whether a note should be printed to the console that probably more than one antiviral agent code or name can be retrieved from a single input value.
#' @param info a [logical] to indicate whether a progress bar should be printed, defaults to `TRUE` only in interactive mode
#' @param ... arguments passed on to internal functions
#' @rdname as.av
#' @inheritSection WHOCC WHOCC
#' @details All entries in the [antivirals] data set have three different identifiers: a human readable EARS-Net code (column `ab`, used by ECDC and WHONET), an ATC code (column `atc`, used by WHO), and a CID code (column `cid`, Compound ID, used by PubChem). The data set contains more than 5,000 official brand names from many different countries, as found in PubChem. Not that some drugs contain multiple ATC codes.
#'
#' All these properties will be searched for the user input. The [as.av()] can correct for different forms of misspelling:
#'
#' * Wrong spelling of drug names (such as "acyclovir"), which corrects for most audible similarities such as f/ph, x/ks, c/z/s, t/th, etc.
#' * Too few or too many vowels or consonants
#' * Switching two characters (such as "aycclovir", often the case in clinical data, when doctors typed too fast)
#' * Digitalised paper records, leaving artefacts like 0/o/O (zero and O's), B/8, n/r, etc.
#'
#' Use the [`av_*`][av_property()] functions to get properties based on the returned antiviral agent ID, see *Examples*.
#'
#' Note: the [as.av()] and [`av_*`][av_property()] functions may use very long regular expression to match brand names of antimicrobial agents. This may fail on some systems.
#' @section Source:
#' World Health Organization (WHO) Collaborating Centre for Drug Statistics Methodology: \url{https://www.whocc.no/atc_ddd_index/}
#'
#' European Commission Public Health PHARMACEUTICALS - COMMUNITY REGISTER: \url{https://ec.europa.eu/health/documents/community-register/html/reg_hum_atc.htm}
#' @aliases ab
#' @return A [character] [vector] with additional class [`ab`]
#' @seealso
#' * [antivirals] for the [data.frame] that is being used to determine ATCs
#' * [av_from_text()] for a function to retrieve antimicrobial drugs from clinical text (from health care records)
#' @inheritSection AMR Reference Data Publicly Available
#' @export
#' @examples
#' # these examples all return "ACI", the ID of aciclovir:
#' as.av("J05AB01")
#' as.av("J 05 AB 01")
#' as.av("Aciclovir")
#' as.av("aciclo")
#' as.av(" aciclo 123")
#' as.av("ACICL")
#' as.av("ACI")
#' as.av("Virorax") # trade name
#' as.av("Zovirax") # trade name
#'
#' as.av("acyklofir") # severe spelling error, yet works
#'
#' # use av_* functions to get a specific properties (see ?av_property);
#' # they use as.av() internally:
#' av_name("J05AB01")
#' av_name("acicl")
as.av <- function(x, flag_multiple_results = TRUE, info = interactive(), ...) {
meet_criteria(x, allow_class = c("character", "numeric", "integer", "factor"), allow_NA = TRUE)
meet_criteria(flag_multiple_results, allow_class = "logical", has_length = 1)
meet_criteria(info, allow_class = "logical", has_length = 1)
if (is.av(x)) {
return(x)
}
if (all(x %in% c(AMR_env$AV_lookup$av, NA))) {
# all valid AB codes, but not yet right class
return(set_clean_class(x,
new_class = c("av", "character")
))
}
initial_search <- is.null(list(...)$initial_search)
already_regex <- isTRUE(list(...)$already_regex)
fast_mode <- isTRUE(list(...)$fast_mode)
x_bak <- x
x <- toupper(x)
# remove diacritics
x <- iconv(x, from = "UTF-8", to = "ASCII//TRANSLIT")
x <- gsub('"', "", x, fixed = TRUE)
x <- gsub("(specimen|specimen date|specimen_date|spec_date|gender|^dates?$)", "", x, ignore.case = TRUE, perl = TRUE)
x_bak_clean <- x
if (already_regex == FALSE) {
x_bak_clean <- generalise_antibiotic_name(x_bak_clean)
}
x <- unique(x_bak_clean) # this means that every x is in fact generalise_antibiotic_name(x)
x_new <- rep(NA_character_, length(x))
x_unknown <- character(0)
x_unknown_ATCs <- character(0)
note_if_more_than_one_found <- function(found, index, from_text) {
if (initial_search == TRUE && isTRUE(length(from_text) > 1)) {
avnames <- av_name(from_text, tolower = TRUE, initial_search = FALSE)
if (av_name(found[1L], language = NULL) %like% "(clavulanic acid|avibactam)") {
avnames <- avnames[!avnames %in% c("clavulanic acid", "avibactam")]
}
if (length(avnames) > 1) {
warning_(
"More than one result was found for item ", index, ": ",
vector_and(avnames, quotes = FALSE)
)
}
}
found[1L]
}
# Fill in names, AB codes, CID codes and ATC codes directly (`x` is already clean and uppercase)
known_names <- x %in% AMR_env$AV_lookup$generalised_name
x_new[known_names] <- AMR_env$AV_lookup$av[match(x[known_names], AMR_env$AV_lookup$generalised_name)]
known_codes_av <- x %in% AMR_env$AV_lookup$av
known_codes_atc <- vapply(FUN.VALUE = logical(1), x, function(x_) x_ %in% unlist(AMR_env$AV_lookup$atc), USE.NAMES = FALSE)
known_codes_cid <- x %in% AMR_env$AV_lookup$cid
x_new[known_codes_av] <- AMR_env$AV_lookup$av[match(x[known_codes_av], AMR_env$AV_lookup$av)]
x_new[known_codes_atc] <- AMR_env$AV_lookup$av[vapply(
FUN.VALUE = integer(1),
x[known_codes_atc],
function(x_) {
which(vapply(
FUN.VALUE = logical(1),
AMR_env$AV_lookup$atc,
function(atc) x_ %in% atc
))[1L]
},
USE.NAMES = FALSE
)]
x_new[known_codes_cid] <- AMR_env$AV_lookup$av[match(x[known_codes_cid], AMR_env$AV_lookup$cid)]
previously_coerced <- x %in% AMR_env$av_previously_coerced$x
x_new[previously_coerced & is.na(x_new)] <- AMR_env$av_previously_coerced$av[match(x[is.na(x_new) & x %in% AMR_env$av_previously_coerced$x], AMR_env$av_previously_coerced$x)]
already_known <- known_names | known_codes_av | known_codes_atc | known_codes_cid | previously_coerced
# fix for NAs
x_new[is.na(x)] <- NA
already_known[is.na(x)] <- FALSE
if (initial_search == TRUE && sum(already_known) < length(x)) {
progress <- progress_ticker(n = sum(!already_known), n_min = 25, print = info) # start if n >= 25
on.exit(close(progress))
}
for (i in which(!already_known)) {
if (initial_search == TRUE) {
progress$tick()
}
if (is.na(x[i]) || is.null(x[i])) {
next
}
if (identical(x[i], "") ||
# prevent "bacteria" from coercing to TMP, since Bacterial is a brand name of it:
identical(tolower(x[i]), "bacteria")) {
x_unknown <- c(x_unknown, x_bak[x[i] == x_bak_clean][1])
next
}
if (x[i] %like_case% "[A-Z][0-9][0-9][A-Z][A-Z][0-9][0-9]") {
# seems an ATC code, but the available ones are in `already_known`, so:
x_unknown <- c(x_unknown, x[i])
x_unknown_ATCs <- c(x_unknown_ATCs, x[i])
x_new[i] <- NA_character_
next
}
if (fast_mode == FALSE && flag_multiple_results == TRUE && x[i] %like% "[ ]") {
from_text <- tryCatch(suppressWarnings(av_from_text(x[i], initial_search = FALSE, translate_av = FALSE)[[1]]),
error = function(e) character(0)
)
} else {
from_text <- character(0)
}
# old code for phenoxymethylpenicillin (Peni V)
if (x[i] == "PNV") {
x_new[i] <- "PHN"
next
}
# exact LOINC code
loinc_found <- unlist(lapply(
AMR_env$AV_lookup$generalised_loinc,
function(s) x[i] %in% s
))
found <- AMR_env$AV_lookup$av[loinc_found == TRUE]
if (length(found) > 0) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
# exact synonym
synonym_found <- unlist(lapply(
AMR_env$AV_lookup$generalised_synonyms,
function(s) x[i] %in% s
))
found <- AMR_env$AV_lookup$av[synonym_found == TRUE]
if (length(found) > 0) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
# length of input is quite long, and Levenshtein distance is only max 2
if (nchar(x[i]) >= 10) {
levenshtein <- as.double(utils::adist(x[i], AMR_env$AV_lookup$generalised_name))
if (any(levenshtein <= 2)) {
found <- AMR_env$AV_lookup$av[which(levenshtein <= 2)]
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
}
# allow characters that resemble others, but only continue when having more than 3 characters
if (nchar(x[i]) <= 3) {
x_unknown <- c(x_unknown, x_bak[x[i] == x_bak_clean][1])
next
}
x_spelling <- x[i]
if (already_regex == FALSE) {
x_spelling <- gsub("[IY]+", "[IY]+", x_spelling, perl = TRUE)
x_spelling <- gsub("(C|K|Q|QU|S|Z|X|KS)+", "(C|K|Q|QU|S|Z|X|KS)+", x_spelling, perl = TRUE)
x_spelling <- gsub("(PH|F|V)+", "(PH|F|V)+", x_spelling, perl = TRUE)
x_spelling <- gsub("(TH|T)+", "(TH|T)+", x_spelling, perl = TRUE)
x_spelling <- gsub("A+", "A+", x_spelling, perl = TRUE)
x_spelling <- gsub("E+", "E+", x_spelling, perl = TRUE)
x_spelling <- gsub("O+", "O+", x_spelling, perl = TRUE)
# allow any ending of -in/-ine and -im/-ime
x_spelling <- gsub("(\\[IY\\]\\+(N|M)|\\[IY\\]\\+(N|M)E\\+?)$", "[IY]+(N|M)E*", x_spelling, perl = TRUE)
# allow any ending of -ol/-ole
x_spelling <- gsub("(O\\+L|O\\+LE\\+)$", "O+LE*", x_spelling, perl = TRUE)
# allow any ending of -on/-one
x_spelling <- gsub("(O\\+N|O\\+NE\\+)$", "O+NE*", x_spelling, perl = TRUE)
# replace multiple same characters to single one with '+', like "ll" -> "l+"
x_spelling <- gsub("(.)\\1+", "\\1+", x_spelling, perl = TRUE)
# replace spaces and slashes with a possibility on both
x_spelling <- gsub("[ /]", "( .*|.*/)", x_spelling, perl = TRUE)
# correct for digital reading text (OCR)
x_spelling <- gsub("[NRD8B]", "[NRD8B]", x_spelling, perl = TRUE)
x_spelling <- gsub("(O|0)", "(O|0)+", x_spelling, perl = TRUE)
x_spelling <- gsub("++", "+", x_spelling, fixed = TRUE)
}
# try if name starts with it
found <- AMR_env$AV_lookup[which(AMR_env$AV_lookup$generalised_name %like% paste0("^", x_spelling)), "av", drop = TRUE]
if (length(found) > 0) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
# try if name ends with it
found <- AMR_env$AV_lookup[which(AMR_env$AV_lookup$generalised_name %like% paste0(x_spelling, "$")), "av", drop = TRUE]
if (nchar(x[i]) >= 4 && length(found) > 0) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
# and try if any synonym starts with it
synonym_found <- unlist(lapply(
AMR_env$AV_lookup$generalised_synonyms,
function(s) any(s %like% paste0("^", x_spelling))
))
found <- AMR_env$AV_lookup$av[synonym_found == TRUE]
if (length(found) > 0) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
# INITIAL SEARCH - More uncertain results ----
if (initial_search == TRUE && fast_mode == FALSE) {
# only run on first try
# try by removing all spaces
if (x[i] %like% " ") {
found <- suppressWarnings(as.av(gsub(" +", "", x[i], perl = TRUE), initial_search = FALSE))
if (length(found) > 0 && !is.na(found)) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
}
# try by removing all spaces and numbers
if (x[i] %like% " " || x[i] %like% "[0-9]") {
found <- suppressWarnings(as.av(gsub("[ 0-9]", "", x[i], perl = TRUE), initial_search = FALSE))
if (length(found) > 0 && !is.na(found)) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
}
# transform back from other languages and try again
x_translated <- paste(lapply(
strsplit(x[i], "[^A-Z0-9]"),
function(y) {
for (i in seq_len(length(y))) {
for (lang in LANGUAGES_SUPPORTED[LANGUAGES_SUPPORTED != "en"]) {
y[i] <- ifelse(tolower(y[i]) %in% tolower(TRANSLATIONS[, lang, drop = TRUE]),
TRANSLATIONS[which(tolower(TRANSLATIONS[, lang, drop = TRUE]) == tolower(y[i]) &
!isFALSE(TRANSLATIONS$fixed)), "pattern"],
y[i]
)
}
}
generalise_antibiotic_name(y)
}
)[[1]],
collapse = "/"
)
x_translated_guess <- suppressWarnings(as.av(x_translated, initial_search = FALSE))
if (!is.na(x_translated_guess)) {
x_new[i] <- x_translated_guess
next
}
# now also try to coerce brandname combinations like "Amoxy/clavulanic acid"
x_translated <- paste(lapply(
strsplit(x_translated, "[^A-Z0-9 ]"),
function(y) {
for (i in seq_len(length(y))) {
y_name <- suppressWarnings(av_name(y[i], language = NULL, initial_search = FALSE))
y[i] <- ifelse(!is.na(y_name),
y_name,
y[i]
)
}
generalise_antibiotic_name(y)
}
)[[1]],
collapse = "/"
)
x_translated_guess <- suppressWarnings(as.av(x_translated, initial_search = FALSE))
if (!is.na(x_translated_guess)) {
x_new[i] <- x_translated_guess
next
}
# try by removing all trailing capitals
if (x[i] %like_case% "[a-z]+[A-Z]+$") {
found <- suppressWarnings(as.av(gsub("[A-Z]+$", "", x[i], perl = TRUE), initial_search = FALSE))
if (!is.na(found)) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
}
# keep only letters
found <- suppressWarnings(as.av(gsub("[^A-Z]", "", x[i], perl = TRUE), initial_search = FALSE))
if (!is.na(found)) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
# try from a bigger text, like from a health care record, see ?av_from_text
# already calculated above if flag_multiple_results = TRUE
if (flag_multiple_results == TRUE) {
found <- from_text[1L]
} else {
found <- tryCatch(suppressWarnings(av_from_text(x[i], initial_search = FALSE, translate_av = FALSE)[[1]][1L]),
error = function(e) NA_character_
)
}
if (!is.na(found)) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
# first 5 except for cephalosporins, then first 7 (those cephalosporins all start quite the same!)
found <- suppressWarnings(as.av(substr(x[i], 1, 5), initial_search = FALSE))
if (!is.na(found) && av_group(found, initial_search = FALSE) %unlike% "cephalosporins") {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
found <- suppressWarnings(as.av(substr(x[i], 1, 7), initial_search = FALSE))
if (!is.na(found)) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
# make all consonants facultative
search_str <- gsub("([BCDFGHJKLMNPQRSTVWXZ])", "\\1*", x[i], perl = TRUE)
found <- suppressWarnings(as.av(search_str, initial_search = FALSE, already_regex = TRUE))
# keep at least 4 normal characters
if (nchar(gsub(".\\*", "", search_str, perl = TRUE)) < 4) {
found <- NA
}
if (!is.na(found)) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
# make all vowels facultative
search_str <- gsub("([AEIOUY])", "\\1*", x[i], perl = TRUE)
found <- suppressWarnings(as.av(search_str, initial_search = FALSE, already_regex = TRUE))
# keep at least 5 normal characters
if (nchar(gsub(".\\*", "", search_str, perl = TRUE)) < 5) {
found <- NA
}
if (!is.na(found)) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
# allow misspelling of vowels
x_spelling <- gsub("A+", "[AEIOU]+", x_spelling, fixed = TRUE)
x_spelling <- gsub("E+", "[AEIOU]+", x_spelling, fixed = TRUE)
x_spelling <- gsub("I+", "[AEIOU]+", x_spelling, fixed = TRUE)
x_spelling <- gsub("O+", "[AEIOU]+", x_spelling, fixed = TRUE)
x_spelling <- gsub("U+", "[AEIOU]+", x_spelling, fixed = TRUE)
found <- suppressWarnings(as.av(x_spelling, initial_search = FALSE, already_regex = TRUE))
if (!is.na(found)) {
x_new[i] <- note_if_more_than_one_found(found, i, from_text)
next
}
# try with switched character, like "mreopenem"
for (j in seq_len(nchar(x[i]))) {
x_switched <- paste0(
# beginning part:
substr(x[i], 1, j - 1),
# here is the switching of 2 characters:
substr(x[i], j + 1, j + 1),
substr(x[i], j, j),
# ending part:
substr(x[i], j + 2, nchar(x[i]))
)
found <- suppressWarnings(as.av(x_switched, initial_search = FALSE))
if (!is.na(found)) {
break
}
}
if (!is.na(found)) {
x_new[i] <- found[1L]
next
}
} # end of initial_search = TRUE
# not found
x_unknown <- c(x_unknown, x_bak[x[i] == x_bak_clean][1])
}
if (initial_search == TRUE && sum(already_known) < length(x)) {
close(progress)
}
# save to package env to save time for next time
if (initial_search == TRUE) {
AMR_env$av_previously_coerced <- AMR_env$av_previously_coerced[which(!AMR_env$av_previously_coerced$x %in% x), , drop = FALSE]
AMR_env$av_previously_coerced <- unique(rbind(AMR_env$av_previously_coerced,
data.frame(
x = x,
av = x_new,
x_bak = x_bak[match(x, x_bak_clean)],
stringsAsFactors = FALSE
),
stringsAsFactors = FALSE
))
}
# take failed ATC codes apart from rest
if (length(x_unknown_ATCs) > 0 && fast_mode == FALSE) {
warning_(
"in `as.av()`: these ATC codes are not (yet) in the antivirals data set: ",
vector_and(x_unknown_ATCs), "."
)
}
x_unknown <- x_unknown[!x_unknown %in% x_unknown_ATCs]
x_unknown <- c(x_unknown,
AMR_env$av_previously_coerced$x_bak[which(AMR_env$av_previously_coerced$x %in% x & is.na(AMR_env$av_previously_coerced$av))])
if (length(x_unknown) > 0 && fast_mode == FALSE) {
warning_(
"in `as.av()`: these values could not be coerced to a valid antiviral agent ID: ",
vector_and(x_unknown), "."
)
}
x_result <- x_new[match(x_bak_clean, x)]
if (length(x_result) == 0) {
x_result <- NA_character_
}
set_clean_class(x_result,
new_class = c("av", "character")
)
}
#' @rdname as.av
#' @export
is.av <- function(x) {
inherits(x, "av")
}
# will be exported using s3_register() in R/zzz.R
pillar_shaft.av <- function(x, ...) {
out <- trimws(format(x))
out[is.na(x)] <- font_na(NA)
create_pillar_column(out, align = "left", min_width = 4)
}
# will be exported using s3_register() in R/zzz.R
type_sum.av <- function(x, ...) {
"av"
}
#' @method print av
#' @export
#' @noRd
print.av <- function(x, ...) {
cat("Class 'av'\n")
print(as.character(x), quote = FALSE)
}
#' @method as.data.frame av
#' @export
#' @noRd
as.data.frame.av <- function(x, ...) {
nm <- deparse1(substitute(x))
if (!"nm" %in% names(list(...))) {
as.data.frame.vector(as.av(x), ..., nm = nm)
} else {
as.data.frame.vector(as.av(x), ...)
}
}
#' @method [ av
#' @export
#' @noRd
"[.av" <- function(x, ...) {
y <- NextMethod()
attributes(y) <- attributes(x)
y
}
#' @method [[ av
#' @export
#' @noRd
"[[.av" <- function(x, ...) {
y <- NextMethod()
attributes(y) <- attributes(x)
y
}
#' @method [<- av
#' @export
#' @noRd
"[<-.av" <- function(i, j, ..., value) {
y <- NextMethod()
attributes(y) <- attributes(i)
return_after_integrity_check(y, "antimicrobial code", AMR_env$AV_lookup$av)
}
#' @method [[<- av
#' @export
#' @noRd
"[[<-.av" <- function(i, j, ..., value) {
y <- NextMethod()
attributes(y) <- attributes(i)
return_after_integrity_check(y, "antimicrobial code", AMR_env$AV_lookup$av)
}
#' @method c av
#' @export
#' @noRd
c.av <- function(...) {
x <- list(...)[[1L]]
y <- NextMethod()
attributes(y) <- attributes(x)
return_after_integrity_check(y, "antimicrobial code", AMR_env$AV_lookup$av)
}
#' @method unique av
#' @export
#' @noRd
unique.av <- function(x, incomparables = FALSE, ...) {
y <- NextMethod()
attributes(y) <- attributes(x)
y
}
#' @method rep av
#' @export
#' @noRd
rep.av <- function(x, ...) {
y <- NextMethod()
attributes(y) <- attributes(x)
y
}
get_translate_av <- function(translate_av) {
translate_av <- as.character(translate_av)[1L]
if (translate_av %in% c("TRUE", "official")) {
return("name")
} else if (translate_av %in% c(NA_character_, "FALSE")) {
return(FALSE)
} else {
translate_av <- tolower(translate_av)
stop_ifnot(translate_av %in% colnames(AMR::antivirals),
"invalid value for 'translate_av', this must be a column name of the antivirals data set\n",
"or TRUE (equals 'name') or FALSE to not translate at all.",
call = FALSE
)
translate_av
}
}

186
R/av_from_text.R Normal file
View File

@ -0,0 +1,186 @@
# ==================================================================== #
# TITLE #
# AMR: An R Package for Working with Antimicrobial Resistance Data #
# #
# SOURCE #
# https://github.com/msberends/AMR #
# #
# CITE AS #
# Berends MS, Luz CF, Friedrich AW, Sinha BNM, Albers CJ, Glasner C #
# (2022). AMR: An R Package for Working with Antimicrobial Resistance #
# Data. Journal of Statistical Software, 104(3), 1-31. #
# doi:10.18637/jss.v104.i03 #
# #
# Developed at the University of Groningen, the Netherlands, in #
# collaboration with non-profit organisations Certe Medical #
# Diagnostics & Advice, and University Medical Center Groningen. #
# #
# This R package is free software; you can freely use and distribute #
# it for both personal and commercial purposes under the terms of the #
# GNU General Public License version 2.0 (GNU GPL-2), as published by #
# the Free Software Foundation. #
# We created this package for both routine data analysis and academic #
# research and it was publicly released in the hope that it will be #
# useful, but it comes WITHOUT ANY WARRANTY OR LIABILITY. #
# #
# Visit our website for the full manual and a complete tutorial about #
# how to conduct AMR data analysis: https://msberends.github.io/AMR/ #
# ==================================================================== #
#' Retrieve Antiviral Drug Names and Doses from Clinical Text
#'
#' Use this function on e.g. clinical texts from health care records. It returns a [list] with all antiviral drugs, doses and forms of administration found in the texts.
#' @param text text to analyse
#' @param type type of property to search for, either `"drug"`, `"dose"` or `"administration"`, see *Examples*
#' @param collapse a [character] to pass on to `paste(, collapse = ...)` to only return one [character] per element of `text`, see *Examples*
#' @param translate_av if `type = "drug"`: a column name of the [antivirals] data set to translate the antibiotic abbreviations to, using [av_property()]. Defaults to `FALSE`. Using `TRUE` is equal to using "name".
#' @param thorough_search a [logical] to indicate whether the input must be extensively searched for misspelling and other faulty input values. Setting this to `TRUE` will take considerably more time than when using `FALSE`. At default, it will turn `TRUE` when all input elements contain a maximum of three words.
#' @param info a [logical] to indicate whether a progress bar should be printed, defaults to `TRUE` only in interactive mode
#' @param ... arguments passed on to [as.av()]
#' @details This function is also internally used by [as.av()], although it then only searches for the first drug name and will throw a note if more drug names could have been returned. Note: the [as.av()] function may use very long regular expression to match brand names of antiviral agents. This may fail on some systems.
#'
#' ### Argument `type`
#' At default, the function will search for antiviral drug names. All text elements will be searched for official names, ATC codes and brand names. As it uses [as.av()] internally, it will correct for misspelling.
#'
#' With `type = "dose"` (or similar, like "dosing", "doses"), all text elements will be searched for [numeric] values that are higher than 100 and do not resemble years. The output will be [numeric]. It supports any unit (g, mg, IE, etc.) and multiple values in one clinical text, see *Examples*.
#'
#' With `type = "administration"` (or abbreviations, like "admin", "adm"), all text elements will be searched for a form of drug administration. It supports the following forms (including common abbreviations): buccal, implant, inhalation, instillation, intravenous, nasal, oral, parenteral, rectal, sublingual, transdermal and vaginal. Abbreviations for oral (such as 'po', 'per os') will become "oral", all values for intravenous (such as 'iv', 'intraven') will become "iv". It supports multiple values in one clinical text, see *Examples*.
#'
#' ### Argument `collapse`
#' Without using `collapse`, this function will return a [list]. This can be convenient to use e.g. inside a `mutate()`):\cr
#' `df %>% mutate(avx = av_from_text(clinical_text))`
#'
#' The returned AV codes can be transformed to official names, groups, etc. with all [`av_*`][av_property()] functions such as [av_name()] and [av_group()], or by using the `translate_av` argument.
#'
#' With using `collapse`, this function will return a [character]:\cr
#' `df %>% mutate(avx = av_from_text(clinical_text, collapse = "|"))`
#' @export
#' @return A [list], or a [character] if `collapse` is not `NULL`
#' @examples
#' av_from_text("28/03/2020 valaciclovir po tid")
#' av_from_text("28/03/2020 valaciclovir po tid", type = "admin")
av_from_text <- function(text,
type = c("drug", "dose", "administration"),
collapse = NULL,
translate_av = FALSE,
thorough_search = NULL,
info = interactive(),
...) {
if (missing(type)) {
type <- type[1L]
}
meet_criteria(text)
meet_criteria(type, allow_class = "character", has_length = 1)
meet_criteria(collapse, has_length = 1, allow_NULL = TRUE)
meet_criteria(translate_av, allow_NULL = FALSE) # get_translate_av() will be more informative about what's allowed
meet_criteria(thorough_search, allow_class = "logical", has_length = 1, allow_NULL = TRUE)
meet_criteria(info, allow_class = "logical", has_length = 1)
type <- tolower(trimws2(type))
text <- tolower(as.character(text))
text_split_all <- strsplit(text, "[ ;.,:\\|]")
progress <- progress_ticker(n = length(text_split_all), n_min = 5, print = info)
on.exit(close(progress))
if (type %like% "(drug|ab|anti)") {
translate_av <- get_translate_av(translate_av)
if (isTRUE(thorough_search) ||
(isTRUE(is.null(thorough_search)) && max(vapply(FUN.VALUE = double(1), text_split_all, length), na.rm = TRUE) <= 3)) {
text_split_all <- text_split_all[nchar(text_split_all) >= 4 & grepl("[a-z]+", text_split_all)]
result <- lapply(text_split_all, function(text_split) {
progress$tick()
suppressWarnings(
as.av(text_split, ...)
)
})
} else {
# no thorough search
names_atc <- substr(c(AMR::antivirals$name, AMR::antivirals$atc), 1, 5)
synonyms <- unlist(AMR::antivirals$synonyms)
synonyms <- synonyms[nchar(synonyms) >= 4]
# regular expression must not be too long, so split synonyms in two:
synonyms_part1 <- synonyms[seq_len(0.5 * length(synonyms))]
synonyms_part2 <- synonyms[!synonyms %in% synonyms_part1]
to_regex <- function(x) {
paste0(
"^(",
paste0(unique(gsub("[^a-z0-9]+", "", sort(tolower(x)))), collapse = "|"),
").*"
)
}
result <- lapply(text_split_all, function(text_split) {
progress$tick()
suppressWarnings(
as.av(
unique(c(
text_split[text_split %like_case% to_regex(names_atc)],
text_split[text_split %like_case% to_regex(synonyms_part1)],
text_split[text_split %like_case% to_regex(synonyms_part2)]
)),
...
)
)
})
}
close(progress)
result <- lapply(result, function(out) {
out <- out[!is.na(out)]
if (length(out) == 0) {
as.av(NA)
} else {
if (!isFALSE(translate_av)) {
out <- av_property(out, property = translate_av, initial_search = FALSE)
}
out
}
})
} else if (type %like% "dos") {
text_split_all <- strsplit(text, " ", fixed = TRUE)
result <- lapply(text_split_all, function(text_split) {
text_split <- text_split[text_split %like% "^[0-9]{2,}(/[0-9]+)?[a-z]*$"]
# only left part of "/", like 500 in "500/125"
text_split <- gsub("/.*", "", text_split)
text_split <- gsub(",", ".", text_split, fixed = TRUE) # foreign system using comma as decimal sep
text_split <- as.double(gsub("[^0-9.]", "", text_split))
# minimal 100 units/mg and no years that unlikely doses
text_split <- text_split[text_split >= 100 & !text_split %in% c(1951:1999, 2001:2049)]
if (length(text_split) > 0) {
text_split
} else {
NA_real_
}
})
} else if (type %like% "adm") {
result <- lapply(text_split_all, function(text_split) {
text_split <- text_split[text_split %like% "(^iv$|intraven|^po$|per os|oral|implant|inhal|instill|nasal|paren|rectal|sublingual|buccal|trans.*dermal|vaginal)"]
if (length(text_split) > 0) {
text_split <- gsub("(^po$|.*per os.*)", "oral", text_split)
text_split <- gsub("(^iv$|.*intraven.*)", "iv", text_split)
text_split
} else {
NA_character_
}
})
} else {
stop_("`type` must be either 'drug', 'dose' or 'administration'")
}
# collapse text if needed
if (!is.null(collapse)) {
result <- vapply(FUN.VALUE = character(1), result, function(x) {
if (length(x) == 1 & all(is.na(x))) {
NA_character_
} else {
paste0(x, collapse = collapse)
}
})
}
result
}

337
R/av_property.R Normal file
View File

@ -0,0 +1,337 @@
# ==================================================================== #
# TITLE #
# AMR: An R Package for Working with Antimicrobial Resistance Data #
# #
# SOURCE #
# https://github.com/msberends/AMR #
# #
# CITE AS #
# Berends MS, Luz CF, Friedrich AW, Sinha BNM, Albers CJ, Glasner C #
# (2022). AMR: An R Package for Working with Antimicrobial Resistance #
# Data. Journal of Statistical Software, 104(3), 1-31. #
# doi:10.18637/jss.v104.i03 #
# #
# Developed at the University of Groningen, the Netherlands, in #
# collaboration with non-profit organisations Certe Medical #
# Diagnostics & Advice, and University Medical Center Groningen. #
# #
# This R package is free software; you can freely use and distribute #
# it for both personal and commercial purposes under the terms of the #
# GNU General Public License version 2.0 (GNU GPL-2), as published by #
# the Free Software Foundation. #
# We created this package for both routine data analysis and academic #
# research and it was publicly released in the hope that it will be #
# useful, but it comes WITHOUT ANY WARRANTY OR LIABILITY. #
# #
# Visit our website for the full manual and a complete tutorial about #
# how to conduct AMR data analysis: https://msberends.github.io/AMR/ #
# ==================================================================== #
#' Get Properties of an Antiviral Agent
#'
#' Use these functions to return a specific property of an antiviral agent from the [antivirals] data set. All input values will be evaluated internally with [as.av()].
#' @param x any (vector of) text that can be coerced to a valid antiviral agent code with [as.av()]
#' @param tolower a [logical] to indicate whether the first [character] of every output should be transformed to a lower case [character].
#' @param property one of the column names of one of the [antivirals] data set: `vector_or(colnames(antivirals), sort = FALSE)`.
#' @param language language of the returned text, defaults to system language (see [get_AMR_locale()]) and can also be set with `getOption("AMR_locale")`. Use `language = NULL` or `language = ""` to prevent translation.
#' @param administration way of administration, either `"oral"` or `"iv"`
#' @param open browse the URL using [utils::browseURL()]
#' @param ... other arguments passed on to [as.av()]
#' @details All output [will be translated][translate] where possible.
#'
#' The function [av_url()] will return the direct URL to the official WHO website. A warning will be returned if the required ATC code is not available.
#' @inheritSection as.av Source
#' @rdname av_property
#' @name av_property
#' @return
#' - An [integer] in case of [av_cid()]
#' - A named [list] in case of [av_info()] and multiple [av_atc()]/[av_synonyms()]/[av_tradenames()]
#' - A [double] in case of [av_ddd()]
#' - A [character] in all other cases
#' @export
#' @seealso [antivirals]
#' @inheritSection AMR Reference Data Publicly Available
#' @examples
#' # all properties:
#' av_name("AMX") # "Amoxicillin"
#' av_atc("AMX") # "J01CA04" (ATC code from the WHO)
#' av_cid("AMX") # 33613 (Compound ID from PubChem)
#' av_synonyms("AMX") # a list with brand names of amoxicillin
#' av_tradenames("AMX") # same
#' av_group("AMX") # "Beta-lactams/penicillins"
#' av_atc_group1("AMX") # "Beta-lactam antibacterials, penicillins"
#' av_atc_group2("AMX") # "Penicillins with extended spectrum"
#' av_url("AMX") # link to the official WHO page
#'
#' # smart lowercase tranformation
#' av_name(x = c("AMC", "PLB")) # "Amoxicillin/clavulanic acid" "Polymyxin B"
#' av_name(
#' x = c("AMC", "PLB"),
#' tolower = TRUE
#' ) # "amoxicillin/clavulanic acid" "polymyxin B"
#'
#' # defined daily doses (DDD)
#' av_ddd("AMX", "oral") # 1.5
#' av_ddd_units("AMX", "oral") # "g"
#' av_ddd("AMX", "iv") # 3
#' av_ddd_units("AMX", "iv") # "g"
#'
#' av_info("AMX") # all properties as a list
#'
#' # all av_* functions use as.av() internally, so you can go from 'any' to 'any':
#' av_atc("AMP") # ATC code of AMP (ampicillin)
#' av_group("J01CA01") # Drug group of ampicillins ATC code
#' av_loinc("ampicillin") # LOINC codes of ampicillin
#' av_name("21066-6") # "Ampicillin" (using LOINC)
#' av_name(6249) # "Ampicillin" (using CID)
#' av_name("J01CA01") # "Ampicillin" (using ATC)
#'
#' # spelling from different languages and dyslexia are no problem
#' av_atc("ceftriaxon")
#' av_atc("cephtriaxone")
#' av_atc("cephthriaxone")
#' av_atc("seephthriaaksone")
av_name <- function(x, language = get_AMR_locale(), tolower = FALSE, ...) {
meet_criteria(x, allow_NA = TRUE)
language <- validate_language(language)
meet_criteria(tolower, allow_class = "logical", has_length = 1)
x <- translate_into_language(av_validate(x = x, property = "name", ...), language = language, only_affect_ab_names = TRUE)
if (tolower == TRUE) {
# use perl to only transform the first character
# as we want "polymyxin B", not "polymyxin b"
x <- gsub("^([A-Z])", "\\L\\1", x, perl = TRUE)
}
x
}
#' @rdname av_property
#' @export
av_cid <- function(x, ...) {
meet_criteria(x, allow_NA = TRUE)
av_validate(x = x, property = "cid", ...)
}
#' @rdname av_property
#' @export
av_synonyms <- function(x, ...) {
meet_criteria(x, allow_NA = TRUE)
syns <- av_validate(x = x, property = "synonyms", ...)
names(syns) <- x
if (length(syns) == 1) {
unname(unlist(syns))
} else {
syns
}
}
#' @rdname av_property
#' @export
av_tradenames <- function(x, ...) {
meet_criteria(x, allow_NA = TRUE)
av_synonyms(x, ...)
}
#' @rdname av_property
#' @export
av_group <- function(x, language = get_AMR_locale(), ...) {
meet_criteria(x, allow_NA = TRUE)
language <- validate_language(language)
translate_into_language(av_validate(x = x, property = "group", ...), language = language, only_affect_ab_names = TRUE)
}
#' @rdname av_property
#' @aliases ATC
#' @export
av_atc <- function(x, only_first = FALSE, ...) {
meet_criteria(x, allow_NA = TRUE)
meet_criteria(only_first, allow_class = "logical", has_length = 1)
atcs <- av_validate(x = x, property = "atc", ...)
if (only_first == TRUE) {
atcs <- vapply(
FUN.VALUE = character(1),
# get only the first ATC code
atcs,
function(x) {
# try to get the J-group
if (any(x %like% "^J")) {
x[x %like% "^J"][1L]
} else {
as.character(x[1L])
}
}
)
} else if (length(atcs) == 1) {
atcs <- unname(unlist(atcs))
} else {
names(atcs) <- x
}
atcs
}
#' @rdname av_property
#' @export
av_loinc <- function(x, ...) {
meet_criteria(x, allow_NA = TRUE)
loincs <- av_validate(x = x, property = "loinc", ...)
names(loincs) <- x
if (length(loincs) == 1) {
unname(unlist(loincs))
} else {
loincs
}
}
#' @rdname av_property
#' @export
av_ddd <- function(x, administration = "oral", ...) {
meet_criteria(x, allow_NA = TRUE)
meet_criteria(administration, is_in = c("oral", "iv"), has_length = 1)
x <- as.av(x, ...)
ddd_prop <- administration
# old behaviour
units <- list(...)$units
if (!is.null(units) && isTRUE(units)) {
if (message_not_thrown_before("av_ddd", entire_session = TRUE)) {
warning_(
"in `av_ddd()`: using `av_ddd(..., units = TRUE)` is deprecated, use `av_ddd_units()` to retrieve units instead.",
"This warning will be shown once per session."
)
}
ddd_prop <- paste0(ddd_prop, "_units")
} else {
ddd_prop <- paste0(ddd_prop, "_ddd")
}
out <- av_validate(x = x, property = ddd_prop)
if (any(av_name(x, language = NULL) %like% "/" & is.na(out))) {
warning_(
"in `av_ddd()`: DDDs of some combined products are available for different dose combinations and not (yet) part of the AMR package.",
"Please refer to the WHOCC website:\n",
"www.whocc.no/ddd/list_of_ddds_combined_products/"
)
}
out
}
#' @rdname av_property
#' @export
av_ddd_units <- function(x, administration = "oral", ...) {
meet_criteria(x, allow_NA = TRUE)
meet_criteria(administration, is_in = c("oral", "iv"), has_length = 1)
x <- as.av(x, ...)
if (any(av_name(x, language = NULL) %like% "/")) {
warning_(
"in `av_ddd_units()`: DDDs of combined products are available for different dose combinations and not (yet) part of the AMR package.",
"Please refer to the WHOCC website:\n",
"www.whocc.no/ddd/list_of_ddds_combined_products/"
)
}
ddd_prop <- paste0(administration, "_units")
av_validate(x = x, property = ddd_prop)
}
#' @rdname av_property
#' @export
av_info <- function(x, language = get_AMR_locale(), ...) {
meet_criteria(x, allow_NA = TRUE)
language <- validate_language(language)
x <- as.av(x, ...)
list(
av = as.character(x),
cid = av_cid(x),
name = av_name(x, language = language),
group = av_group(x, language = language),
atc = av_atc(x),
tradenames = av_tradenames(x),
loinc = av_loinc(x),
ddd = list(
oral = list(
amount = av_ddd(x, administration = "oral"),
units = av_ddd_units(x, administration = "oral")
),
iv = list(
amount = av_ddd(x, administration = "iv"),
units = av_ddd_units(x, administration = "iv")
)
)
)
}
#' @rdname av_property
#' @export
av_url <- function(x, open = FALSE, ...) {
meet_criteria(x, allow_NA = TRUE)
meet_criteria(open, allow_class = "logical", has_length = 1)
av <- as.av(x = x, ...)
atcs <- av_atc(av, only_first = TRUE)
u <- paste0("https://www.whocc.no/atc_ddd_index/?code=", atcs, "&showdescription=no")
u[is.na(atcs)] <- NA_character_
names(u) <- av_name(av)
NAs <- av_name(av, tolower = TRUE, language = NULL)[!is.na(av) & is.na(atcs)]
if (length(NAs) > 0) {
warning_("in `av_url()`: no ATC code available for ", vector_and(NAs, quotes = FALSE), ".")
}
if (open == TRUE) {
if (length(u) > 1 && !is.na(u[1L])) {
warning_("in `av_url()`: only the first URL will be opened, as `browseURL()` only suports one string.")
}
if (!is.na(u[1L])) {
utils::browseURL(u[1L])
}
}
u
}
#' @rdname av_property
#' @export
av_property <- function(x, property = "name", language = get_AMR_locale(), ...) {
meet_criteria(x, allow_NA = TRUE)
meet_criteria(property, is_in = colnames(AMR::antivirals), has_length = 1)
meet_criteria(language, is_in = c(LANGUAGES_SUPPORTED, ""), has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
translate_into_language(av_validate(x = x, property = property, ...), language = language)
}
av_validate <- function(x, property, ...) {
if (tryCatch(all(x[!is.na(x)] %in% AMR_env$AV_lookup$av), error = function(e) FALSE)) {
# special case for av_* functions where class is already 'av'
x <- AMR_env$AV_lookup[match(x, AMR_env$AV_lookup$av), property, drop = TRUE]
} else {
# try to catch an error when inputting an invalid argument
# so the 'call.' can be set to FALSE
tryCatch(x[1L] %in% AMR_env$AV_lookup[1, property, drop = TRUE],
error = function(e) stop(e$message, call. = FALSE)
)
if (!all(x %in% AMR_env$AV_lookup[, property, drop = TRUE])) {
x <- as.av(x, ...)
if (all(is.na(x)) && is.list(AMR_env$AV_lookup[, property, drop = TRUE])) {
x <- rep(NA_character_, length(x))
} else {
x <- AMR_env$AV_lookup[match(x, AMR_env$AV_lookup$av), property, drop = TRUE]
}
}
}
if (property == "av") {
return(set_clean_class(x, new_class = c("av", "character")))
} else if (property == "cid") {
return(as.integer(x))
} else if (property %like% "ddd") {
return(as.double(x))
} else {
x[is.na(x)] <- NA
return(x)
}
}

View File

@ -48,15 +48,17 @@
#' - `loinc`\cr All LOINC codes (Logical Observation Identifiers Names and Codes) associated with the name of the antimicrobial agent. Use [ab_loinc()] to retrieve them quickly, see [ab_property()].
#'
#' ### For the [antivirals] data set: a [tibble][tibble::tibble] with `r nrow(antivirals)` observations and `r ncol(antivirals)` variables:
#' - `av`\cr Antibiotic ID as used in this package (such as `AMC`), using the official EARS-Net (European Antimicrobial Resistance Surveillance Network) codes where available
#' - `name`\cr Official name as used by WHONET/EARS-Net or the WHO
#' - `atc`\cr ATC codes (Anatomical Therapeutic Chemical) as defined by the WHOCC
#' - `cid`\cr Compound ID as found in PubChem
#' - `name`\cr Official name as used by WHONET/EARS-Net or the WHO
#' - `atc_group`\cr Official pharmacological subgroup (3rd level ATC code) as defined by the WHOCC
#' - `synonyms`\cr Synonyms (often trade names) of a drug, as found in PubChem based on their compound ID
#' - `oral_ddd`\cr Defined Daily Dose (DDD), oral treatment
#' - `oral_units`\cr Units of `oral_ddd`
#' - `iv_ddd`\cr Defined Daily Dose (DDD), parenteral treatment
#' - `iv_units`\cr Units of `iv_ddd`
#' - `loinc`\cr All LOINC codes (Logical Observation Identifiers Names and Codes) associated with the name of the antimicrobial agent.
#' @details Properties that are based on an ATC code are only available when an ATC is available. These properties are: `atc_group1`, `atc_group2`, `oral_ddd`, `oral_units`, `iv_ddd` and `iv_units`.
#'
#' Synonyms (i.e. trade names) were derived from the PubChem Compound ID (column `cid`) and consequently only available where a CID is available.

View File

@ -375,20 +375,3 @@ rsi_calc_df <- function(type, # "proportion", "count" or "both"
out <- as_original_data_class(out, class(data.bak))
structure(out, class = c("rsi_df", class(out)))
}
get_translate_ab <- function(translate_ab) {
translate_ab <- as.character(translate_ab)[1L]
if (translate_ab %in% c("TRUE", "official")) {
return("name")
} else if (translate_ab %in% c(NA_character_, "FALSE")) {
return(FALSE)
} else {
translate_ab <- tolower(translate_ab)
stop_ifnot(translate_ab %in% colnames(AMR::antibiotics),
"invalid value for 'translate_ab', this must be a column name of the antibiotics data set\n",
"or TRUE (equals 'name') or FALSE to not translate at all.",
call = FALSE
)
translate_ab
}
}

Binary file not shown.

View File

@ -168,6 +168,7 @@ if (utf8_supported && !is_latex) {
# reference data - they have additional columns compared to `antibiotics` and `microorganisms` to improve speed
# they cannot be part of R/sysdata.rda since CRAN thinks it would make the package too large (+3 MB)
AMR_env$AB_lookup <- create_AB_lookup()
AMR_env$AV_lookup <- create_AV_lookup()
AMR_env$MO_lookup <- create_MO_lookup()
}
@ -190,6 +191,10 @@ create_AB_lookup <- function() {
cbind(AMR::antibiotics, AB_LOOKUP)
}
create_AV_lookup <- function() {
cbind(AMR::antivirals, AV_LOOKUP)
}
create_MO_lookup <- function() {
MO_lookup <- AMR::microorganisms

View File

@ -267,17 +267,19 @@ AB_BETALACTAMS <- c(AB_PENICILLINS, AB_CEPHALOSPORINS, AB_CARBAPENEMS)
# this will be used for documentation:
DEFINED_AB_GROUPS <- ls(envir = globalenv())
DEFINED_AB_GROUPS <- DEFINED_AB_GROUPS[!DEFINED_AB_GROUPS %in% globalenv_before_ab]
create_AB_lookup <- function() {
AMR_env$AB_lookup <- AMR::antibiotics
AMR_env$AB_lookup$generalised_name <- generalise_antibiotic_name(AMR_env$AB_lookup$name)
AMR_env$AB_lookup$generalised_synonyms <- lapply(AMR_env$AB_lookup$synonyms, generalise_antibiotic_name)
AMR_env$AB_lookup$generalised_abbreviations <- lapply(AMR_env$AB_lookup$abbreviations, generalise_antibiotic_name)
AMR_env$AB_lookup$generalised_loinc <- lapply(AMR_env$AB_lookup$loinc, generalise_antibiotic_name)
AMR_env$AB_lookup$generalised_all <- unname(lapply(
as.list(as.data.frame(t(AMR_env$AB_lookup[,
create_AB_AV_lookup <- function(df) {
new_df <- df
new_df$generalised_name <- generalise_antibiotic_name(new_df$name)
new_df$generalised_synonyms <- lapply(new_df$synonyms, generalise_antibiotic_name)
if ("abbreviations" %in% colnames(df)) {
new_df$generalised_abbreviations <- lapply(new_df$abbreviations, generalise_antibiotic_name)
}
new_df$generalised_loinc <- lapply(new_df$loinc, generalise_antibiotic_name)
new_df$generalised_all <- unname(lapply(
as.list(as.data.frame(t(new_df[,
c(
"ab", "atc", "cid", "name",
colnames(AMR_env$AB_lookup)[colnames(AMR_env$AB_lookup) %like% "generalised"]
colnames(new_df)[colnames(new_df) %in% c("ab", "av", "atc", "cid", "name")],
colnames(new_df)[colnames(new_df) %like% "generalised"]
),
drop = FALSE
]),
@ -288,9 +290,10 @@ create_AB_lookup <- function() {
x[x != ""]
}
))
AMR_env$AB_lookup[, colnames(AMR_env$AB_lookup)[colnames(AMR_env$AB_lookup) %like% "^generalised"]]
new_df[, colnames(new_df)[colnames(new_df) %like% "^generalised"]]
}
AB_LOOKUP <- create_AB_lookup()
AB_LOOKUP <- create_AB_AV_lookup(AMR::antibiotics)
AV_LOOKUP <- create_AB_AV_lookup(AMR::antivirals)
# Export to package as internal data ----
usethis::ui_info(paste0("Updating internal package data"))
@ -304,6 +307,7 @@ suppressMessages(usethis::use_data(EUCAST_RULES_DF,
MO_FULLNAME_LOWER,
MO_PREVALENT_GENERA,
AB_LOOKUP,
AV_LOOKUP,
AB_AMINOGLYCOSIDES,
AB_AMINOPENICILLINS,
AB_ANTIFUNGALS,

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

View File

@ -1,103 +1,121 @@
"atc" "cid" "name" "atc_group" "synonyms" "oral_ddd" "oral_units" "iv_ddd" "iv_units"
"J05AF06" 441300 "Abacavir" "Nucleoside and nucleotide reverse transcriptase inhibitors" "Abacavir,Abacavir sulfate,Ziagen" 0.6 "g"
"J05AB01" 135398513 "Aciclovir" "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "Acicloftal,Aciclovier,Aciclovir,Aciclovirum,Activir,AcycloFoam,Acycloguanosine,Acyclovir,Acyclovir Lauriad,ACYCLOVIR SODIUM,Avirax,Cargosil,Cyclovir,Genvir,Gerpevir,Hascovir,Herpevir,Maynar,Poviral,Sitavig,Sitavir,Vipral,Virolex,Viropump,Virorax,Zovirax,Zovirax topical,Zyclir" 4 "g" 4 "g"
"J05AF08" 60871 "Adefovir dipivoxil" "Nucleoside and nucleotide reverse transcriptase inhibitors" "Adefovir di ester,Adefovir dipivoxil,Adefovir Dipivoxil,Adefovir dipivoxyl,Adefovir pivoxil,Adefovirdipivoxl,Bisadenine,BISADENINE,BisPMEA,Hepsera,Preveon,YouHeDing" 10 "mg"
"J05AE05" 65016 "Amprenavir" "Protease inhibitors" "Agenerase,Amprenavir,Amprenavirum,Prozei,Vertex" 1.2 "g"
"J05AP06" 16076883 "Asunaprevir" "Antivirals for treatment of HCV infections" "Asunaprevir,Sunvepra"
"J05AE08" 148192 "Atazanavir" "Protease inhibitors" "Atazanavir,Atazanavir Base,Latazanavir,Reyataz,Zrivada" 0.3 "g"
"J05AR15" 86583336 "Atazanavir and cobicistat" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR23" "Atazanavir and ritonavir" "Antivirals for treatment of HIV infections, combinations" "" 0.3 "g"
"J05AP03" 10324367 "Boceprevir" "Antivirals for treatment of HCV infections" "Bocepravir,Boceprevir,Victrelis" 2.4 "g"
"J05AB15" 446727 "Brivudine" "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "Bridic,Brivox,Brivudin,Brivudina,Brivudine,Brivudinum,BrVdUrd,Helpin,Zerpex,Zostex" 0.125 "g"
"J05AB12" 60613 "Cidofovir" "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "Cidofovir,Cidofovir anhydrous,Cidofovir gel,Cidofovirum,Forvade,Vistide" 25 "mg"
"J05AF12" 73115 "Clevudine" "Nucleoside and nucleotide reverse transcriptase inhibitors" "Clevudine,Levovir,Revovir" 30 "mg"
"J05AP07" 25154714 "Daclatasvir" "Antivirals for treatment of HCV infections" "Daclatasvir,Daklinza" 60 "mg"
"J05AE10" 213039 "Darunavir" "Protease inhibitors" "Darunavir,Darunavirum,Prezista,Prezista Naive" 1.2 "g"
"J05AR14" "Darunavir and cobicistat" "Antivirals for treatment of HIV infections, combinations" ""
"J05AP09" 56640146 "Dasabuvir" "Antivirals for treatment of HCV infections" "Dasabuvir" 0.5 "g"
"J05AP52" "Dasabuvir, ombitasvir, paritaprevir and ritonavir" "Antivirals for treatment of HCV infections" ""
"J05AG02" 5625 "Delavirdine" "Non-nucleoside reverse transcriptase inhibitors" "BHAP der,Delavirdin,Delavirdina,Delavirdine,Delavirdinum,PIPERAZINE,Rescriptor" 1.2 "g"
"J05AF02" 135398739 "Didanosine" "Nucleoside and nucleotide reverse transcriptase inhibitors" "Didanosina,Didanosine,Didanosinum,Dideoxyinosine,DIDEOXYINOSINE,Hypoxanthine ddN,Videx,Videx EC" 0.4 "g"
"J05AX12" 54726191 "Dolutegravir" "Other antivirals" "Dolutegravir,Dolutegravir Sodium,Soltegravir,Tivicay" 50 "mg"
"J05AR21" 131801472 "Dolutegravir and rilpivirine" "Antivirals for treatment of HIV infections, combinations" ""
"J05AG06" 58460047 "Doravirine" "Non-nucleoside reverse transcriptase inhibitors" "Doravirine,Pifeltro"
"J05AG03" 64139 "Efavirenz" "Non-nucleoside reverse transcriptase inhibitors" "Efavirenz,Efavirenzum,Eravirenz,Stocrin,Strocin,Sustiva" 0.6 "g"
"J05AP54" 91669168 "Elbasvir and grazoprevir" "Antivirals for treatment of HCV infections" ""
"J05AX11" 5277135 "Elvitegravir" "Other antivirals" "Elvitegravir,Vitekta"
"J05AF09" 60877 "Emtricitabine" "Nucleoside and nucleotide reverse transcriptase inhibitors" "Coviracil,Emtricitabin,Emtricitabina,Emtricitabine,Emtricitabinum,Emtritabine,Emtriva,Racivir" 0.2 "g"
"J05AR17" 90469070 "Emtricitabine and tenofovir alafenamide" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR20" "Emtricitabine, tenofovir alafenamide and bictegravir" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR19" "Emtricitabine, tenofovir alafenamide and rilpivirine" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR22" "Emtricitabine, tenofovir alafenamide, darunavir and cobicistat" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR18" "Emtricitabine, tenofovir alafenamide, elvitegravir and cobicistat" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR06" "Emtricitabine, tenofovir disoproxil and efavirenz" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR08" "Emtricitabine, tenofovir disoproxil and rilpivirine" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR09" "Emtricitabine, tenofovir disoproxil, elvitegravir and cobicistat" "Antivirals for treatment of HIV infections, combinations" ""
"J05AX07" 16130199 "Enfuvirtide" "Other antivirals" "Enfurvitide,Enfuvirtide,Fuzeon,Pentafuside" 0.18 "g"
"J05AX17" 10089466 "Enisamium iodide" "Other antivirals" "Enisamium iodide" 1.5 "g"
"J05AF10" 135398508 "Entecavir" "Nucleoside and nucleotide reverse transcriptase inhibitors" "Baraclude,Entecavir,Entecavir anhydrous,Entecavirum" 0.5 "mg"
"J05AG04" 193962 "Etravirine" "Non-nucleoside reverse transcriptase inhibitors" "DAPY deriv,Etravine,Etravirine,Intelence" 0.4 "g"
"J05AP04" 42601552 "Faldaprevir" "Antivirals for treatment of HCV infections" "Faldaprevir"
"J05AB09" 3324 "Famciclovir" "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "Famciclovir,Famciclovirum,Famvir,Oravir" 0.75 "g"
"J05AE07" 131536 "Fosamprenavir" "Protease inhibitors" "Amprenavir phosphate,Fosamprenavir,Lexiva,Telzir" 1.4 "g"
"J05AD01" 3415 "Foscarnet" "Phosphonic acid derivatives" "Forscarnet,Forscarnet sodium,Foscarmet,Foscarnet,Phosphonoformate,Phosphonoformic acid" 6.5 "g"
"J05AD02" 546 "Fosfonet" "Phosphonic acid derivatives" "Fosfonet,Fosfonet sodium,Fosfonet Sodium,Fosfonoacetate,Fosfonoacetic acid,Phosphonacetate,Phosphonacetic acid"
"J05AB06" 135398740 "Ganciclovir" "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "Citovirax,Cymevan,Cymeven,Cymevene,Cytovene,Cytovene IV,Ganciclovir,Ganciclovirum,Gancyclovir,Hydroxyacyclovir,Virgan,Vitrasert,Zirgan" 3 "g" 0.5 "g"
"J05AP57" "Glecaprevir and pibrentasvir" "Antivirals for treatment of HCV infections" ""
"J05AX23" "Ibalizumab" "Other antivirals" ""
"J05AB02" 5905 "Idoxuridine" "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "Antizona,Dendrid,Emanil,Heratil,Herpesil,Herpid,Herpidu,Herplex,HERPLEX,Herplex liquifilm,Idexur,Idossuridina,Idoxene,Idoxuridin,Idoxuridina,Idoxuridine,Idoxuridinum,Idu Oculos,Iducher,Idulea,Iduoculos,Iduridin,Iduviran,Iododeoxyridine,Iododeoxyuridine,Iodoxuridine,Joddeoxiuridin,Kerecid,Kerecide,Ophthalmadine,Spectanefran,Stoxil,Synmiol,Virudox"
"J05AE02" 5362440 "Indinavir" "Protease inhibitors" "Compound J,Crixivan,Indinavir,Indinavir anhydrous,Propolis+Indinavir" 2.4 "g"
"J05AX05" 135449284 "Inosine pranobex" "Other antivirals" "Aviral,Delimmun,Immunovir,Imunovir,Inosine pranobex,Inosiplex,Isoprinosin,Isoprinosina,Isoprinosine,Isoviral,Methisoprinol,Methysoprinol,Metisoprinol,Viruxan" 3 "g"
"J05AF05" 60825 "Lamivudine" "Nucleoside and nucleotide reverse transcriptase inhibitors" "Epivir,Hepitec,Heptivir,Heptodin,Heptovir,Lamivir,Lamivudin,Lamivudina,Lamivudine,Lamivudinum,Zeffix" 0.3 "g"
"J05AR02" "Lamivudine and abacavir" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR16" 73386700 "Lamivudine and raltegravir" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR12" "Lamivudine and tenofovir disoproxil" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR13" "Lamivudine, abacavir and dolutegravir" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR24" "Lamivudine, tenofovir disoproxil and doravirine" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR11" "Lamivudine, tenofovir disoproxil and efavirenz" "Antivirals for treatment of HIV infections, combinations" ""
"J05AX18" 45138674 "Letermovir" "Other antivirals" "Letermovir,Prevymis" 0.48 "g" 0.48 "g"
"J05AR10" 11979606 "Lopinavir and ritonavir" "Antivirals for treatment of HIV infections, combinations" "Aluvia,Kaletra" 0.8 "g"
"J05AX02" 24839946 "Lysozyme" "Other antivirals" "Lysozyme chloride,Lysozyme Chloride,Lysozyme G"
"J05AX09" 3002977 "Maraviroc" "Other antivirals" "Celsentri,Maraviroc,Selzentry" 0.6 "g"
"J05AX10" 471161 "Maribavir" "Other antivirals" "Benzimidavir,Camvia,Maribavir"
"J05AA01" 667492 "Metisazone" "Thiosemicarbazones" "Kemoviran,Marboran,Marborane,Methisazon,Methisazone,Methsazone,Metisazon,Metisazona,Metisazone,Metisazonum,Viruzona"
"J05AX01" 71655 "Moroxydine" "Other antivirals" "Bimolin,Flumidine,Influmine,Moroxidina,Moroxydine,Moroxydinum,Vironil,Virugon,Virumin,Wirumin" 0.3 "g"
"J05AE04" 64143 "Nelfinavir" "Protease inhibitors" "Nelfinavir,Viracept" 2.25 "g"
"J05AG01" 4463 "Nevirapine" "Non-nucleoside reverse transcriptase inhibitors" "Nevirapine,Nevirapine anhydrous,Viramune,Viramune IR,Viramune XR" 0.4 "g"
"J05AP53" "Ombitasvir, paritaprevir and ritonavir" "Antivirals for treatment of HCV infections" ""
"J05AH02" 65028 "Oseltamivir" "Neuraminidase inhibitors" "Agucort,Oseltamivir,Tamiflu,Tamvir" 0.15 "g"
"J05AB13" 135398748 "Penciclovir" "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "Adenovir,Denavir,Penciceovir,Penciclovir,Penciclovirum,Pencyclovir,Vectavir"
"J05AX21" 9942657 "Pentanedioic acid imidazolyl ethanamide" "Other antivirals" "Ingamine" 90 "mg"
"J05AH03" 154234 "Peramivir" "Neuraminidase inhibitors" "PeramiFlu,Peramivir,Rapiacta,RAPIVAB"
"J05AX06" 1684 "Pleconaril" "Other antivirals" "Picovir,Pleconaril,Pleconarilis"
"J05AX08" 54671008 "Raltegravir" "Other antivirals" "Isentress,Raltegravir" 0.8 "g"
"J05AP01" 37542 "Ribavirin" "Antivirals for treatment of HCV infections" "Copegus,Cotronak,Drug: Ribavirin,Ravanex,Rebetol,Rebetron,Rebretron,Ribacine,Ribamide,Ribamidil,Ribamidyl,Ribasphere,Ribavirin,Ribavirin Capsules,Ribavirina,Ribavirine,Ribavirinum,Ribovirin,Tribavirin,Varazid,Vilona,Viramid,Viramide,Virazid,Virazide,Virazole" 1 "g"
"J05AG05" 6451164 "Rilpivirine" "Non-nucleoside reverse transcriptase inhibitors" "Edurant,Rilpivirine" 25 "mg"
"J05AC02" 5071 "Rimantadine" "Cyclic amines" "Remantadine,Riamantadine,Rimant,RIMANTADIN,Rimantadin A,Rimantadina,Rimantadine,Rimantadinum" 0.2 "g"
"J05AE03" 392622 "Ritonavir" "Protease inhibitors" "Norvir,Norvir Sec,Norvir Softgel,Ritonavir,Ritonavire,Ritonavirum" 1.2 "g"
"J05AE01" 441243 "Saquinavir" "Protease inhibitors" "Fortovase,Invirase,Saquinavir" 1.8 "g"
"J05AP05" 24873435 "Simeprevir" "Antivirals for treatment of HCV infections" "Olysio,Simeprevir sodium" 0.15 "g"
"J05AP08" 45375808 "Sofosbuvir" "Antivirals for treatment of HCV infections" "Hepcinat,Hepcvir,Sofosbuvir,Sovaldi,SOVALDI,SoviHep" 0.4 "g"
"J05AP51" 72734365 "Sofosbuvir and ledipasvir" "Antivirals for treatment of HCV infections" ""
"J05AP55" 91885554 "Sofosbuvir and velpatasvir" "Antivirals for treatment of HCV infections" "Epclusa Tablet"
"J05AP56" "Sofosbuvir, velpatasvir and voxilaprevir" "Antivirals for treatment of HCV infections" ""
"J05AF04" 18283 "Stavudine" "Nucleoside and nucleotide reverse transcriptase inhibitors" "Estavudina,Sanilvudine,Stavudin,Stavudine,Stavudinum,Zerit Xr,Zerut XR" 80 "mg"
"J05AR07" 15979285 "Stavudine, lamivudine and nevirapine" "Antivirals for treatment of HIV infections, combinations" "STAVUDIINE"
"J05AP02" 3010818 "Telaprevir" "Antivirals for treatment of HCV infections" "Incivek,Incivo,Telaprevir,Telavic" 2.25 "g"
"J05AF11" 159269 "Telbivudine" "Nucleoside and nucleotide reverse transcriptase inhibitors" "Epavudine,Sebivo,Telbivudin,Telbivudine,Tyzeka" 0.6 "g"
"J05AF13" 9574768 "Tenofovir alafenamide" "Nucleoside and nucleotide reverse transcriptase inhibitors" "Vemlidy" 25 "mg"
"J05AF07" 5481350 "Tenofovir disoproxil" "Nucleoside and nucleotide reverse transcriptase inhibitors" "BisPMPA,PMPA prodrug,Tenofovir,Viread" 0.245 "g"
"J05AR03" "Tenofovir disoproxil and emtricitabine" "Antivirals for treatment of HIV infections, combinations" ""
"J05AX19" 5475 "Tilorone" "Other antivirals" "Amiksin,Amixin,Amixin IC,Amyxin,Tiloron,Tilorona,Tilorone,Tiloronum" 0.125 "g"
"J05AE09" 54682461 "Tipranavir" "Protease inhibitors" "Aptivus,Tipranavir" 1 "g"
"J05AC03" 64377 "Tromantadine" "Cyclic amines" "Tromantadina,Tromantadine,Tromantadinum,Viruserol"
"J05AX13" 131411 "Umifenovir" "Other antivirals" "Arbidol,Arbidol base,Umifenovir" 0.8 "g"
"J05AB11" 135398742 "Valaciclovir" "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "Talavir,Valaciclovir,Valaciclovirum,ValACV,Valcivir,Valcyclovir,Valtrex,Virval,Zelitrex" 3 "g"
"J05AB14" 135413535 "Valganciclovir" "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "Cymeval,Valganciclovir" 0.9 "g"
"J05AB03" 21704 "Vidarabine" "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "Adenine arabinoside,Araadenosine,Arabinoside adenine,Arabinosyl adenine,Arabinosyladenine,Spongoadenosine,Vidarabin,Vidarabina,Vidarabine,Vidarabine anhydrous,Vidarabinum,Vira A,Vira ATM"
"J05AF03" 24066 "Zalcitabine" "Nucleoside and nucleotide reverse transcriptase inhibitors" "Dideoxycytidine,Interferon AD + ddC,Zalcitabine,Zalcitibine" 2.25 "mg"
"J05AH01" 60855 "Zanamivir" "Neuraminidase inhibitors" "MODIFIED SIALIC ACID,Relenza,Zanamavir,Zanamir,Zanamivi,Zanamivir,Zanamivir hydrate"
"J05AF01" 35370 "Zidovudine" "Nucleoside and nucleotide reverse transcriptase inhibitors" "Azidothymidine,AZT Antiviral,Beta interferon,Compound S,Propolis+AZT,Retrovir,Zidovudina,Zidovudine,ZIDOVUDINE,Zidovudine EP III,Zidovudinum" 0.6 "g" 0.6 "g"
"J05AR01" "Zidovudine and lamivudine" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR04" "Zidovudine, lamivudine and abacavir" "Antivirals for treatment of HIV infections, combinations" ""
"J05AR05" "Zidovudine, lamivudine and nevirapine" "Antivirals for treatment of HIV infections, combinations" ""
"av" "name" "atc" "cid" "atc_group" "synonyms" "oral_ddd" "oral_units" "iv_ddd" "iv_units" "loinc"
"ABA" "Abacavir" "J05AF06" 441300 "Nucleoside and nucleotide reverse transcriptase inhibitors" "abacavir sulfate,avacavir,ziagen" 0.6 "g" "29113-8,78772-1,78773-9,79134-3,80118-3"
"ACI" "Aciclovir" "J05AB01" 135398513 "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "acicloftal,aciclovier,aciclovirum,activir,acyclofoam,acycloguanosine,acyclovir,acyclovir lauriad,avaclyr,cargosil,cyclovir,genvir,gerpevir,hascovir,maynar,novirus,poviral,sitavig,sitavir,vipral,viropump,virorax,zovirax,zyclir" 4 "g" 4 "g" ""
"ADD" "Adefovir dipivoxil" "J05AF08" 60871 "Nucleoside and nucleotide reverse transcriptase inhibitors" "adefovir di,adefovir di ester,adefovir dipivoxyl,adefovir pivoxil,adefovirdipivoxl,bisadenine,bispmea,hepsera,preveon,youheding" 10 "mg" ""
"AME" "Amenamevir" "J05AX26" 11397521 "Other antivirals" "amenalief" 0.4 "g" ""
"AMP" "Amprenavir" "J05AE05" 65016 "Protease inhibitors" "agenerase,carbamate,prozei" 1.2 "g" "29114-6,31028-4,78791-1"
"ASU" "Asunaprevir" "J05AP06" 16076883 "Antivirals for treatment of HCV infections" "sunvepra,sunvepratrade" 0.2 "g" ""
"ATA" "Atazanavir" "J05AE08" 148192 "Protease inhibitors" "atazanavir base,latazanavir,reyataz,zrivada" 0.3 "g" "41470-6,78796-0,78797-8,80142-3,80143-1"
"ATA+COBI" "Atazanavir/cobicistat" "J05AR15" 86583336 "Antivirals for treatment of HIV infections, combinations" "" ""
"ATA+RIT" "Atazanavir/ritonavir" "J05AR23" 25134325 "Antivirals for treatment of HIV infections, combinations" "" 0.3 "g" ""
"BAM" "Baloxavir marboxil" "J05AX25" 124081896 "Other antivirals" "xofluza" 40 "mg" ""
"BOC" "Boceprevir" "J05AP03" 10324367 "Antivirals for treatment of HCV infections" "victrelis" 2.4 "g" ""
"BRIN" "Brincidofovir" "J05AB17" 483477 "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "cidofovir prodrug,tembexa" ""
"BRIV" "Brivudine" "J05AB15" 446727 "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "bridic,brivox,brivudin,brivudina,brivudinum,brvdurd,helpin,zerpex,zostex" 0.125 "g" ""
"BUL" "Bulevirtide" "J05AX28" "Other antivirals" "" ""
"CAB" "Cabotegravir" "J05AJ04" 54713659 "Integrase inhibitors" "cabenuva" 30 "mg" 10 "mg" ""
"CID" "Cidofovir" "J05AB12" 60613 "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "cidofovir anhydrous,cidofovir gel,cidofovir hydrate,cidofovirum,forvade,hpmpc dihydrate,phosphonic acid,vistide" 25 "mg" ""
"CLE" "Clevudine" "J05AF12" 73115 "Nucleoside and nucleotide reverse transcriptase inhibitors" "levovir,revovir" 30 "mg" ""
"COBL" "Coblopasvir" "J05AP12" 58316387 "Antivirals for treatment of HCV infections" "" ""
"DAC" "Daclatasvir" "J05AP07" 25154714 "Antivirals for treatment of HCV infections" "daklinza" 60 "mg" ""
"DAC+ASU+BEC" "Daclatasvir/asunaprevir/beclabuvir" "J05AP58" "Antivirals for treatment of HCV infections" "" ""
"DAR" "Darunavir" "J05AE10" 213039 "Protease inhibitors" "carbamate,darunavirum,derunavir,prezista,prezista naive" 1.2 "g" "57954-0"
"DAR+COBI" "Darunavir/cobicistat" "J05AR14" 57327017 "Antivirals for treatment of HIV infections, combinations" "" ""
"DAR+RIT" "Darunavir/ritonavir" "J05AR26" "Antivirals for treatment of HIV infections, combinations" "" ""
"DAS" "Dasabuvir" "J05AP09" 56640146 "Antivirals for treatment of HCV infections" "" 0.5 "g" ""
"DAS+OMB+PAR+RIT" "Dasabuvir/ombitasvir/paritaprevir/ritonavir" "J05AP52" "Antivirals for treatment of HCV infections" "" ""
"DEL" "Delavirdine" "J05AG02" 5625 "Non-nucleoside reverse transcriptase inhibitors" "piperazine,rescriptor" 1.2 "g" "27082-7,29115-3"
"DID" "Didanosine" "J05AF02" 135398739 "Nucleoside and nucleotide reverse transcriptase inhibitors" "didanosina,didanosinum,dideoxyinosine,hypoxanthine ddn,videx ec" 0.4 "g" "29116-1,48307-3"
"DOL" "Dolutegravir" "J05AJ03" 54726191 "Integrase inhibitors" "dolutegravir dtg,soltegravir,tivicay" 50 "mg" ""
"DOL+RIL" "Dolutegravir/rilpivirine" "J05AR21" 131801472 "Antivirals for treatment of HIV infections, combinations" "" ""
"DOR" "Doravirine" "J05AG06" 58460047 "Non-nucleoside reverse transcriptase inhibitors" "pifeltro" 0.1 "g" ""
"EFA" "Efavirenz" "J05AG03" 64139 "Non-nucleoside reverse transcriptase inhibitors" "efavirenz teva,efavirenzum,eravirenz,stocrin,strocin,sustiva,viraday" 0.6 "g" "29117-9,33928-3,51907-4,51908-2"
"ELB" "Elbasvir" "J05AP10" 71661251 "Antivirals for treatment of HCV infections" "methyl carbamate" 50 "mg" ""
"ELB+GRA" "Elbasvir/grazoprevir" "J05AP54" 91669168 "Antivirals for treatment of HCV infections" "zepatier" ""
"ELV" "Elvitegravir" "J05AJ02" 5277135 "Integrase inhibitors" "vitekta" "88986-5"
"EMT" "Emtricitabine" "J05AF09" 60877 "Nucleoside and nucleotide reverse transcriptase inhibitors" "coviracil,emtricitabinum,emtritabine,emtriva,racivir" 0.2 "g" ""
"EMT+TEA" "Emtricitabine/tenofovir alafenamide" "J05AR17" 90469070 "Antivirals for treatment of HIV infections, combinations" "descovy" ""
"EMT+TEA+BIC" "Emtricitabine/tenofovir alafenamide/bictegravir" "J05AR20" "Antivirals for treatment of HIV infections, combinations" "" ""
"EMT+TEA+RIL" "Emtricitabine/tenofovir alafenamide/rilpivirine" "J05AR19" "Antivirals for treatment of HIV infections, combinations" "" ""
"EMT+TEA+DAR+COBI" "Emtricitabine/tenofovir alafenamide/darunavir/cobicistat" "J05AR22" "Antivirals for treatment of HIV infections, combinations" "" ""
"EMT+TEA+ELV+COBI" "Emtricitabine/tenofovir alafenamide/elvitegravir/cobicistat" "J05AR18" "Antivirals for treatment of HIV infections, combinations" "" ""
"EMT+TED+EFA" "Emtricitabine/tenofovir disoproxil/efavirenz" "J05AR06" "Antivirals for treatment of HIV infections, combinations" "" ""
"EMT+TED+RIL" "Emtricitabine/tenofovir disoproxil/rilpivirine" "J05AR08" "Antivirals for treatment of HIV infections, combinations" "" ""
"EMT+TED+ELV+COBI" "Emtricitabine/tenofovir disoproxil/elvitegravir/cobicistat" "J05AR09" "Antivirals for treatment of HIV infections, combinations" "" ""
"ENF" "Enfuvirtide" "J05AX07" 16130199 "Other antivirals" "enfurvitide,fuzeon,pentafuside" 0.18 "g" ""
"ENI" "Enisamium iodide" "J05AX17" 10089466 "Other antivirals" "amizon" 1.5 "g" ""
"ENT" "Entecavir" "J05AF10" 135398508 "Nucleoside and nucleotide reverse transcriptase inhibitors" "baraclude,entecavir anhydrous" 0.5 "mg" ""
"ETR" "Etravirine" "J05AG04" 193962 "Non-nucleoside reverse transcriptase inhibitors" "dapy deriv,etravine,intelence" 0.4 "g" "57961-5"
"FAL" "Faldaprevir" "J05AP04" 42601552 "Antivirals for treatment of HCV infections" "" ""
"FAM" "Famciclovir" "J05AB09" 3324 "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "famciclovirum,famvir,oravir" 0.75 "g" ""
"FAV" "Favipiravir" "J05AX27" 492405 "Other antivirals" "avigan,fapilavir,favilavir" 1.6 "g" ""
"FOSA" "Fosamprenavir" "J05AE07" 131536 "Protease inhibitors" "amprenavir phosphate,carbamate,lexiva,telzir" 1.4 "g" ""
"FOSC" "Foscarnet" "J05AD01" 3415 "Phosphonic acid derivatives" "forscarnet,foscarmet,foscavir,phosphonoformate,phosphonoformic acid" 6.5 "g" ""
"FOSF" "Fosfonet" "J05AD02" 546 "Phosphonic acid derivatives" "fosfonet sodium,fosfonoacetate,fosfonoacetic acid,phosphonacetate,phosphonacetic acid,phosphonoaceticacid" ""
"FOST" "Fostemsavir" "J05AX29" 11319217 "Other antivirals" "rukobia" 1.2 "g" ""
"GAN" "Ganciclovir" "J05AB06" 135398740 "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "citovirax,cymevan,cymeven,cymevene,cytovene,ganciclovirum,gancyclovir,hydroxyacyclovir,virgan,vitrasert,zirgan" 3 "g" 0.5 "g" "15367-6,25256-9,59798-9,59799-7,60077-5,60078-3"
"GLE+PIB" "Glecaprevir/pibrentasvir" "J05AP57" 85471918 "Antivirals for treatment of HCV infections" "" ""
"GRA" "Grazoprevir" "J05AP11" 44603531 "Antivirals for treatment of HCV infections" "" 0.1 "g" ""
"IBA" "Ibalizumab" "J05AX23" "Other antivirals" "" ""
"IDO" "Idoxuridine" "J05AB02" 5905 "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "antizona,dendrid,heratil,herplex,idossuridina,idoxene,idoxuridin,idoxuridina,idoxuridinum,iduoculos,iduridin,iododeoxyridine,iododeoxyuridine,iodoxuridine,joddeoxiuridin,kerecid,stoxil,virudox" ""
"IND" "Indinavir" "J05AE02" 5362440 "Protease inhibitors" "compound j,crixivan,indinavir anhydrous,propolis+indinavir" 2.4 "g" "29118-7,31033-4,51918-1"
"INP" "Inosine pranobex" "J05AX05" 135449284 "Other antivirals" "aviral,delimmun,groprinosin,immunovir,imunovir,imunoviral,inosiplex,isoprinosin,isoprinosina,isoprinosine,isoviral,methisoprinol,modimmunal,pranosina,pranosine,viruxan" 3 "g" ""
"LAM" "Lamivudine" "J05AF05" 60825 "Nucleoside and nucleotide reverse transcriptase inhibitors" "epivir,hepitec,heptivir,heptodin,heptovir,lamivir,lamivudeine,lamivudine teva,lamivudinum,virolam,zeffix" 0.3 "g" "29119-5,49226-4"
"LAM+ABA" "Lamivudine/abacavir" "J05AR02" "Antivirals for treatment of HIV infections, combinations" "" ""
"LAM+DOL" "Lamivudine/dolutegravir" "J05AR25" "Antivirals for treatment of HIV infections, combinations" "" ""
"LAM+RAL" "Lamivudine/raltegravir" "J05AR16" 73386700 "Antivirals for treatment of HIV infections, combinations" "" ""
"LAM+TED" "Lamivudine/tenofovir disoproxil" "J05AR12" "Antivirals for treatment of HIV infections, combinations" "" ""
"LAM+ABA+DOL" "Lamivudine/abacavir/dolutegravir" "J05AR13" "Antivirals for treatment of HIV infections, combinations" "" ""
"LAM+TED+DOL" "Lamivudine/tenofovir disoproxil/dolutegravir" "J05AR27" "Antivirals for treatment of HIV infections, combinations" "" ""
"LAM+TED+DOR" "Lamivudine/tenofovir disoproxil/doravirine" "J05AR24" "Antivirals for treatment of HIV infections, combinations" "" ""
"LAM+TED+EFA" "Lamivudine/tenofovir disoproxil/efavirenz" "J05AR11" "Antivirals for treatment of HIV infections, combinations" "" ""
"LAN" "Laninamivir" "J05AH04" 502272 "Neuraminidase inhibitors" "" ""
"LEN" "Lenacapavir" "J05AX31" 133082658 "Other antivirals" "" ""
"LET" "Letermovir" "J05AX18" 45138674 "Other antivirals" "acetic acid,prevymis" 0.48 "g" 0.48 "g" ""
"LOP+RIT" "Lopinavir/ritonavir" "J05AR10" 11979606 "Antivirals for treatment of HIV infections, combinations" "aluvia,kaletra,lopimune" 0.8 "g" ""
"LYS" "Lysozyme" "J05AX02" 16130991 "Other antivirals" "" ""
"MARA" "Maraviroc" "J05AX09" 3002977 "Other antivirals" "celsentri,selzentry" 0.6 "g" "88987-3"
"MARI" "Maribavir" "J05AX10" 471161 "Other antivirals" "benzimidavir,camvia" ""
"MET" "Metisazone" "J05AA01" 667492 "Thiosemicarbazones" "kemoviran,marboran,marborane,methisazon,methisazone,methsazone,metisazon,metisazona,metisazonum,viruzona" ""
"MOR" "Moroxydine" "J05AX01" 71655 "Other antivirals" "bimolin,moroxidina,moroxydinum,virugon,virumin,wirumin" 0.3 "g" ""
"NEL" "Nelfinavir" "J05AE04" 64143 "Protease inhibitors" "viracept" 2.25 "g" "29120-3,32647-0,35113-0,51923-1"
"NEV" "Nevirapine" "J05AG01" 4463 "Non-nucleoside reverse transcriptase inhibitors" "nevirapine anhydrous,nevirapine teva,nevirapine),viramune,viramune ir,viramune xr" 0.4 "g" "29121-1,32646-2,51925-6"
"OMB+PAR+RIT" "Ombitasvir/paritaprevir/ritonavir" "J05AP53" "Antivirals for treatment of HCV infections" "" ""
"OSE" "Oseltamivir" "J05AH02" 65028 "Neuraminidase inhibitors" "agucort,tamiflu,tamvir" 0.15 "g" ""
"PEN" "Penciclovir" "J05AB13" 135398748 "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "adenovir,denavir,penciceovir,penciclovirum,pencyclovir,vectavir" "60140-1,60141-9"
"PAIE" "Pentanedioic acid imidazolyl ethanamide" "J05AX21" 9942657 "Other antivirals" "ingamine" 90 "mg" ""
"PER" "Peramivir" "J05AH03" 154234 "Neuraminidase inhibitors" "peramiflu,peramivir anhydrous,rapiacta,rapivab" 0.6 "g" ""
"PLE" "Pleconaril" "J05AX06" 1684 "Other antivirals" "picovir,pleconarilis" ""
"RAL" "Raltegravir" "J05AJ01" 54671008 "Integrase inhibitors" "isentress" 0.8 "g" "72835-2"
"REM" "Remdesivir" "J05AB16" 121304016 "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "veklury" 0.1 "g" ""
"RIB" "Ribavirin" "J05AP01" 37542 "Antivirals for treatment of HCV infections" "copegus,cotronak,ravanex,rebetol,rebetron,rebretron,ribacine,ribamide,ribamidil,ribamidyl,ribasphere,ribavirin capsules,ribavirin mylan,ribavirin teva,ribavirina,ribavirine,ribavirinum,tribavirin,varazid,vilona,viramid,virazid,virazide,virazole" 1 "g" "41469-8"
"RIL" "Rilpivirine" "J05AG05" 6451164 "Non-nucleoside reverse transcriptase inhibitors" "edurant,rilpivirina" 25 "mg" 15 "mg" "80547-3"
"RIM" "Rimantadine" "J05AC02" 5071 "Cyclic amines" "ethanamine,rimant,rimantadin,rimantadin a,rimantadina,rimantadinum" 0.2 "g" ""
"RIT" "Ritonavir" "J05AE03" 392622 "Protease inhibitors" "empetus,norvir,norvir softgel,ritomune,ritonavirum,ritovir,viekirax,viriton" 1.2 "g" "29122-9,31027-6,51929-8,51930-6"
"SAQ" "Saquinavir" "J05AE01" 441243 "Protease inhibitors" "fortovase,invirase,saquinavirum" 1.8 "g" "19051-2,29123-7,51932-2"
"SIM" "Simeprevir" "J05AP05" 24873435 "Antivirals for treatment of HCV infections" "olysio,simeprevir sodium" 0.15 "g" ""
"SOF" "Sofosbuvir" "J05AP08" 45375808 "Antivirals for treatment of HCV infections" "hepcinat,hepcvir,sovaldi,sovihep" 0.4 "g" ""
"SOF+LED" "Sofosbuvir/ledipasvir" "J05AP51" 72734365 "Antivirals for treatment of HCV infections" "harvoni" ""
"SOF+VEL" "Sofosbuvir/velpatasvir" "J05AP55" 91885554 "Antivirals for treatment of HCV infections" "epclusa,epclusa tablet" ""
"SOF+VEL+VOX" "Sofosbuvir/velpatasvir/voxilaprevir" "J05AP56" "Antivirals for treatment of HCV infections" "" ""
"STA" "Stavudine" "J05AF04" 18283 "Nucleoside and nucleotide reverse transcriptase inhibitors" "estavudina,sanilvudine,stavudinum,zerit xr,zerut xr" 80 "mg" "29124-5,49227-2"
"STA+LAM+NEV" "Stavudine/lamivudine/nevirapine" "J05AR07" 15979285 "Antivirals for treatment of HIV infections, combinations" "" ""
"TEC" "Tecovirimat" "J05AX24" 16124688 "Other antivirals" "" ""
"TELA" "Telaprevir" "J05AP02" 3010818 "Antivirals for treatment of HCV infections" "incivek,incivo,telavic" 2.25 "g" ""
"TELB" "Telbivudine" "J05AF11" 159269 "Nucleoside and nucleotide reverse transcriptase inhibitors" "epavudine,sebivo,telbivudin,tyzeka" 0.6 "g" ""
"TEA" "Tenofovir alafenamide" "J05AF13" 9574768 "Nucleoside and nucleotide reverse transcriptase inhibitors" "vemlidy" 25 "mg" ""
"TED" "Tenofovir disoproxil" "J05AF07" 5481350 "Nucleoside and nucleotide reverse transcriptase inhibitors" "bispmpa,pmpa prodrug,tenofovir,tenofovir bis,tenofovirdisoproxil,viread" 0.245 "g" ""
"TED+EMT" "Tenofovir disoproxil/emtricitabine" "J05AR03" "Antivirals for treatment of HIV infections, combinations" "" ""
"TIL" "Tilorone" "J05AX19" 5475 "Other antivirals" "amixin ic,tiloron,tilorona,tiloronum" 0.125 "g" ""
"TIP" "Tipranavir" "J05AE09" 54682461 "Protease inhibitors" "aptivus" 1 "g" "57383-2"
"TRO" "Tromantadine" "J05AC03" 64377 "Cyclic amines" "tromantadina,tromantadinum" ""
"UMI" "Umifenovir" "J05AX13" 131411 "Other antivirals" "arbidol,arbidol base" 0.8 "g" ""
"VALA" "Valaciclovir" "J05AB11" 135398742 "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "talavir,valacv,valacyclovir,valcivir,valcyclovir,valtrex,virval,zelitrex" 3 "g" ""
"VALG" "Valganciclovir" "J05AB14" 135413535 "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "cymeval" 0.9 "g" "74960-6"
"VID" "Vidarabine" "J05AB03" 21704 "Nucleosides and nucleotides excl. reverse transcriptase inhibitors" "adenine arabinoside,araadenosine,arabinoside adenine,arabinosyl adenine,arabinosyladenine,spongoadenosine,vidarabin,vidarabina,vidarabine anhydrous,vidarabinum,vira a,vira atm" 0.7 "g" ""
"ZAL" "Zalcitabine" "J05AF03" 24066 "Nucleoside and nucleotide reverse transcriptase inhibitors" "dideoxycytidine,interferon ad + ddc,zalcitibine" 2.25 "mg" "29125-2"
"ZAN" "Zanamivir" "J05AH01" 60855 "Neuraminidase inhibitors" "modified sialic acid,relenza,zanamavir,zanamivi,zanamivirhydrate" 1.2 "g" ""
"ZID" "Zidovudine" "J05AF01" 35370 "Nucleoside and nucleotide reverse transcriptase inhibitors" "azidothymidine,beta interferon,compound s,propolis+azt,retrovir,trizivir,zidovudina,zidovudinum" 0.6 "g" 0.6 "g" "29126-0,6894-0"
"ZID+LAM" "Zidovudine/lamivudine" "J05AR01" "Antivirals for treatment of HIV infections, combinations" "" ""
"ZID+LAM+ABA" "Zidovudine/lamivudine/abacavir" "J05AR04" "Antivirals for treatment of HIV infections, combinations" "" ""
"ZID+LAM+NEV" "Zidovudine/lamivudine/nevirapine" "J05AR05" "Antivirals for treatment of HIV infections, combinations" "" ""

Binary file not shown.

View File

@ -1 +1 @@
246da79545e045edac7c3ec445b3a04e
009fea3738cdb6390dccd470cb27f015

View File

@ -62,7 +62,7 @@ for (i in seq_len(nrow(antibiotics))) {
# sort and fix for empty values
for (i in 1:nrow(antibiotics)) {
loinc <- as.character(sort(unique(tolower(antibiotics[i, "loinc"][[1]]))))
antibiotics[i, "loinc"][[1]] <- ifelse(length(syn[!syn == ""]) == 0, list(""), list(loinc))
antibiotics[i, "loinc"][[1]] <- ifelse(length(loinc[!loinc == ""]) == 0, list(""), list(loinc))
}
# remember to update R/aa_globals.R for the documentation

View File

@ -192,7 +192,7 @@ abx2$abbr <- lapply(as.list(abx2$abbr), function(x) unlist(strsplit(x, "|", fixe
# vector with official names, returns vector with CIDs
get_CID <- function(ab) {
CID <- rep(NA_integer_, length(ab))
p <- progress_ticker(n = length(ab), min_time = 0)
p <- AMR:::progress_ticker(n = length(ab), min_time = 0)
for (i in 1:length(ab)) {
p$tick()
@ -248,7 +248,7 @@ antibiotics[is.na(CIDs), ] %>% View()
# returns list with synonyms (brand names), with CIDs as names
get_synonyms <- function(CID, clean = TRUE) {
synonyms <- rep(NA_character_, length(CID))
p <- progress_ticker(n = length(CID), min_time = 0)
p <- AMR:::progress_ticker(n = length(CID), min_time = 0)
for (i in 1:length(CID)) {
p$tick()

View File

@ -27,14 +27,18 @@
# how to conduct AMR data analysis: https://msberends.github.io/AMR/ #
# ==================================================================== #
# get all data from the WHOCC website
library(dplyr)
library(tidyr)
library(rvest)
# get all data from the WHOCC website
get_atc_table <- function(atc_group) {
# give as input J0XXX, like atc_group = "J05AB"
downloaded <- read_html(paste0("https://www.whocc.no/atc_ddd_index/?code=", atc_group, "&showdescription=no"))
table_title <- downloaded %>%
html_nodes(paste0('a[href="./?code=', atc_group, '"]')) %>%
html_nodes(paste0('a[href^="./?code=', atc_group, '&"]')) %>%
html_text()
table_title <- table_title[tolower(table_title) != "show text from guidelines"][1]
table_content <- downloaded %>%
html_nodes("table") %>%
html_table(header = TRUE) %>%
@ -59,12 +63,13 @@ get_atc_table <- function(atc_group) {
}
# these are the relevant groups for input: https://www.whocc.no/atc_ddd_index/?code=J05A (J05 only contains J05A)
atc_groups <- c("J05AA", "J05AB", "J05AC", "J05AD", "J05AE", "J05AF", "J05AG", "J05AH", "J05AP", "J05AR", "J05AX")
atc_groups <- c("J05AA", "J05AB", "J05AC", "J05AD", "J05AE", "J05AF", "J05AG", "J05AH", "J05AJ", "J05AP", "J05AR", "J05AX")
# get the first
antivirals <- get_atc_table(atc_groups[1])
# bind all others to it
for (i in 2:length(atc_groups)) {
message(atc_groups[i], "...")
antivirals <- rbind(antivirals, get_atc_table(atc_groups[i]))
}
@ -73,7 +78,8 @@ antivirals <- antivirals %>%
arrange(name) %>%
as.data.frame(stringsAsFactors = FALSE)
# add PubChem Compound ID (cid) and their trade names - functions are in file to create `antibiotics` data set
# add PubChem Compound ID (cid) and their trade names
# see `data-raw/reproduction_of_antibiotics` for get_CID() and get_synonyms()
CIDs <- get_CID(antivirals$name)
# these could not be found:
antivirals[is.na(CIDs), ] %>% View()
@ -92,7 +98,7 @@ synonyms <- lapply(
antivirals <- antivirals %>%
transmute(atc,
cid = CIDs,
cid = as.double(CIDs),
name,
atc_group,
synonyms = unname(synonyms),
@ -100,7 +106,79 @@ antivirals <- antivirals %>%
oral_units,
iv_ddd,
iv_units
)
) %>%
AMR:::dataset_UTF8_to_ASCII()
av_codes <- tibble(name = antivirals$name %>%
strsplit("(, | and )") %>%
unlist() %>%
unique() %>%
sort()) %>%
mutate(av_1st = toupper(abbreviate(name, minlength = 3, use.classes = FALSE))) %>%
filter(!name %in% c("acid", "dipivoxil", "disoproxil", "marboxil", "alafenamide"))
replace_with_av_code <- function(name) {
unname(av_codes$av_1st[match(name, av_codes$name)])
}
names_codes <- antivirals %>%
separate(name,
into = paste0("name", c(1:7)),
sep = "(, | and )",
remove = FALSE,
fill = "right") %>%
# remove empty columns
select(!where(function(x) all(is.na(x)))) %>%
mutate_at(vars(matches("name[1-9]")), replace_with_av_code) %>%
unite(av, matches("name[1-9]"), sep = "+", na.rm = TRUE) %>%
mutate(name = gsub("(, | and )", "/", name))
substr(names_codes$name, 1, 1) <- toupper(substr(names_codes$name, 1, 1))
antivirals <- bind_cols(
names_codes %>% select(av, name),
antivirals %>% select(-name)
)
class(antivirals$av) <- c("av", "character")
antivirals <- antivirals %>% AMR:::dataset_UTF8_to_ASCII()
# add loinc, see 'data-raw/loinc.R'
loinc_df <- read.csv("data-raw/Loinc.csv",
row.names = NULL,
stringsAsFactors = FALSE)
loinc_df <- loinc_df %>% filter(CLASS == "DRUG/TOX")
av_names <- antivirals %>%
pull(name) %>%
paste0(collapse = "|") %>%
paste0("(", ., ")")
antivirals$loinc <- as.list(rep(NA_character_, nrow(antivirals)))
for (i in seq_len(nrow(antivirals))) {
message(i)
loinc_ab <- loinc_df %>%
filter(COMPONENT %like% paste0("^", antivirals$name[i])) %>%
pull(LOINC_NUM)
if (length(loinc_ab) > 0) {
antivirals$loinc[i] <- list(loinc_ab)
}
}
# sort and fix for empty values
for (i in 1:nrow(antivirals)) {
loinc <- as.character(sort(unique(tolower(antivirals[i, "loinc", drop = TRUE][[1]]))))
antivirals[i, "loinc"][[1]] <- ifelse(length(loinc[!loinc == ""]) == 0, list(""), list(loinc))
}
# de-duplicate synonyms
for (i in 1:nrow(antivirals)) {
syn <- as.character(sort(unique(tolower(antivirals[i, "synonyms", drop = TRUE][[1]]))))
syn <- syn[!syn %in% tolower(antivirals[i, "name", drop = TRUE])]
antivirals[i, "synonyms"][[1]] <- ifelse(length(syn[!syn == ""]) == 0, list(""), list(syn))
}
antivirals <- antivirals %>% AMR:::dataset_UTF8_to_ASCII()
# check it
antivirals
# save it
usethis::use_data(antivirals, overwrite = TRUE)
usethis::use_data(antivirals, overwrite = TRUE, internal = FALSE, compress = "xz", version = 2)

Binary file not shown.

View File

@ -6,7 +6,7 @@ The `AMR` package is a [free and open-source](#copyright) R package with [zero d
This work was published in the Journal of Statistical Software (Volume 104(3); [DOI 10.18637/jss.v104.i03](https://doi.org/10.18637/jss.v104.i03)) and formed the basis of two PhD theses ([DOI 10.33612/diss.177417131](https://doi.org/10.33612/diss.177417131) and [DOI 10.33612/diss.192486375](https://doi.org/10.33612/diss.192486375)).
After installing this package, R knows [**~49,000 distinct microbial species**](./reference/microorganisms.html) and all [**~570 antibiotic, antimycotic and antiviral drugs**](./reference/antibiotics.html) by name and code (including ATC, EARS-Net, ASIARS-Net, PubChem, LOINC and SNOMED CT), and knows all about valid R/SI and MIC values. The integral breakpoint guidelines from CLSI and EUCAST are included from the last 10 years. It supports and can read any data format, including WHONET data. This package works on Windows, macOS and Linux with all versions of R since R-3.0 (April 2013). **It was designed to work in any setting, including those with very limited resources**. It was created for both routine data analysis and academic research at the Faculty of Medical Sciences of the [University of Groningen](https://www.rug.nl), in collaboration with non-profit organisations [Certe Medical Diagnostics and Advice Foundation](https://www.certe.nl) and [University Medical Center Groningen](https://www.umcg.nl), and is being [actively and durably maintained](./news) by two public healthcare organisations in the Netherlands.
After installing this package, R knows [**~49,000 distinct microbial species**](./reference/microorganisms.html) and all [**~600 antibiotic, antimycotic and antiviral drugs**](./reference/antibiotics.html) by name and code (including ATC, EARS-Net, ASIARS-Net, PubChem, LOINC and SNOMED CT), and knows all about valid R/SI and MIC values. The integral breakpoint guidelines from CLSI and EUCAST are included from the last 10 years. It supports and can read any data format, including WHONET data. This package works on Windows, macOS and Linux with all versions of R since R-3.0 (April 2013). **It was designed to work in any setting, including those with very limited resources**. It was created for both routine data analysis and academic research at the Faculty of Medical Sciences of the [University of Groningen](https://www.rug.nl), in collaboration with non-profit organisations [Certe Medical Diagnostics and Advice Foundation](https://www.certe.nl) and [University Medical Center Groningen](https://www.umcg.nl), and is being [actively and durably maintained](./news) by two public healthcare organisations in the Netherlands.
##### Used in 175 countries, translated to 16 languages

View File

@ -32,7 +32,7 @@ Welcome to the \code{AMR} package.
This work was published in the Journal of Statistical Software (Volume 104(3); \doi{10.18637/jss.v104.i03}) and formed the basis of two PhD theses (\doi{10.33612/diss.177417131} and \doi{10.33612/diss.192486375}).
After installing this package, \R knows ~49,000 distinct microbial species and all ~580 antibiotic, antimycotic and antiviral drugs by name and code (including ATC, EARS-NET, LOINC and SNOMED CT), and knows all about valid R/SI and MIC values. It supports any data format, including WHONET/EARS-Net data.
After installing this package, \R knows ~49,000 distinct microbial species and all ~600 antibiotic, antimycotic and antiviral drugs by name and code (including ATC, EARS-NET, LOINC and SNOMED CT), and knows all about valid R/SI and MIC values. It supports any data format, including WHONET/EARS-Net data.
This package is fully independent of any other \R package and works on Windows, macOS and Linux with all versions of \R since R-3.0.0 (April 2013). It was designed to work in any setting, including those with very limited resources. It was created for both routine data analysis and academic research at the Faculty of Medical Sciences of the University of Groningen, in collaboration with non-profit organisations Certe Medical Diagnostics and Advice and University Medical Center Groningen. This \R package is actively maintained and free software; you can freely use and distribute it for both personal and commercial (but not patent) purposes under the terms of the GNU General Public License version 2.0 (GPL-2), as published by the Free Software Foundation.

View File

@ -60,7 +60,7 @@ With using \code{collapse}, this function will return a \link{character}:\cr
\examples{
# mind the bad spelling of amoxicillin in this line,
# straight from a true health care record:
ab_from_text("28/03/2020 regular amoxicilliin 500mg po tds")
ab_from_text("28/03/2020 regular amoxicilliin 500mg po tid")
ab_from_text("500 mg amoxi po and 400mg cipro iv")
ab_from_text("500 mg amoxi po and 400mg cipro iv", type = "dose")

View File

@ -4,7 +4,7 @@
\name{antibiotics}
\alias{antibiotics}
\alias{antivirals}
\title{Data Sets with 585 Antimicrobial Drugs}
\title{Data Sets with 603 Antimicrobial Drugs}
\format{
\subsection{For the \link{antibiotics} data set: a \link[tibble:tibble]{tibble} with 483 observations and 14 variables:}{
\itemize{
@ -25,21 +25,23 @@
}
}
\subsection{For the \link{antivirals} data set: a \link[tibble:tibble]{tibble} with 102 observations and 9 variables:}{
\subsection{For the \link{antivirals} data set: a \link[tibble:tibble]{tibble} with 120 observations and 11 variables:}{
\itemize{
\item \code{av}\cr Antibiotic ID as used in this package (such as \code{AMC}), using the official EARS-Net (European Antimicrobial Resistance Surveillance Network) codes where available
\item \code{name}\cr Official name as used by WHONET/EARS-Net or the WHO
\item \code{atc}\cr ATC codes (Anatomical Therapeutic Chemical) as defined by the WHOCC
\item \code{cid}\cr Compound ID as found in PubChem
\item \code{name}\cr Official name as used by WHONET/EARS-Net or the WHO
\item \code{atc_group}\cr Official pharmacological subgroup (3rd level ATC code) as defined by the WHOCC
\item \code{synonyms}\cr Synonyms (often trade names) of a drug, as found in PubChem based on their compound ID
\item \code{oral_ddd}\cr Defined Daily Dose (DDD), oral treatment
\item \code{oral_units}\cr Units of \code{oral_ddd}
\item \code{iv_ddd}\cr Defined Daily Dose (DDD), parenteral treatment
\item \code{iv_units}\cr Units of \code{iv_ddd}
\item \code{loinc}\cr All LOINC codes (Logical Observation Identifiers Names and Codes) associated with the name of the antimicrobial agent.
}
}
An object of class \code{tbl_df} (inherits from \code{tbl}, \code{data.frame}) with 102 rows and 9 columns.
An object of class \code{tbl_df} (inherits from \code{tbl}, \code{data.frame}) with 120 rows and 11 columns.
}
\source{
\itemize{

View File

@ -87,8 +87,8 @@ ab_atc("seephthriaaksone") # and even this works
# use ab_* functions to get a specific properties (see ?ab_property);
# they use as.ab() internally:
ab_name("J01FA01") # "Erythromycin"
ab_name("eryt") # "Erythromycin"
ab_name("J01FA01")
ab_name("eryt")
\donttest{
if (require("dplyr")) {

91
man/as.av.Rd Normal file
View File

@ -0,0 +1,91 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/av.R
\name{as.av}
\alias{as.av}
\alias{ab}
\alias{is.av}
\title{Transform Input to an Antiviral Agent ID}
\usage{
as.av(x, flag_multiple_results = TRUE, info = interactive(), ...)
is.av(x)
}
\arguments{
\item{x}{a \link{character} vector to determine to antiviral agent ID}
\item{flag_multiple_results}{a \link{logical} to indicate whether a note should be printed to the console that probably more than one antiviral agent code or name can be retrieved from a single input value.}
\item{info}{a \link{logical} to indicate whether a progress bar should be printed, defaults to \code{TRUE} only in interactive mode}
\item{...}{arguments passed on to internal functions}
}
\value{
A \link{character} \link{vector} with additional class \code{\link{ab}}
}
\description{
Use this function to determine the antiviral agent code of one or more antiviral agents. The data set \link{antivirals} will be searched for abbreviations, official names and synonyms (brand names).
}
\details{
All entries in the \link{antivirals} data set have three different identifiers: a human readable EARS-Net code (column \code{ab}, used by ECDC and WHONET), an ATC code (column \code{atc}, used by WHO), and a CID code (column \code{cid}, Compound ID, used by PubChem). The data set contains more than 5,000 official brand names from many different countries, as found in PubChem. Not that some drugs contain multiple ATC codes.
All these properties will be searched for the user input. The \code{\link[=as.av]{as.av()}} can correct for different forms of misspelling:
\itemize{
\item Wrong spelling of drug names (such as "acyclovir"), which corrects for most audible similarities such as f/ph, x/ks, c/z/s, t/th, etc.
\item Too few or too many vowels or consonants
\item Switching two characters (such as "aycclovir", often the case in clinical data, when doctors typed too fast)
\item Digitalised paper records, leaving artefacts like 0/o/O (zero and O's), B/8, n/r, etc.
}
Use the \code{\link[=av_property]{av_*}} functions to get properties based on the returned antiviral agent ID, see \emph{Examples}.
Note: the \code{\link[=as.av]{as.av()}} and \code{\link[=av_property]{av_*}} functions may use very long regular expression to match brand names of antimicrobial agents. This may fail on some systems.
}
\section{Source}{
World Health Organization (WHO) Collaborating Centre for Drug Statistics Methodology: \url{https://www.whocc.no/atc_ddd_index/}
European Commission Public Health PHARMACEUTICALS - COMMUNITY REGISTER: \url{https://ec.europa.eu/health/documents/community-register/html/reg_hum_atc.htm}
}
\section{WHOCC}{
\if{html}{\figure{logo_who.png}{options: height="60" style=margin-bottom:"5"} \cr}
This package contains \strong{all ~550 antibiotic, antimycotic and antiviral drugs} and their Anatomical Therapeutic Chemical (ATC) codes, ATC groups and Defined Daily Dose (DDD) from the World Health Organization Collaborating Centre for Drug Statistics Methodology (WHOCC, \url{https://www.whocc.no}) and the Pharmaceuticals Community Register of the European Commission (\url{https://ec.europa.eu/health/documents/community-register/html/reg_hum_atc.htm}).
These have become the gold standard for international drug utilisation monitoring and research.
The WHOCC is located in Oslo at the Norwegian Institute of Public Health and funded by the Norwegian government. The European Commission is the executive of the European Union and promotes its general interest.
\strong{NOTE: The WHOCC copyright does not allow use for commercial purposes, unlike any other info from this package.} See \url{https://www.whocc.no/copyright_disclaimer/.}
}
\section{Reference Data Publicly Available}{
All data sets in this \code{AMR} package (about microorganisms, antibiotics, R/SI interpretation, EUCAST rules, etc.) are publicly and freely available for download in the following formats: R, MS Excel, Apache Feather, Apache Parquet, SPSS, SAS, and Stata. We also provide tab-separated plain text files that are machine-readable and suitable for input in any software program, such as laboratory information systems. Please visit \href{https://msberends.github.io/AMR/articles/datasets.html}{our website for the download links}. The actual files are of course available on \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}.
}
\examples{
# these examples all return "ACI", the ID of aciclovir:
as.av("J05AB01")
as.av("J 05 AB 01")
as.av("Aciclovir")
as.av("aciclo")
as.av(" aciclo 123")
as.av("ACICL")
as.av("ACI")
as.av("Virorax") # trade name
as.av("Zovirax") # trade name
as.av("acyklofir") # severe spelling error, yet works
# use av_* functions to get a specific properties (see ?av_property);
# they use as.av() internally:
av_name("J05AB01")
av_name("acicl")
}
\seealso{
\itemize{
\item \link{antivirals} for the \link{data.frame} that is being used to determine ATCs
\item \code{\link[=av_from_text]{av_from_text()}} for a function to retrieve antimicrobial drugs from clinical text (from health care records)
}
}

63
man/av_from_text.Rd Normal file
View File

@ -0,0 +1,63 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/av_from_text.R
\name{av_from_text}
\alias{av_from_text}
\title{Retrieve Antiviral Drug Names and Doses from Clinical Text}
\usage{
av_from_text(
text,
type = c("drug", "dose", "administration"),
collapse = NULL,
translate_av = FALSE,
thorough_search = NULL,
info = interactive(),
...
)
}
\arguments{
\item{text}{text to analyse}
\item{type}{type of property to search for, either \code{"drug"}, \code{"dose"} or \code{"administration"}, see \emph{Examples}}
\item{collapse}{a \link{character} to pass on to \code{paste(, collapse = ...)} to only return one \link{character} per element of \code{text}, see \emph{Examples}}
\item{translate_av}{if \code{type = "drug"}: a column name of the \link{antivirals} data set to translate the antibiotic abbreviations to, using \code{\link[=av_property]{av_property()}}. Defaults to \code{FALSE}. Using \code{TRUE} is equal to using "name".}
\item{thorough_search}{a \link{logical} to indicate whether the input must be extensively searched for misspelling and other faulty input values. Setting this to \code{TRUE} will take considerably more time than when using \code{FALSE}. At default, it will turn \code{TRUE} when all input elements contain a maximum of three words.}
\item{info}{a \link{logical} to indicate whether a progress bar should be printed, defaults to \code{TRUE} only in interactive mode}
\item{...}{arguments passed on to \code{\link[=as.av]{as.av()}}}
}
\value{
A \link{list}, or a \link{character} if \code{collapse} is not \code{NULL}
}
\description{
Use this function on e.g. clinical texts from health care records. It returns a \link{list} with all antiviral drugs, doses and forms of administration found in the texts.
}
\details{
This function is also internally used by \code{\link[=as.av]{as.av()}}, although it then only searches for the first drug name and will throw a note if more drug names could have been returned. Note: the \code{\link[=as.av]{as.av()}} function may use very long regular expression to match brand names of antiviral agents. This may fail on some systems.
\subsection{Argument \code{type}}{
At default, the function will search for antiviral drug names. All text elements will be searched for official names, ATC codes and brand names. As it uses \code{\link[=as.av]{as.av()}} internally, it will correct for misspelling.
With \code{type = "dose"} (or similar, like "dosing", "doses"), all text elements will be searched for \link{numeric} values that are higher than 100 and do not resemble years. The output will be \link{numeric}. It supports any unit (g, mg, IE, etc.) and multiple values in one clinical text, see \emph{Examples}.
With \code{type = "administration"} (or abbreviations, like "admin", "adm"), all text elements will be searched for a form of drug administration. It supports the following forms (including common abbreviations): buccal, implant, inhalation, instillation, intravenous, nasal, oral, parenteral, rectal, sublingual, transdermal and vaginal. Abbreviations for oral (such as 'po', 'per os') will become "oral", all values for intravenous (such as 'iv', 'intraven') will become "iv". It supports multiple values in one clinical text, see \emph{Examples}.
}
\subsection{Argument \code{collapse}}{
Without using \code{collapse}, this function will return a \link{list}. This can be convenient to use e.g. inside a \code{mutate()}):\cr
\code{df \%>\% mutate(avx = av_from_text(clinical_text))}
The returned AV codes can be transformed to official names, groups, etc. with all \code{\link[=av_property]{av_*}} functions such as \code{\link[=av_name]{av_name()}} and \code{\link[=av_group]{av_group()}}, or by using the \code{translate_av} argument.
With using \code{collapse}, this function will return a \link{character}:\cr
\code{df \%>\% mutate(avx = av_from_text(clinical_text, collapse = "|"))}
}
}
\examples{
av_from_text("28/03/2020 valaciclovir po tid")
av_from_text("28/03/2020 valaciclovir po tid", type = "admin")
}

129
man/av_property.Rd Normal file
View File

@ -0,0 +1,129 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/av_property.R
\name{av_property}
\alias{av_property}
\alias{av_name}
\alias{av_cid}
\alias{av_synonyms}
\alias{av_tradenames}
\alias{av_group}
\alias{av_atc}
\alias{ATC}
\alias{av_loinc}
\alias{av_ddd}
\alias{av_ddd_units}
\alias{av_info}
\alias{av_url}
\title{Get Properties of an Antiviral Agent}
\usage{
av_name(x, language = get_AMR_locale(), tolower = FALSE, ...)
av_cid(x, ...)
av_synonyms(x, ...)
av_tradenames(x, ...)
av_group(x, language = get_AMR_locale(), ...)
av_atc(x, only_first = FALSE, ...)
av_loinc(x, ...)
av_ddd(x, administration = "oral", ...)
av_ddd_units(x, administration = "oral", ...)
av_info(x, language = get_AMR_locale(), ...)
av_url(x, open = FALSE, ...)
av_property(x, property = "name", language = get_AMR_locale(), ...)
}
\arguments{
\item{x}{any (vector of) text that can be coerced to a valid antiviral agent code with \code{\link[=as.av]{as.av()}}}
\item{language}{language of the returned text, defaults to system language (see \code{\link[=get_AMR_locale]{get_AMR_locale()}}) and can also be set with \code{getOption("AMR_locale")}. Use \code{language = NULL} or \code{language = ""} to prevent translation.}
\item{tolower}{a \link{logical} to indicate whether the first \link{character} of every output should be transformed to a lower case \link{character}.}
\item{...}{other arguments passed on to \code{\link[=as.av]{as.av()}}}
\item{administration}{way of administration, either \code{"oral"} or \code{"iv"}}
\item{open}{browse the URL using \code{\link[utils:browseURL]{utils::browseURL()}}}
\item{property}{one of the column names of one of the \link{antivirals} data set: \code{vector_or(colnames(antivirals), sort = FALSE)}.}
}
\value{
\itemize{
\item An \link{integer} in case of \code{\link[=av_cid]{av_cid()}}
\item A named \link{list} in case of \code{\link[=av_info]{av_info()}} and multiple \code{\link[=av_atc]{av_atc()}}/\code{\link[=av_synonyms]{av_synonyms()}}/\code{\link[=av_tradenames]{av_tradenames()}}
\item A \link{double} in case of \code{\link[=av_ddd]{av_ddd()}}
\item A \link{character} in all other cases
}
}
\description{
Use these functions to return a specific property of an antiviral agent from the \link{antivirals} data set. All input values will be evaluated internally with \code{\link[=as.av]{as.av()}}.
}
\details{
All output \link[=translate]{will be translated} where possible.
The function \code{\link[=av_url]{av_url()}} will return the direct URL to the official WHO website. A warning will be returned if the required ATC code is not available.
}
\section{Source}{
World Health Organization (WHO) Collaborating Centre for Drug Statistics Methodology: \url{https://www.whocc.no/atc_ddd_index/}
European Commission Public Health PHARMACEUTICALS - COMMUNITY REGISTER: \url{https://ec.europa.eu/health/documents/community-register/html/reg_hum_atc.htm}
}
\section{Reference Data Publicly Available}{
All data sets in this \code{AMR} package (about microorganisms, antibiotics, R/SI interpretation, EUCAST rules, etc.) are publicly and freely available for download in the following formats: R, MS Excel, Apache Feather, Apache Parquet, SPSS, SAS, and Stata. We also provide tab-separated plain text files that are machine-readable and suitable for input in any software program, such as laboratory information systems. Please visit \href{https://msberends.github.io/AMR/articles/datasets.html}{our website for the download links}. The actual files are of course available on \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}.
}
\examples{
# all properties:
av_name("AMX") # "Amoxicillin"
av_atc("AMX") # "J01CA04" (ATC code from the WHO)
av_cid("AMX") # 33613 (Compound ID from PubChem)
av_synonyms("AMX") # a list with brand names of amoxicillin
av_tradenames("AMX") # same
av_group("AMX") # "Beta-lactams/penicillins"
av_atc_group1("AMX") # "Beta-lactam antibacterials, penicillins"
av_atc_group2("AMX") # "Penicillins with extended spectrum"
av_url("AMX") # link to the official WHO page
# smart lowercase tranformation
av_name(x = c("AMC", "PLB")) # "Amoxicillin/clavulanic acid" "Polymyxin B"
av_name(
x = c("AMC", "PLB"),
tolower = TRUE
) # "amoxicillin/clavulanic acid" "polymyxin B"
# defined daily doses (DDD)
av_ddd("AMX", "oral") # 1.5
av_ddd_units("AMX", "oral") # "g"
av_ddd("AMX", "iv") # 3
av_ddd_units("AMX", "iv") # "g"
av_info("AMX") # all properties as a list
# all av_* functions use as.av() internally, so you can go from 'any' to 'any':
av_atc("AMP") # ATC code of AMP (ampicillin)
av_group("J01CA01") # Drug group of ampicillins ATC code
av_loinc("ampicillin") # LOINC codes of ampicillin
av_name("21066-6") # "Ampicillin" (using LOINC)
av_name(6249) # "Ampicillin" (using CID)
av_name("J01CA01") # "Ampicillin" (using ATC)
# spelling from different languages and dyslexia are no problem
av_atc("ceftriaxon")
av_atc("cephtriaxone")
av_atc("cephthriaxone")
av_atc("seephthriaaksone")
}
\seealso{
\link{antivirals}
}