mirror of
https://github.com/msberends/AMR.git
synced 2025-07-12 23:41:57 +02:00
(v0.8.0.9036) complete documentation rewrite
This commit is contained in:
13
R/ab.R
13
R/ab.R
@ -21,25 +21,26 @@
|
||||
|
||||
#' Transform to antibiotic ID
|
||||
#'
|
||||
#' Use this function to determine the antibiotic code of one or more antibiotics. The data set \code{\link{antibiotics}} will be searched for abbreviations, official names and synonyms (brand names).
|
||||
#' Use this function to determine the antibiotic code of one or more antibiotics. The data set [antibiotics] will be searched for abbreviations, official names and synonyms (brand names).
|
||||
#' @param x character vector to determine to antibiotic ID
|
||||
#' @param ... arguments passed on to internal functions
|
||||
#' @rdname as.ab
|
||||
#' @inheritSection WHOCC WHOCC
|
||||
#' @export
|
||||
#' @importFrom dplyr %>% filter slice pull
|
||||
#' @details All entries in the \code{\link{antibiotics}} 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.
|
||||
#' @details All entries in the [antibiotics] 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.
|
||||
#'
|
||||
#' Use the \code{\link{ab_property}} functions to get properties based on the returned antibiotic ID, see Examples.
|
||||
#' Use the [ab_property()] functions to get properties based on the returned antibiotic ID, see Examples.
|
||||
#' @section Source:
|
||||
#' World Health Organization (WHO) Collaborating Centre for Drug Statistics Methodology: \url{https://www.whocc.no/atc_ddd_index/}
|
||||
#'
|
||||
#' WHONET 2019 software: \url{http://www.whonet.org/software.html}
|
||||
#'
|
||||
#' European Commission Public Health PHARMACEUTICALS - COMMUNITY REGISTER: \url{http://ec.europa.eu/health/documents/community-register/html/atc.htm}
|
||||
#' @return Character (vector) with class \code{"ab"}. Unknown values will return \code{NA}.
|
||||
#' @seealso \code{\link{antibiotics}} for the dataframe that is being used to determine ATCs.
|
||||
#' @aliases ab
|
||||
#' @return Character (vector) with class [`ab`]. Unknown values will return `NA`.
|
||||
#' @seealso [antibiotics] for the dataframe that is being used to determine ATCs.
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @export
|
||||
#' @examples
|
||||
#' # These examples all return "ERY", the ID of Erythromycin:
|
||||
#' as.ab("J01FA01")
|
||||
|
@ -21,26 +21,25 @@
|
||||
|
||||
#' Property of an antibiotic
|
||||
#'
|
||||
#' Use these functions to return a specific property of an antibiotic from the \code{\link{antibiotics}} data set. All input values will be evaluated internally with \code{\link{as.ab}}.
|
||||
#' @param x any (vector of) text that can be coerced to a valid microorganism code with \code{\link{as.ab}}
|
||||
#' Use these functions to return a specific property of an antibiotic from the [antibiotics] data set. All input values will be evaluated internally with [as.ab()].
|
||||
#' @param x any (vector of) text that can be coerced to a valid microorganism code with [as.ab()]
|
||||
#' @param tolower logical to indicate whether the first character of every output should be transformed to a lower case character. This will lead to e.g. "polymyxin B" and not "polymyxin b".
|
||||
#' @param property one of the column names of one of the \code{\link{antibiotics}} data set
|
||||
#' @param language language of the returned text, defaults to system language (see \code{\link{get_locale}}) and can also be set with \code{\link{getOption}("AMR_locale")}. Use \code{language = NULL} or \code{language = ""} to prevent translation.
|
||||
#' @param administration way of administration, either \code{"oral"} or \code{"iv"}
|
||||
#' @param property one of the column names of one of the [antibiotics] data set
|
||||
#' @param language language of the returned text, defaults to system language (see [get_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 units a logical to indicate whether the units instead of the DDDs itself must be returned, see Examples
|
||||
#' @param ... other parameters passed on to \code{\link{as.ab}}
|
||||
#' @details All output will be \link{translate}d where possible.
|
||||
#' @param ... other parameters passed on to [as.ab()]
|
||||
#' @details All output will be [translate]d where possible.
|
||||
#' @inheritSection as.ab Source
|
||||
#' @rdname ab_property
|
||||
#' @name ab_property
|
||||
#' @return \itemize{
|
||||
#' \item{An \code{integer} in case of \code{ab_cid}}
|
||||
#' \item{A named \code{list} in case of \code{ab_info} and multiple \code{ab_synonyms}/\code{ab_tradenames}}
|
||||
#' \item{A \code{double} in case of \code{ab_ddd}}
|
||||
#' \item{A \code{character} in all other cases}
|
||||
#' }
|
||||
#' @return
|
||||
#' - An [`integer`] in case of [ab_cid()]
|
||||
#' - A named [`list`] in case of [ab_info()] and multiple [ab_synonyms()]/[ab_tradenames()]
|
||||
#' - A [`double`] in case of [ab_ddd()]
|
||||
#' - A [`character`] in all other cases
|
||||
#' @export
|
||||
#' @seealso \code{\link{antibiotics}}
|
||||
#' @seealso [antibiotics]
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @examples
|
||||
#' # all properties:
|
||||
|
39
R/age.R
39
R/age.R
@ -22,12 +22,12 @@
|
||||
#' Age in years of individuals
|
||||
#'
|
||||
#' Calculates age in years based on a reference date, which is the sytem date at default.
|
||||
#' @param x date(s), will be coerced with \code{\link{as.POSIXlt}}
|
||||
#' @param reference reference date(s) (defaults to today), will be coerced with \code{\link{as.POSIXlt}} and cannot be lower than \code{x}
|
||||
#' @param exact a logical to indicate whether age calculation should be exact, i.e. with decimals. It divides the number of days of \href{https://en.wikipedia.org/wiki/Year-to-date}{year-to-date} (YTD) of \code{x} by the number of days in a year of \code{reference} (either 365 or 366).
|
||||
#' @param x date(s), will be coerced with [as.POSIXlt()]
|
||||
#' @param reference reference date(s) (defaults to today), will be coerced with [as.POSIXlt()] and cannot be lower than `x`
|
||||
#' @param exact a logical to indicate whether age calculation should be exact, i.e. with decimals. It divides the number of days of [year-to-date](https://en.wikipedia.org/wiki/Year-to-date) (YTD) of `x` by the number of days in the year of `reference` (either 365 or 366).
|
||||
#' @param na.rm a logical to indicate whether missing values should be removed
|
||||
#' @return An integer (no decimals) if \code{exact = FALSE}, a double (with decimals) otherwise
|
||||
#' @seealso To split ages into groups, use the \code{\link{age_groups}} function.
|
||||
#' @return An integer (no decimals) if `exact = FALSE`, a double (with decimals) otherwise
|
||||
#' @seealso To split ages into groups, use the [age_groups()] function.
|
||||
#' @importFrom dplyr if_else
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @export
|
||||
@ -90,24 +90,21 @@ age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE) {
|
||||
|
||||
#' Split ages into age groups
|
||||
#'
|
||||
#' Split ages into age groups defined by the \code{split} parameter. This allows for easier demographic (antimicrobial resistance) analysis.
|
||||
#' @param x age, e.g. calculated with \code{\link{age}}
|
||||
#' @param split_at values to split \code{x} at, defaults to age groups 0-11, 12-24, 25-54, 55-74 and 75+. See Details.
|
||||
#' Split ages into age groups defined by the `split` parameter. This allows for easier demographic (antimicrobial resistance) analysis.
|
||||
#' @param x age, e.g. calculated with [age()]
|
||||
#' @param split_at values to split `x` at, defaults to age groups 0-11, 12-24, 25-54, 55-74 and 75+. See Details.
|
||||
#' @param na.rm a logical to indicate whether missing values should be removed
|
||||
#' @details To split ages, the input can be:
|
||||
#' \itemize{
|
||||
#' \item{A numeric vector. A vector of e.g. \code{c(10, 20)} will split on 0-9, 10-19 and 20+. A value of only \code{50} will split on 0-49 and 50+.
|
||||
#' The default is to split on young children (0-11), youth (12-24), young adults (25-54), middle-aged adults (55-74) and elderly (75+).}
|
||||
#' \item{A character:}
|
||||
#' \itemize{
|
||||
#' \item{\code{"children"} or \code{"kids"}, equivalent of: \code{c(0, 1, 2, 4, 6, 13, 18)}. This will split on 0, 1, 2-3, 4-5, 6-12, 13-17 and 18+.}
|
||||
#' \item{\code{"elderly"} or \code{"seniors"}, equivalent of: \code{c(65, 75, 85)}. This will split on 0-64, 65-74, 75-84, 85+.}
|
||||
#' \item{\code{"fives"}, equivalent of: \code{1:20 * 5}. This will split on 0-4, 5-9, 10-14, ..., 90-94, 95-99, 100+.}
|
||||
#' \item{\code{"tens"}, equivalent of: \code{1:10 * 10}. This will split on 0-9, 10-19, 20-29, ... 80-89, 90-99, 100+.}
|
||||
#' }
|
||||
#' }
|
||||
#' @return Ordered \code{\link{factor}}
|
||||
#' @seealso To determine ages, based on one or more reference dates, use the \code{\link{age}} function.
|
||||
#'
|
||||
#' * A numeric vector. A vector of e.g. `c(10, 20)` will split on 0-9, 10-19 and 20+. A value of only `50` will split on 0-49 and 50+.
|
||||
#' The default is to split on young children (0-11), youth (12-24), young adults (25-54), middle-aged adults (55-74) and elderly (75+).
|
||||
#' * A character:
|
||||
#' - `"children"` or `"kids"`, equivalent of: `c(0, 1, 2, 4, 6, 13, 18)`. This will split on 0, 1, 2-3, 4-5, 6-12, 13-17 and 18+.
|
||||
#' - `"elderly"` or `"seniors"`, equivalent of: `c(65, 75, 85)`. This will split on 0-64, 65-74, 75-84, 85+.
|
||||
#' - `"fives"`, equivalent of: `1:20 * 5`. This will split on 0-4, 5-9, 10-14, ..., 90-94, 95-99, 100+.
|
||||
#' - `"tens"`, equivalent of: `1:10 * 10`. This will split on 0-9, 10-19, 20-29, ... 80-89, 90-99, 100+.
|
||||
#' @return Ordered [`factor`]
|
||||
#' @seealso To determine ages, based on one or more reference dates, use the [age()] function.
|
||||
#' @export
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @examples
|
||||
|
37
R/amr.R
37
R/amr.R
@ -19,30 +19,29 @@
|
||||
# Visit our website for more info: https://msberends.gitlab.io/AMR. #
|
||||
# ==================================================================== #
|
||||
|
||||
#' The \code{AMR} Package
|
||||
#' The `AMR` Package
|
||||
#'
|
||||
#' Welcome to the \code{AMR} package.
|
||||
#' Welcome to the `AMR` package.
|
||||
#' @details
|
||||
#' \code{AMR} is a free and open-source R package to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial properties by using evidence-based methods. It supports any table format, including WHONET/EARS-Net data.
|
||||
#' `AMR` is a free and open-source R package to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial properties by using evidence-based methods. It supports any table format, including WHONET/EARS-Net data.
|
||||
#'
|
||||
#' We created this package for both academic research and routine analysis at the Faculty of Medical Sciences of the University of Groningen and the Medical Microbiology & Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG). This R package is actively maintained and free software; you can freely use and distribute it for both personal and commercial (but not patent) purposes under the terms of the GNU General Public License version 2.0 (GPL-2), as published by the Free Software Foundation.
|
||||
#'
|
||||
#' This package can be used for:
|
||||
#' \itemize{
|
||||
#' \item{Reference for the taxonomy of microorganisms, since the package contains all microbial (sub)species from the Catalogue of Life}
|
||||
#' \item{Interpreting raw MIC and disk diffusion values, based on the latest CLSI or EUCAST guidelines}
|
||||
#' \item{Determining first isolates to be used for AMR analysis}
|
||||
#' \item{Calculating antimicrobial resistance}
|
||||
#' \item{Determining multi-drug resistance (MDR) / multi-drug resistant organisms (MDRO)}
|
||||
#' \item{Calculating (empirical) susceptibility of both mono therapy and combination therapies}
|
||||
#' \item{Predicting future antimicrobial resistance using regression models}
|
||||
#' \item{Getting properties for any microorganism (like Gram stain, species, genus or family)}
|
||||
#' \item{Getting properties for any antibiotic (like name, EARS-Net code, ATC code, PubChem code, defined daily dose or trade name)}
|
||||
#' \item{Plotting antimicrobial resistance}
|
||||
#' \item{Applying EUCAST expert rules}
|
||||
#' }
|
||||
#' - Reference for the taxonomy of microorganisms, since the package contains all microbial (sub)species from the [Catalogue of Life](http://www.catalogueoflife.org)
|
||||
#' - Interpreting raw MIC and disk diffusion values, based on the latest CLSI or EUCAST guidelines
|
||||
#' - Determining first isolates to be used for AMR analysis
|
||||
#' - Calculating antimicrobial resistance
|
||||
#' - Determining multi-drug resistance (MDR) / multi-drug resistant organisms (MDRO)
|
||||
#' - Calculating (empirical) susceptibility of both mono therapy and combination therapies
|
||||
#' - Predicting future antimicrobial resistance using regression models
|
||||
#' - Getting properties for any microorganism (like Gram stain, species, genus or family)
|
||||
#' - Getting properties for any antibiotic (like name, EARS-Net code, ATC code, PubChem code, defined daily dose or trade name)
|
||||
#' - Plotting antimicrobial resistance
|
||||
#' - Applying EUCAST expert rules
|
||||
|
||||
#' @section Read more on our website!:
|
||||
#' On our website \url{https://msberends.gitlab.io/AMR} you can find \href{https://msberends.gitlab.io/AMR/articles/AMR.html}{a tutorial} about how to conduct AMR analysis, the \href{https://msberends.gitlab.io/AMR/reference}{complete documentation of all functions} (which reads a lot easier than here in R) and \href{https://msberends.gitlab.io/AMR/articles/WHONET.html}{an example analysis using WHONET data}.
|
||||
#' On our website <https://msberends.gitlab.io/AMR> you can find [a tutorial](https://msberends.gitlab.io/AMR/articles/AMR.html) about how to conduct AMR analysis, the [complete documentation of all functions](https://msberends.gitlab.io/AMR/reference) (which reads a lot easier than here in R) and [an example analysis using WHONET data](https://msberends.gitlab.io/AMR/articles/WHONET.html).
|
||||
#' @section Contact us:
|
||||
#' For suggestions, comments or questions, please contact us at:
|
||||
#'
|
||||
@ -51,11 +50,11 @@
|
||||
#' Department of Medical Microbiology, University of Groningen \cr
|
||||
#' University Medical Center Groningen \cr
|
||||
#' Post Office Box 30001 \cr
|
||||
#' 9700 RB Groningen
|
||||
#' 9700 RB Groningen \cr
|
||||
#' The Netherlands
|
||||
#'
|
||||
#' If you have found a bug, please file a new issue at: \cr
|
||||
#' \url{https://gitlab.com/msberends/AMR/issues}
|
||||
#' <https://gitlab.com/msberends/AMR/issues>
|
||||
#' @name AMR
|
||||
#' @rdname AMR
|
||||
#' @importFrom microbenchmark microbenchmark
|
||||
|
@ -21,43 +21,43 @@
|
||||
|
||||
#' Get ATC properties from WHOCC website
|
||||
#'
|
||||
#' Gets data from the WHO to determine properties of an ATC (e.g. an antibiotic) like name, defined daily dose (DDD) or standard unit. \cr \strong{This function requires an internet connection.}
|
||||
#' @description Gets data from the WHO to determine properties of an ATC (e.g. an antibiotic) like name, defined daily dose (DDD) or standard unit.
|
||||
#'
|
||||
#' **This function requires an internet connection.**
|
||||
#' @param atc_code a character or character vector with ATC code(s) of antibiotic(s)
|
||||
#' @param property property of an ATC code. Valid values are \code{"ATC"}, \code{"Name"}, \code{"DDD"}, \code{"U"} (\code{"unit"}), \code{"Adm.R"}, \code{"Note"} and \code{groups}. For this last option, all hierarchical groups of an ATC code will be returned, see Examples.
|
||||
#' @param administration type of administration when using \code{property = "Adm.R"}, see Details
|
||||
#' @param url url of website of the WHO. The sign \code{\%s} can be used as a placeholder for ATC codes.
|
||||
#' @param ... parameters to pass on to \code{atc_property}
|
||||
#' @param property property of an ATC code. Valid values are `"ATC"`, `"Name"`, `"DDD"`, `"U"` (`"unit"`), `"Adm.R"`, `"Note"` and `groups`. For this last option, all hierarchical groups of an ATC code will be returned, see Examples.
|
||||
#' @param administration type of administration when using `property = "Adm.R"`, see Details
|
||||
#' @param url url of website of the WHO. The sign `%s` can be used as a placeholder for ATC codes.
|
||||
#' @param ... parameters to pass on to `atc_property`
|
||||
#' @details
|
||||
#' Options for parameter \code{administration}:
|
||||
#' \itemize{
|
||||
#' \item{\code{"Implant"}}{ = Implant}
|
||||
#' \item{\code{"Inhal"}}{ = Inhalation}
|
||||
#' \item{\code{"Instill"}}{ = Instillation}
|
||||
#' \item{\code{"N"}}{ = nasal}
|
||||
#' \item{\code{"O"}}{ = oral}
|
||||
#' \item{\code{"P"}}{ = parenteral}
|
||||
#' \item{\code{"R"}}{ = rectal}
|
||||
#' \item{\code{"SL"}}{ = sublingual/buccal}
|
||||
#' \item{\code{"TD"}}{ = transdermal}
|
||||
#' \item{\code{"V"}}{ = vaginal}
|
||||
#' }
|
||||
#' Options for parameter `administration`:
|
||||
#'
|
||||
#' - `"Implant"` = Implant
|
||||
#' - `"Inhal"` = Inhalation
|
||||
#' - `"Instill"` = Instillation
|
||||
#' - `"N"` = nasal
|
||||
#' - `"O"` = oral
|
||||
#' - `"P"` = parenteral
|
||||
#' - `"R"` = rectal
|
||||
#' - `"SL"` = sublingual/buccal
|
||||
#' - `"TD"` = transdermal
|
||||
#' - `"V"` = vaginal
|
||||
#'
|
||||
#' Abbreviations of return values when using \code{property = "U"} (unit):
|
||||
#' \itemize{
|
||||
#' \item{\code{"g"}}{ = gram}
|
||||
#' \item{\code{"mg"}}{ = milligram}
|
||||
#' \item{\code{"mcg"}}{ = microgram}
|
||||
#' \item{\code{"U"}}{ = unit}
|
||||
#' \item{\code{"TU"}}{ = thousand units}
|
||||
#' \item{\code{"MU"}}{ = million units}
|
||||
#' \item{\code{"mmol"}}{ = millimole}
|
||||
#' \item{\code{"ml"}}{ = milliliter (e.g. eyedrops)}
|
||||
#' }
|
||||
#' Abbreviations of return values when using `property = "U"` (unit):
|
||||
#'
|
||||
#' - `"g"` = gram
|
||||
#' - `"mg"` = milligram
|
||||
#' - `"mcg"`` = microgram
|
||||
#' - `"U"` = unit
|
||||
#' - `"TU"` = thousand units
|
||||
#' - `"MU"` = million units
|
||||
#' - `"mmol"` = millimole
|
||||
#' - `"ml"` = milliliter (e.g. eyedrops)
|
||||
#' @export
|
||||
#' @rdname atc_online
|
||||
#' @importFrom dplyr %>% progress_estimated
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @source \url{https://www.whocc.no/atc_ddd_alterations__cumulative/ddd_alterations/abbrevations/}
|
||||
#' @source <https://www.whocc.no/atc_ddd_alterations__cumulative/ddd_alterations/abbrevations/>
|
||||
#' @examples
|
||||
#' \donttest{
|
||||
#' # oral DDD (Defined Daily Dose) of amoxicillin
|
||||
|
@ -21,11 +21,11 @@
|
||||
|
||||
#' Check availability of columns
|
||||
#'
|
||||
#' Easy check for availability of columns in a data set. This makes it easy to get an idea of which antimicrobial combination can be used for calculation with e.g. \code{\link{resistance}}.
|
||||
#' @param tbl a \code{data.frame} or \code{list}
|
||||
#' Easy check for availability of columns in a data set. This makes it easy to get an idea of which antimicrobial combination can be used for calculation with e.g. [resistance()].
|
||||
#' @param tbl a [`data.frame`] or [`list`]
|
||||
#' @param width number of characters to present the visual availability, defaults to filling the width of the console
|
||||
#' @details The function returns a \code{data.frame} with columns \code{"resistant"} and \code{"visual_resistance"}. The values in that columns are calculated with \code{\link{resistance}}.
|
||||
#' @return \code{data.frame} with column names of \code{tbl} as row names
|
||||
#' @details The function returns a [`data.frame`] with columns `"resistant"` and `"visual_resistance"`. The values in that columns are calculated with [resistance()].
|
||||
#' @return [`data.frame`] with column names of `tbl` as row names
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @importFrom cleaner percentage
|
||||
#' @export
|
||||
|
@ -21,25 +21,25 @@
|
||||
|
||||
#' Determine bug-drug combinations
|
||||
#'
|
||||
#' Determine antimicrobial resistance (AMR) of all bug-drug combinations in your data set where at least 30 (default) isolates are available per species. Use \code{format} on the result to prettify it to a publicable/printable format, see Examples.
|
||||
#' Determine antimicrobial resistance (AMR) of all bug-drug combinations in your data set where at least 30 (default) isolates are available per species. Use [format()] on the result to prettify it to a publicable/printable format, see Examples.
|
||||
#' @inheritParams eucast_rules
|
||||
#' @param combine_IR logical to indicate whether values R and I should be summed
|
||||
#' @param add_ab_group logical to indicate where the group of the antimicrobials must be included as a first column
|
||||
#' @param remove_intrinsic_resistant logical to indicate that rows with 100\% resistance for all tested antimicrobials must be removed from the table
|
||||
#' @param FUN the function to call on the \code{mo} column to transform the microorganism IDs, defaults to \code{\link{mo_shortname}}
|
||||
#' @param translate_ab a character of length 1 containing column names of the \code{\link{antibiotics}} data set
|
||||
#' @param ... arguments passed on to \code{FUN}
|
||||
#' @param remove_intrinsic_resistant logical to indicate that rows with 100% resistance for all tested antimicrobials must be removed from the table
|
||||
#' @param FUN the function to call on the `mo` column to transform the microorganism IDs, defaults to [mo_shortname()]
|
||||
#' @param translate_ab a character of length 1 containing column names of the [antibiotics] data set
|
||||
#' @param ... arguments passed on to `FUN`
|
||||
#' @inheritParams rsi_df
|
||||
#' @inheritParams base::formatC
|
||||
#' @importFrom dplyr %>% rename group_by select mutate filter summarise ungroup
|
||||
#' @importFrom tidyr pivot_longer
|
||||
#' @details The function \code{format} calculates the resistance per bug-drug combination. Use \code{combine_IR = FALSE} (default) to test R vs. S+I and \code{combine_IR = TRUE} to test R+I vs. S.
|
||||
#' @details The function [format()] calculates the resistance per bug-drug combination. Use `combine_IR = FALSE` (default) to test R vs. S+I and `combine_IR = TRUE` to test R+I vs. S.
|
||||
#'
|
||||
#' The language of the output can be overwritten with \code{options(AMR_locale)}, please see \link{translate}.
|
||||
#' The language of the output can be overwritten with `options(AMR_locale)`, please see [translate].
|
||||
#' @export
|
||||
#' @rdname bug_drug_combinations
|
||||
#' @return The function \code{bug_drug_combinations} returns a \code{data.frame} with columns "mo", "ab", "S", "I", "R" and "total".
|
||||
#' @source \strong{M39 Analysis and Presentation of Cumulative Antimicrobial Susceptibility Test Data, 4th Edition}, 2014, \emph{Clinical and Laboratory Standards Institute (CLSI)}. \url{https://clsi.org/standards/products/microbiology/documents/m39/}.
|
||||
#' @return The function [bug_drug_combinations()] returns a [`data.frame`] with columns "mo", "ab", "S", "I", "R" and "total".
|
||||
#' @source \strong{M39 Analysis and Presentation of Cumulative Antimicrobial Susceptibility Test Data, 4th Edition}, 2014, *Clinical and Laboratory Standards Institute (CLSI)*. <https://clsi.org/standards/products/microbiology/documents/m39/>.
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @examples
|
||||
#' \donttest{
|
||||
|
@ -24,28 +24,26 @@
|
||||
#' This package contains the complete taxonomic tree of almost all microorganisms from the authoritative and comprehensive Catalogue of Life.
|
||||
#' @section Catalogue of Life:
|
||||
#' \if{html}{\figure{logo_col.png}{options: height=40px style=margin-bottom:5px} \cr}
|
||||
#' This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (\url{http://www.catalogueoflife.org}). The Catalogue of Life is the most comprehensive and authoritative global index of species currently available.
|
||||
#' This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (<http://www.catalogueoflife.org>). The Catalogue of Life is the most comprehensive and authoritative global index of species currently available.
|
||||
#'
|
||||
#' \link[=catalogue_of_life]{Click here} for more information about the included taxa. Check which version of the Catalogue of Life was included in this package with \code{\link{catalogue_of_life_version}()}.
|
||||
#' [Click here][catalogue_of_life] for more information about the included taxa. Check which version of the Catalogue of Life was included in this package with [catalogue_of_life_version()].
|
||||
#' @section Included taxa:
|
||||
#' Included are:
|
||||
#' \itemize{
|
||||
#' \item{All ~61,000 (sub)species from the kingdoms of Archaea, Bacteria, Chromista and Protozoa}
|
||||
#' \item{All ~8,500 (sub)species from these orders of the kingdom of Fungi: Eurotiales, Microascales, Mucorales, Onygenales, Pneumocystales, Saccharomycetales, Schizosaccharomycetales and Tremellales. The kingdom of Fungi is a very large taxon with almost 300,000 different (sub)species, of which most are not microbial (but rather macroscopic, like mushrooms). Because of this, not all fungi fit the scope of this package and including everything would tremendously slow down our algorithms too. By only including the aforementioned taxonomic orders, the most relevant fungi are covered (like all species of \emph{Aspergillus}, \emph{Candida}, \emph{Cryptococcus}, \emph{Histplasma}, \emph{Pneumocystis}, \emph{Saccharomyces} and \emph{Trichophyton}).}
|
||||
#' \item{All ~150 (sub)species from ~100 other relevant genera from the kingdom of Animalia (like \emph{Strongyloides} and \emph{Taenia})}
|
||||
#' \item{All ~23,000 previously accepted names of all included (sub)species (these were taxonomically renamed)}
|
||||
#' \item{The complete taxonomic tree of all included (sub)species: from kingdom to subspecies}
|
||||
#' \item{The responsible author(s) and year of scientific publication}
|
||||
#' }
|
||||
#' - All ~61,000 (sub)species from the kingdoms of Archaea, Bacteria, Chromista and Protozoa
|
||||
#' - All ~8,500 (sub)species from these orders of the kingdom of Fungi: Eurotiales, Microascales, Mucorales, Onygenales, Pneumocystales, Saccharomycetales, Schizosaccharomycetales and Tremellales. The kingdom of Fungi is a very large taxon with almost 300,000 different (sub)species, of which most are not microbial (but rather macroscopic, like mushrooms). Because of this, not all fungi fit the scope of this package and including everything would tremendously slow down our algorithms too. By only including the aforementioned taxonomic orders, the most relevant fungi are covered (like all species of *Aspergillus*, *Candida*, *Cryptococcus*, *Histplasma*, *Pneumocystis*, *Saccharomyces* and *Trichophyton*).
|
||||
#' - All ~150 (sub)species from ~100 other relevant genera from the kingdom of Animalia (like *Strongyloides* and *Taenia*)
|
||||
#' - All ~23,000 previously accepted names of all included (sub)species (these were taxonomically renamed)
|
||||
#' - The complete taxonomic tree of all included (sub)species: from kingdom to subspecies
|
||||
#' - The responsible author(s) and year of scientific publication
|
||||
#'
|
||||
#' The Catalogue of Life (\url{http://www.catalogueoflife.org}) is the most comprehensive and authoritative global index of species currently available. It holds essential information on the names, relationships and distributions of over 1.9 million species. The Catalogue of Life is used to support the major biodiversity and conservation information services such as the Global Biodiversity Information Facility (GBIF), Encyclopedia of Life (EoL) and the International Union for Conservation of Nature Red List. It is recognised by the Convention on Biological Diversity as a significant component of the Global Taxonomy Initiative and a contribution to Target 1 of the Global Strategy for Plant Conservation.
|
||||
#' The Catalogue of Life (<http://www.catalogueoflife.org>) is the most comprehensive and authoritative global index of species currently available. It holds essential information on the names, relationships and distributions of over 1.9 million species. The Catalogue of Life is used to support the major biodiversity and conservation information services such as the Global Biodiversity Information Facility (GBIF), Encyclopedia of Life (EoL) and the International Union for Conservation of Nature Red List. It is recognised by the Convention on Biological Diversity as a significant component of the Global Taxonomy Initiative and a contribution to Target 1 of the Global Strategy for Plant Conservation.
|
||||
#'
|
||||
#' The syntax used to transform the original data to a cleansed R format, can be found here: \url{https://gitlab.com/msberends/AMR/blob/master/data-raw/reproduction_of_microorganisms.R}.
|
||||
#' The syntax used to transform the original data to a cleansed R format, can be found here: <https://gitlab.com/msberends/AMR/blob/master/data-raw/reproduction_of_microorganisms.R>.
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @name catalogue_of_life
|
||||
#' @rdname catalogue_of_life
|
||||
#' @seealso Data set \code{\link{microorganisms}} for the actual data. \cr
|
||||
#' Function \code{\link{as.mo}()} to use the data for intelligent determination of microorganisms.
|
||||
#' @seealso Data set [microorganisms] for the actual data. \cr
|
||||
#' Function [as.mo()] to use the data for intelligent determination of microorganisms.
|
||||
#' @examples
|
||||
#' # Get version info of included data set
|
||||
#' catalogue_of_life_version()
|
||||
@ -70,7 +68,7 @@
|
||||
#' mo_ref("E. coli")
|
||||
#' # [1] "Castellani et al., 1919"
|
||||
#'
|
||||
#' # Do not get mistaken - the package only includes microorganisms
|
||||
#' # Do not get mistaken - this package is about microorganisms
|
||||
#' mo_kingdom("C. elegans")
|
||||
#' # [1] "Bacteria" # Bacteria?!
|
||||
#' mo_name("C. elegans")
|
||||
@ -80,9 +78,9 @@ NULL
|
||||
#' Version info of included Catalogue of Life
|
||||
#'
|
||||
#' This function returns information about the included data from the Catalogue of Life.
|
||||
#' @seealso \code{\link{microorganisms}}
|
||||
#' @details For DSMZ, see \code{?microorganisms}.
|
||||
#' @return a \code{list}, which prints in pretty format
|
||||
#' @seealso [microorganisms]
|
||||
#' @details For DSMZ, see [microorganisms].
|
||||
#' @return a [`list`], which prints in pretty format
|
||||
#' @inheritSection catalogue_of_life Catalogue of Life
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @importFrom crayon bold underline
|
||||
|
20
R/count.R
20
R/count.R
@ -19,24 +19,24 @@
|
||||
# Visit our website for more info: https://msberends.gitlab.io/AMR. #
|
||||
# ==================================================================== #
|
||||
|
||||
#' Count isolates
|
||||
#' Count available isolates
|
||||
#'
|
||||
#' @description These functions can be used to count resistant/susceptible microbial isolates. All functions support quasiquotation with pipes, can be used in \code{dplyr}s \code{\link[dplyr]{summarise}} and support grouped variables, see \emph{Examples}.
|
||||
#' @description These functions can be used to count resistant/susceptible microbial isolates. All functions support quasiquotation with pipes, can be used in [summarise()] and support grouped variables, see *Examples*.
|
||||
#'
|
||||
#' \code{count_resistant()} should be used to count resistant isolates, \code{count_susceptible()} should be used to count susceptible isolates.\cr
|
||||
#' @param ... one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with \code{\link{as.rsi}} if needed.
|
||||
#' [count_resistant()] should be used to count resistant isolates, [count_susceptible()] should be used to count susceptible isolates.
|
||||
#' @param ... one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with [as.rsi()] if needed.
|
||||
#' @inheritParams proportion
|
||||
#' @inheritSection as.rsi Interpretation of S, I and R
|
||||
#' @details These functions are meant to count isolates. Use the \code{\link{resistance}}/\code{\link{susceptibility}} functions to calculate microbial resistance/susceptibility.
|
||||
#' @details These functions are meant to count isolates. Use the [resistance()]/[susceptibility()] functions to calculate microbial resistance/susceptibility.
|
||||
#'
|
||||
#' The function \code{count_resistant()} is equal to the function \code{count_R()}. The function \code{count_susceptible()} is equal to the function \code{count_SI()}.
|
||||
#' The function [count_resistant()] is equal to the function [count_R()]. The function [count_susceptible()] is equal to the function [count_SI()].
|
||||
#'
|
||||
#' The function \code{n_rsi()} is an alias of \code{count_all()}. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to \code{\link{n_distinct}()}. Their function is equal to \code{count_susceptible(...) + count_resistant(...)}.
|
||||
#' The function [n_rsi()] is an alias of [count_all()]. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to [n_distinct()]. Their function is equal to `count_susceptible(...) + count_resistant(...)`.
|
||||
#'
|
||||
#' The function \code{count_df()} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}()}) and counts the number of S's, I's and R's. The function \code{rsi_df()} works exactly like \code{count_df()}, but adds the percentage of S, I and R.
|
||||
#' The function [count_df()] takes any variable from `data` that has an [`rsi`] class (created with [as.rsi()]) and counts the number of S's, I's and R's. The function [rsi_df()] works exactly like [count_df()], but adds the percentage of S, I and R.
|
||||
#' @inheritSection proportion Combination therapy
|
||||
#' @seealso \code{\link{proportion}_*} to calculate microbial resistance and susceptibility.
|
||||
#' @return Integer
|
||||
#' @seealso [`proportion_*`][proportion] to calculate microbial resistance and susceptibility.
|
||||
#' @return An [`integer`]
|
||||
#' @rdname count
|
||||
#' @name count
|
||||
#' @export
|
||||
|
254
R/data.R
254
R/data.R
@ -21,48 +21,44 @@
|
||||
|
||||
#' Data sets with ~550 antimicrobials
|
||||
#'
|
||||
#' Two data sets containing all antibiotics/antimycotics and antivirals. Use \code{\link{as.ab}} or one of the \code{\link{ab_property}} functions to retrieve values from the \code{antibiotics} data set. Three identifiers are included in this data set: an antibiotic ID (\code{ab}, primarily used in this package) as defined by WHONET/EARS-Net, an ATC code (\code{atc}) as defined by the WHO, and a Compound ID (\code{cid}) as found in PubChem. Other properties in this data set are derived from one or more of these codes.
|
||||
#' Two data sets containing all antibiotics/antimycotics and antivirals. Use [as.ab()] or one of the [ab_property()] functions to retrieve values from the [antibiotics] data set. Three identifiers are included in this data set: an antibiotic ID (`ab`, primarily used in this package) as defined by WHONET/EARS-Net, an ATC code (`atc`) as defined by the WHO, and a Compound ID (`cid`) as found in PubChem. Other properties in this data set are derived from one or more of these codes.
|
||||
#' @format
|
||||
#' \strong{For the \code{antibiotics} data set: a \code{\link{data.frame}} with 452 observations and 13 variables:}
|
||||
#' \describe{
|
||||
#' \item{\code{ab}}{Antibiotic ID as used in this package (like \code{AMC}), using the official EARS-Net (European Antimicrobial Resistance Surveillance Network) codes where available}
|
||||
#' \item{\code{atc}}{ATC code (Anatomical Therapeutic Chemical) as defined by the WHOCC, like \code{J01CR02}}
|
||||
#' \item{\code{cid}}{Compound ID as found in PubChem}
|
||||
#' \item{\code{name}}{Official name as used by WHONET/EARS-Net or the WHO}
|
||||
#' \item{\code{group}}{A short and concise group name, based on WHONET and WHOCC definitions}
|
||||
#' \item{\code{atc_group1}}{Official pharmacological subgroup (3rd level ATC code) as defined by the WHOCC, like \code{"Macrolides, lincosamides and streptogramins"}}
|
||||
#' \item{\code{atc_group2}}{Official chemical subgroup (4th level ATC code) as defined by the WHOCC, like \code{"Macrolides"}}
|
||||
#' \item{\code{abbr}}{List of abbreviations as used in many countries, also for antibiotic susceptibility testing (AST)}
|
||||
#' \item{\code{synonyms}}{Synonyms (often trade names) of a drug, as found in PubChem based on their compound ID}
|
||||
#' \item{\code{oral_ddd}}{Defined Daily Dose (DDD), oral treatment}
|
||||
#' \item{\code{oral_units}}{Units of \code{oral_ddd}}
|
||||
#' \item{\code{iv_ddd}}{Defined Daily Dose (DDD), parenteral treatment}
|
||||
#' \item{\code{iv_units}}{Units of \code{iv_ddd}}
|
||||
#' }
|
||||
#' ### For the [antibiotics] data set: a [`data.frame`] with 452 observations and 13 variables:
|
||||
#' - `ab`\cr Antibiotic ID as used in this package (like `AMC`), using the official EARS-Net (European Antimicrobial Resistance Surveillance Network) codes where available
|
||||
#' - `atc`\cr ATC code (Anatomical Therapeutic Chemical) as defined by the WHOCC, like `J01CR02`
|
||||
#' - `cid`\cr Compound ID as found in PubChem
|
||||
#' - `name`\cr Official name as used by WHONET/EARS-Net or the WHO
|
||||
#' - `group`\cr A short and concise group name, based on WHONET and WHOCC definitions
|
||||
#' - `atc_group1`\cr Official pharmacological subgroup (3rd level ATC code) as defined by the WHOCC, like `"Macrolides, lincosamides and streptogramins"`
|
||||
#' - `atc_group2`\cr Official chemical subgroup (4th level ATC code) as defined by the WHOCC, like `"Macrolides"`
|
||||
#' - `abbr`\cr List of abbreviations as used in many countries, also for antibiotic susceptibility testing (AST)
|
||||
#' - `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`
|
||||
#'
|
||||
#' \strong{For the \code{antivirals} data set: a \code{\link{data.frame}} with 102 observations and 9 variables:}
|
||||
#' \describe{
|
||||
#' \item{\code{atc}}{ATC code (Anatomical Therapeutic Chemical) as defined by the WHOCC}
|
||||
#' \item{\code{cid}}{Compound ID as found in PubChem}
|
||||
#' \item{\code{name}}{Official name as used by WHONET/EARS-Net or the WHO}
|
||||
#' \item{\code{atc_group}}{Official pharmacological subgroup (3rd level ATC code) as defined by the WHOCC}
|
||||
#' \item{\code{synonyms}}{Synonyms (often trade names) of a drug, as found in PubChem based on their compound ID}
|
||||
#' \item{\code{oral_ddd}}{Defined Daily Dose (DDD), oral treatment}
|
||||
#' \item{\code{oral_units}}{Units of \code{oral_ddd}}
|
||||
#' \item{\code{iv_ddd}}{Defined Daily Dose (DDD), parenteral treatment}
|
||||
#' \item{\code{iv_units}}{Units of \code{iv_ddd}}
|
||||
#' }
|
||||
#' @details Properties that are based on an ATC code are only available when an ATC is available. These properties are: \code{atc_group1}, \code{atc_group2}, \code{oral_ddd}, \code{oral_units}, \code{iv_ddd} and \code{iv_units}.
|
||||
#' ### For the [antivirals] data set: a [`data.frame`] with 102 observations and 9 variables:
|
||||
#' - `atc`\cr ATC code (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`
|
||||
#' @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) are derived from the Compound ID (\code{cid}) and consequently only available where a CID is available.
|
||||
#' @source World Health Organization (WHO) Collaborating Centre for Drug Statistics Methodology (WHOCC): \url{https://www.whocc.no/atc_ddd_index/}
|
||||
#' Synonyms (i.e. trade names) are derived from the Compound ID (`cid`) and consequently only available where a CID is available.
|
||||
#' @source World Health Organization (WHO) Collaborating Centre for Drug Statistics Methodology (WHOCC): <https://www.whocc.no/atc_ddd_index/>
|
||||
#'
|
||||
#' WHONET 2019 software: \url{http://www.whonet.org/software.html}
|
||||
#' WHONET 2019 software: <http://www.whonet.org/software.html>
|
||||
#'
|
||||
#' European Commission Public Health PHARMACEUTICALS - COMMUNITY REGISTER: \url{http://ec.europa.eu/health/documents/community-register/html/atc.htm}
|
||||
#' European Commission Public Health PHARMACEUTICALS - COMMUNITY REGISTER: <http://ec.europa.eu/health/documents/community-register/html/atc.htm>
|
||||
#' @inheritSection WHOCC WHOCC
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @seealso \code{\link{microorganisms}}
|
||||
#' @seealso [microorganisms]
|
||||
"antibiotics"
|
||||
|
||||
#' @rdname antibiotics
|
||||
@ -70,39 +66,35 @@
|
||||
|
||||
#' Data set with ~70,000 microorganisms
|
||||
#'
|
||||
#' A data set containing the microbial taxonomy of six kingdoms from the Catalogue of Life. MO codes can be looked up using \code{\link{as.mo}}.
|
||||
#' A data set containing the microbial taxonomy of six kingdoms from the Catalogue of Life. MO codes can be looked up using [as.mo()].
|
||||
#' @inheritSection catalogue_of_life Catalogue of Life
|
||||
#' @format A \code{\link{data.frame}} with 69,447 observations and 16 variables:
|
||||
#' \describe{
|
||||
#' \item{\code{mo}}{ID of microorganism as used by this package}
|
||||
#' \item{\code{col_id}}{Catalogue of Life ID}
|
||||
#' \item{\code{fullname}}{Full name, like \code{"Escherichia coli"}}
|
||||
#' \item{\code{kingdom}, \code{phylum}, \code{class}, \code{order}, \code{family}, \code{genus}, \code{species}, \code{subspecies}}{Taxonomic rank of the microorganism}
|
||||
#' \item{\code{rank}}{Text of the taxonomic rank of the microorganism, like \code{"species"} or \code{"genus"}}
|
||||
#' \item{\code{ref}}{Author(s) and year of concerning scientific publication}
|
||||
#' \item{\code{species_id}}{ID of the species as used by the Catalogue of Life}
|
||||
#' \item{\code{source}}{Either "CoL", "DSMZ" (see Source) or "manually added"}
|
||||
#' \item{\code{prevalence}}{Prevalence of the microorganism, see \code{?as.mo}}
|
||||
#' }
|
||||
#' @format A [`data.frame`] with 69,447 observations and 16 variables:
|
||||
#' - `mo`\cr ID of microorganism as used by this package
|
||||
#' - `col_id`\cr Catalogue of Life ID
|
||||
#' - `fullname`\cr Full name, like `"Escherichia coli"`
|
||||
#' - `kingdom`, `phylum`, `class`, `order`, `family`, `genus`, `species`, `subspecies`\cr Taxonomic rank of the microorganism
|
||||
#' - `rank`\cr Text of the taxonomic rank of the microorganism, like `"species"` or `"genus"`
|
||||
#' - `ref`\cr Author(s) and year of concerning scientific publication
|
||||
#' - `species_id`\cr ID of the species as used by the Catalogue of Life
|
||||
#' - `source`\cr Either "CoL", "DSMZ" (see Source) or "manually added"
|
||||
#' - `prevalence`\cr Prevalence of the microorganism, see [as.mo()]
|
||||
#' @details Manually added were:
|
||||
#' \itemize{
|
||||
#' \item{11 entries of \emph{Streptococcus} (beta-haemolytic: groups A, B, C, D, F, G, H, K and unspecified; other: viridans, milleri)}
|
||||
#' \item{2 entries of \emph{Staphylococcus} (coagulase-negative [CoNS] and coagulase-positive [CoPS])}
|
||||
#' \item{3 entries of \emph{Trichomonas} (\emph{Trichomonas vaginalis}, and its family and genus)}
|
||||
#' \item{1 entry of \emph{Blastocystis} (\emph{Blastocystis hominis}), although it officially does not exist (Noel \emph{et al.} 2005, PMID 15634993)}
|
||||
#' \item{5 other 'undefined' entries (unknown, unknown Gram negatives, unknown Gram positives, unknown yeast and unknown fungus)}
|
||||
#' \item{6 families under the Enterobacterales order, according to Adeolu \emph{et al.} (2016, PMID 27620848), that are not in the Catalogue of Life}
|
||||
#' \item{12,600 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) since the DSMZ contain the latest taxonomic information based on recent publications}
|
||||
#' }
|
||||
#' - 11 entries of *Streptococcus* (beta-haemolytic: groups A, B, C, D, F, G, H, K and unspecified; other: viridans, milleri)
|
||||
#' - 2 entries of *Staphylococcus* (coagulase-negative [CoNS] and coagulase-positive [CoPS])
|
||||
#' - 3 entries of *Trichomonas* (*Trichomonas vaginalis*, and its family and genus)
|
||||
#' - 1 entry of *Blastocystis* (*Blastocystis hominis*), although it officially does not exist (Noel *et al.* 2005, PMID 15634993)
|
||||
#' - 5 other 'undefined' entries (unknown, unknown Gram negatives, unknown Gram positives, unknown yeast and unknown fungus)
|
||||
#' - 6 families under the Enterobacterales order, according to Adeolu *et al.* (2016, PMID 27620848), that are not in the Catalogue of Life
|
||||
#' - 12,600 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) since the DSMZ contain the latest taxonomic information based on recent publications
|
||||
#' @section About the records from DSMZ (see source):
|
||||
#' Names of prokaryotes are defined as being validly published by the International Code of Nomenclature of Bacteria. Validly published are all names which are included in the Approved Lists of Bacterial Names and the names subsequently published in the International Journal of Systematic Bacteriology (IJSB) and, from January 2000, in the International Journal of Systematic and Evolutionary Microbiology (IJSEM) as original articles or in the validation lists.
|
||||
#'
|
||||
#' From: \url{https://www.dsmz.de/support/bacterial-nomenclature-up-to-date-downloads/readme.html}
|
||||
#' @source Catalogue of Life: Annual Checklist (public online taxonomic database), \url{http://www.catalogueoflife.org} (check included annual version with \code{\link{catalogue_of_life_version}()}).
|
||||
#' From: <https://www.dsmz.de/support/bacterial-nomenclature-up-to-date-downloads/readme.html>
|
||||
#' @source Catalogue of Life: Annual Checklist (public online taxonomic database), <http://www.catalogueoflife.org> (check included annual version with [catalogue_of_life_version()]).
|
||||
#'
|
||||
#' Leibniz Institute DSMZ-German Collection of Microorganisms and Cell Cultures, Germany, Prokaryotic Nomenclature Up-to-Date, \url{http://www.dsmz.de/bacterial-diversity/prokaryotic-nomenclature-up-to-date} (check included version with \code{\link{catalogue_of_life_version}()}).
|
||||
#' Leibniz Institute DSMZ-German Collection of Microorganisms and Cell Cultures, Germany, Prokaryotic Nomenclature Up-to-Date, <http://www.dsmz.de/bacterial-diversity/prokaryotic-nomenclature-up-to-date> (check included version with [catalogue_of_life_version()]).
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @seealso \code{\link{as.mo}}, \code{\link{mo_property}}, \code{\link{microorganisms.codes}}
|
||||
#' @seealso [as.mo()], [mo_property()], [microorganisms.codes]
|
||||
"microorganisms"
|
||||
|
||||
catalogue_of_life <- list(
|
||||
@ -115,103 +107,93 @@ catalogue_of_life <- list(
|
||||
|
||||
#' Data set with previously accepted taxonomic names
|
||||
#'
|
||||
#' A data set containing old (previously valid or accepted) taxonomic names according to the Catalogue of Life. This data set is used internally by \code{\link{as.mo}}.
|
||||
#' A data set containing old (previously valid or accepted) taxonomic names according to the Catalogue of Life. This data set is used internally by [as.mo()].
|
||||
#' @inheritSection catalogue_of_life Catalogue of Life
|
||||
#' @format A \code{\link{data.frame}} with 24,246 observations and 5 variables:
|
||||
#' \describe{
|
||||
#' \item{\code{col_id}}{Catalogue of Life ID that was originally given}
|
||||
#' \item{\code{col_id_new}}{New Catalogue of Life ID that responds to an entry in the \code{\link{microorganisms}} data set}
|
||||
#' \item{\code{fullname}}{Old full taxonomic name of the microorganism}
|
||||
#' \item{\code{ref}}{Author(s) and year of concerning scientific publication}
|
||||
#' \item{\code{prevalence}}{Prevalence of the microorganism, see \code{?as.mo}}
|
||||
#' }
|
||||
#' @source Catalogue of Life: Annual Checklist (public online taxonomic database), \url{http://www.catalogueoflife.org} (check included annual version with \code{\link{catalogue_of_life_version}()}).
|
||||
#' @format A [`data.frame`] with 24,246 observations and 5 variables:
|
||||
#' - `col_id`\cr Catalogue of Life ID that was originally given
|
||||
#' - `col_id_new`\cr New Catalogue of Life ID that responds to an entry in the [microorganisms] data set
|
||||
#' - `fullname`\cr Old full taxonomic name of the microorganism
|
||||
#' - `ref`\cr Author(s) and year of concerning scientific publication
|
||||
#' - `prevalence`\cr Prevalence of the microorganism, see [as.mo()]
|
||||
#' @source Catalogue of Life: Annual Checklist (public online taxonomic database), <http://www.catalogueoflife.org> (check included annual version with [catalogue_of_life_version()]).
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @seealso \code{\link{as.mo}} \code{\link{mo_property}} \code{\link{microorganisms}}
|
||||
#' @seealso [as.mo()] [mo_property()] [microorganisms]
|
||||
"microorganisms.old"
|
||||
|
||||
#' Translation table for common microorganism codes
|
||||
#'
|
||||
#' A data set containing commonly used codes for microorganisms, from laboratory systems and WHONET. Define your own with \code{\link{set_mo_source}}.
|
||||
#' @format A \code{\link{data.frame}} with 5,433 observations and 2 variables:
|
||||
#' \describe{
|
||||
#' \item{\code{code}}{Commonly used code of a microorganism}
|
||||
#' \item{\code{mo}}{ID of the microorganism in the \code{\link{microorganisms}} data set}
|
||||
#' }
|
||||
#' A data set containing commonly used codes for microorganisms, from laboratory systems and WHONET. Define your own with [set_mo_source()].
|
||||
#' @format A [`data.frame`] with 5,433 observations and 2 variables:
|
||||
#' - `code`\cr Commonly used code of a microorganism
|
||||
#' - `mo`\cr ID of the microorganism in the [microorganisms] data set
|
||||
#' @inheritSection catalogue_of_life Catalogue of Life
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @seealso \code{\link{as.mo}} \code{\link{microorganisms}}
|
||||
#' @seealso [as.mo()] [microorganisms]
|
||||
"microorganisms.codes"
|
||||
|
||||
#' Data set with 2,000 example isolates
|
||||
#'
|
||||
#' A data set containing 2,000 microbial isolates with their full antibiograms. The data set reflects reality and can be used to practice AMR analysis. For examples, please read \href{https://msberends.gitlab.io/AMR/articles/AMR.html}{the tutorial on our website}.
|
||||
#' @format A \code{\link{data.frame}} with 2,000 observations and 49 variables:
|
||||
#' \describe{
|
||||
#' \item{\code{date}}{date of receipt at the laboratory}
|
||||
#' \item{\code{hospital_id}}{ID of the hospital, from A to D}
|
||||
#' \item{\code{ward_icu}}{logical to determine if ward is an intensive care unit}
|
||||
#' \item{\code{ward_clinical}}{logical to determine if ward is a regular clinical ward}
|
||||
#' \item{\code{ward_outpatient}}{logical to determine if ward is an outpatient clinic}
|
||||
#' \item{\code{age}}{age of the patient}
|
||||
#' \item{\code{gender}}{gender of the patient}
|
||||
#' \item{\code{patient_id}}{ID of the patient}
|
||||
#' \item{\code{mo}}{ID of microorganism created with \code{\link{as.mo}}, see also \code{\link{microorganisms}}}
|
||||
#' \item{\code{PEN:RIF}}{40 different antibiotics with class \code{rsi} (see \code{\link{as.rsi}}); these column names occur in \code{\link{antibiotics}} data set and can be translated with \code{\link{ab_name}}}
|
||||
#' }
|
||||
#' A data set containing 2,000 microbial isolates with their full antibiograms. The data set reflects reality and can be used to practice AMR analysis. For examples, please read [the tutorial on our website](https://msberends.gitlab.io/AMR/articles/AMR.html).
|
||||
#' @format A [`data.frame`] with 2,000 observations and 49 variables:
|
||||
#' - `date`\cr date of receipt at the laboratory
|
||||
#' - `hospital_id`\cr ID of the hospital, from A to D
|
||||
#' - `ward_icu`\cr logical to determine if ward is an intensive care unit
|
||||
#' - `ward_clinical`\cr logical to determine if ward is a regular clinical ward
|
||||
#' - `ward_outpatient`\cr logical to determine if ward is an outpatient clinic
|
||||
#' - `age`\cr age of the patient
|
||||
#' - `gender`\cr gender of the patient
|
||||
#' - `patient_id`\cr ID of the patient
|
||||
#' - `mo`\cr ID of microorganism created with [as.mo()], see also [microorganisms]
|
||||
#' - `PEN:RIF`\cr 40 different antibiotics with class [`rsi`] (see [as.rsi()]); these column names occur in [antibiotics] data set and can be translated with [ab_name()]
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
"example_isolates"
|
||||
|
||||
#' Data set with 500 isolates - WHONET example
|
||||
#'
|
||||
#' This example data set has the exact same structure as an export file from WHONET. Such files can be used with this package, as this example data set shows. The data itself was based on our \code{\link{example_isolates}} data set.
|
||||
#' @format A \code{\link{data.frame}} with 500 observations and 53 variables:
|
||||
#' \describe{
|
||||
#' \item{\code{Identification number}}{ID of the sample}
|
||||
#' \item{\code{Specimen number}}{ID of the specimen}
|
||||
#' \item{\code{Organism}}{Name of the microorganism. Before analysis, you should transform this to a valid microbial class, using \code{\link{as.mo}}.}
|
||||
#' \item{\code{Country}}{Country of origin}
|
||||
#' \item{\code{Laboratory}}{Name of laboratory}
|
||||
#' \item{\code{Last name}}{Last name of patient}
|
||||
#' \item{\code{First name}}{Initial of patient}
|
||||
#' \item{\code{Sex}}{Gender of patient}
|
||||
#' \item{\code{Age}}{Age of patient}
|
||||
#' \item{\code{Age category}}{Age group, can also be looked up using \code{\link{age_groups}}}
|
||||
#' \item{\code{Date of admission}}{Date of hospital admission}
|
||||
#' \item{\code{Specimen date}}{Date when specimen was received at laboratory}
|
||||
#' \item{\code{Specimen type}}{Specimen type or group}
|
||||
#' \item{\code{Specimen type (Numeric)}}{Translation of \code{"Specimen type"}}
|
||||
#' \item{\code{Reason}}{Reason of request with Differential Diagnosis}
|
||||
#' \item{\code{Isolate number}}{ID of isolate}
|
||||
#' \item{\code{Organism type}}{Type of microorganism, can also be looked up using \code{\link{mo_type}}}
|
||||
#' \item{\code{Serotype}}{Serotype of microorganism}
|
||||
#' \item{\code{Beta-lactamase}}{Microorganism produces beta-lactamase?}
|
||||
#' \item{\code{ESBL}}{Microorganism produces extended spectrum beta-lactamase?}
|
||||
#' \item{\code{Carbapenemase}}{Microorganism produces carbapenemase?}
|
||||
#' \item{\code{MRSA screening test}}{Microorganism is possible MRSA?}
|
||||
#' \item{\code{Inducible clindamycin resistance}}{Clindamycin can be induced?}
|
||||
#' \item{\code{Comment}}{Other comments}
|
||||
#' \item{\code{Date of data entry}}{Date this data was entered in WHONET}
|
||||
#' \item{\code{AMP_ND10:CIP_EE}}{27 different antibiotics. You can lookup the abbreviatons in the \code{\link{antibiotics}} data set, or use e.g. \code{\link{ab_name}("AMP")} to get the official name immediately. Before analysis, you should transform this to a valid antibiotic class, using \code{\link{as.rsi}}.}
|
||||
#' }
|
||||
#' This example data set has the exact same structure as an export file from WHONET. Such files can be used with this package, as this example data set shows. The data itself was based on our [example_isolates] data set.
|
||||
#' @format A [`data.frame`] with 500 observations and 53 variables:
|
||||
#' - `Identification number`\cr ID of the sample
|
||||
#' - `Specimen number`\cr ID of the specimen
|
||||
#' - `Organism`\cr Name of the microorganism. Before analysis, you should transform this to a valid microbial class, using [as.mo()].
|
||||
#' - `Country`\cr Country of origin
|
||||
#' - `Laboratory`\cr Name of laboratory
|
||||
#' - `Last name`\cr Last name of patient
|
||||
#' - `First name`\cr Initial of patient
|
||||
#' - `Sex`\cr Gender of patient
|
||||
#' - `Age`\cr Age of patient
|
||||
#' - `Age category`\cr Age group, can also be looked up using [age_groups()]
|
||||
#' - `Date of admission`\cr Date of hospital admission
|
||||
#' - `Specimen date`\cr Date when specimen was received at laboratory
|
||||
#' - `Specimen type`\cr Specimen type or group
|
||||
#' - `Specimen type (Numeric)`\cr Translation of `"Specimen type"`
|
||||
#' - `Reason`\cr Reason of request with Differential Diagnosis
|
||||
#' - `Isolate number`\cr ID of isolate
|
||||
#' - `Organism type`\cr Type of microorganism, can also be looked up using [mo_type()]
|
||||
#' - `Serotype`\cr Serotype of microorganism
|
||||
#' - `Beta-lactamase`\cr Microorganism produces beta-lactamase?
|
||||
#' - `ESBL`\cr Microorganism produces extended spectrum beta-lactamase?
|
||||
#' - `Carbapenemase`\cr Microorganism produces carbapenemase?
|
||||
#' - `MRSA screening test`\cr Microorganism is possible MRSA?
|
||||
#' - `Inducible clindamycin resistance`\cr Clindamycin can be induced?
|
||||
#' - `Comment`\cr Other comments
|
||||
#' - `Date of data entry`\cr Date this data was entered in WHONET
|
||||
#' - `AMP_ND10:CIP_EE`\cr 27 different antibiotics. You can lookup the abbreviatons in the [antibiotics] data set, or use e.g. [`ab_name("AMP")`][ab_name()] to get the official name immediately. Before analysis, you should transform this to a valid antibiotic class, using [as.rsi()].
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
"WHONET"
|
||||
|
||||
#' Data set for RSI interpretation
|
||||
#'
|
||||
#' Data set to interpret MIC and disk diffusion to RSI values. Included guidelines are CLSI (2011-2019) and EUCAST (2011-2019). Use \code{\link{as.rsi}} to transform MICs or disks measurements to RSI values.
|
||||
#' @format A \code{\link{data.frame}} with 13,975 observations and 9 variables:
|
||||
#' \describe{
|
||||
#' \item{\code{guideline}}{Name of the guideline}
|
||||
#' \item{\code{method}}{Either "MIC" or "DISK"}
|
||||
#' \item{\code{site}}{Body site, e.g. "Oral" or "Respiratory"}
|
||||
#' \item{\code{mo}}{Microbial ID, see \code{\link{as.mo}}}
|
||||
#' \item{\code{ab}}{Antibiotic ID, see \code{\link{as.ab}}}
|
||||
#' \item{\code{ref_tbl}}{Info about where the guideline rule can be found}
|
||||
#' \item{\code{disk_dose}}{Dose of the used disk diffusion method}
|
||||
#' \item{\code{breakpoint_S}}{Lowest MIC value or highest number of millimeters that leads to "S"}
|
||||
#' \item{\code{breakpoint_R}}{Highest MIC value or lowest number of millimeters that leads to "R"}
|
||||
#' }
|
||||
#' Data set to interpret MIC and disk diffusion to RSI values. Included guidelines are CLSI (2011-2019) and EUCAST (2011-2019). Use [as.rsi()] to transform MICs or disks measurements to RSI values.
|
||||
#' @format A [`data.frame`] with 13,975 observations and 9 variables:
|
||||
#' - `guideline`\cr Name of the guideline
|
||||
#' - `method`\cr Either "MIC" or "DISK"
|
||||
#' - `site`\cr Body site, e.g. "Oral" or "Respiratory"
|
||||
#' - `mo`\cr Microbial ID, see [as.mo()]
|
||||
#' - `ab`\cr Antibiotic ID, see [as.ab()]
|
||||
#' - `ref_tbl`\cr Info about where the guideline rule can be found
|
||||
#' - `disk_dose`\cr Dose of the used disk diffusion method
|
||||
#' - `breakpoint_S`\cr Lowest MIC value or highest number of millimeters that leads to "S"
|
||||
#' - `breakpoint_R`\cr Highest MIC value or lowest number of millimeters that leads to "R"
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
"rsi_translation"
|
||||
|
||||
|
@ -21,48 +21,55 @@
|
||||
|
||||
#' Deprecated functions
|
||||
#'
|
||||
#' These functions are so-called '\link{Deprecated}'. They will be removed in a future release. Using the functions will give a warning with the name of the function it has been replaced by (if there is one).
|
||||
#' These functions are so-called '[Deprecated]'. They will be removed in a future release. Using the functions will give a warning with the name of the function it has been replaced by (if there is one).
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @export
|
||||
#' @keywords internal
|
||||
#' @name AMR-deprecated
|
||||
#' @rdname AMR-deprecated
|
||||
p.symbol <- function(...) {
|
||||
.Deprecated("p_symbol", package = "AMR")
|
||||
.Deprecated("p_symbol()", package = "AMR")
|
||||
AMR::p_symbol(...)
|
||||
}
|
||||
|
||||
#' @rdname AMR-deprecated
|
||||
#' @export
|
||||
portion_R <- function(...) {
|
||||
.Deprecated("resistance", package = "AMR")
|
||||
.Deprecated("resistance()", package = "AMR")
|
||||
proportion_R(...)
|
||||
}
|
||||
|
||||
#' @rdname AMR-deprecated
|
||||
#' @export
|
||||
portion_IR <- function(...) {
|
||||
.Deprecated("proportion_IR", package = "AMR")
|
||||
.Deprecated("proportion_IR()", package = "AMR")
|
||||
proportion_IR(...)
|
||||
}
|
||||
|
||||
#' @rdname AMR-deprecated
|
||||
#' @export
|
||||
portion_I <- function(...) {
|
||||
.Deprecated("proportion_I", package = "AMR")
|
||||
.Deprecated("proportion_I()", package = "AMR")
|
||||
proportion_I(...)
|
||||
}
|
||||
|
||||
#' @rdname AMR-deprecated
|
||||
#' @export
|
||||
portion_SI <- function(...) {
|
||||
.Deprecated("susceptibility", package = "AMR")
|
||||
.Deprecated("susceptibility()", package = "AMR")
|
||||
proportion_SI(...)
|
||||
}
|
||||
|
||||
#' @rdname AMR-deprecated
|
||||
#' @export
|
||||
portion_S <- function(...) {
|
||||
.Deprecated("proportion_S", package = "AMR")
|
||||
.Deprecated("proportion_S()", package = "AMR")
|
||||
proportion_S(...)
|
||||
}
|
||||
|
||||
#' @rdname AMR-deprecated
|
||||
#' @export
|
||||
portion_df <- function(...) {
|
||||
.Deprecated("proportion_df()", package = "AMR")
|
||||
proportion_df(...)
|
||||
}
|
||||
|
8
R/disk.R
8
R/disk.R
@ -21,15 +21,15 @@
|
||||
|
||||
#' Class 'disk'
|
||||
#'
|
||||
#' This transforms a vector to a new class \code{disk}, which is a growth zone size (around an antibiotic disk) in millimeters between 6 and 99.
|
||||
#' This transforms a vector to a new class [`disk`], which is a growth zone size (around an antibiotic disk) in millimeters between 6 and 99.
|
||||
#' @rdname as.disk
|
||||
#' @param x vector
|
||||
#' @param na.rm a logical indicating whether missing values should be removed
|
||||
#' @details Interpret disk values as RSI values with \code{\link{as.rsi}}. It supports guidelines from EUCAST and CLSI.
|
||||
#' @return Ordered integer factor with new class \code{disk}
|
||||
#' @details Interpret disk values as RSI values with [as.rsi()]. It supports guidelines from EUCAST and CLSI.
|
||||
#' @return Ordered integer factor with new class [`disk`]
|
||||
#' @aliases disk
|
||||
#' @export
|
||||
#' @seealso \code{\link{as.rsi}}
|
||||
#' @seealso [as.rsi()]
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @examples
|
||||
#' # interpret disk values
|
||||
|
227
R/eucast_rules.R
227
R/eucast_rules.R
@ -26,141 +26,131 @@ EUCAST_VERSION_EXPERT_RULES <- "3.1, 2016"
|
||||
#' EUCAST rules
|
||||
#'
|
||||
#' @description
|
||||
#' Apply susceptibility rules as defined by the European Committee on Antimicrobial Susceptibility Testing (EUCAST, \url{http://eucast.org}), see \emph{Source}. This includes (1) expert rules, (2) intrinsic resistance and (3) inferred resistance as defined in their breakpoint tables.
|
||||
#' Apply susceptibility rules as defined by the European Committee on Antimicrobial Susceptibility Testing (EUCAST, <http://eucast.org>), see *Source*. This includes (1) expert rules, (2) intrinsic resistance and (3) inferred resistance as defined in their breakpoint tables.
|
||||
#'
|
||||
#' To improve the interpretation of the antibiogram before EUCAST rules are applied, some non-EUCAST rules are applied at default, see Details.
|
||||
#' @param x data with antibiotic columns, like e.g. \code{AMX} and \code{AMC}
|
||||
#' @param x data with antibiotic columns, like e.g. `AMX` and `AMC`
|
||||
#' @param info print progress
|
||||
#' @param rules a character vector that specifies which rules should be applied - one or more of \code{c("breakpoints", "expert", "other", "all")}
|
||||
#' @param rules a character vector that specifies which rules should be applied - one or more of `c("breakpoints", "expert", "other", "all")`
|
||||
#' @param verbose a logical to turn Verbose mode on and off (default is off). In Verbose mode, the function does not apply rules to the data, but instead returns a data set in logbook form with extensive info about which rows and columns would be effected and in which way.
|
||||
#' @param ... column name of an antibiotic, see section Antibiotics
|
||||
#' @param ... column name of an antibiotic, please see section *Antibiotics* below
|
||||
#' @inheritParams first_isolate
|
||||
#' @details
|
||||
#' \strong{Note:} This function does not translate MIC values to RSI values. Use \code{\link{as.rsi}} for that. \cr
|
||||
#' \strong{Note:} When ampicillin (AMP, J01CA01) is not available but amoxicillin (AMX, J01CA04) is, the latter will be used for all rules where there is a dependency on ampicillin. These drugs are interchangeable when it comes to expression of antimicrobial resistance.
|
||||
#' **Note:** This function does not translate MIC values to RSI values. Use [as.rsi()] for that. \cr
|
||||
#' **Note:** When ampicillin (AMP, J01CA01) is not available but amoxicillin (AMX, J01CA04) is, the latter will be used for all rules where there is a dependency on ampicillin. These drugs are interchangeable when it comes to expression of antimicrobial resistance.
|
||||
#'
|
||||
#' Before further processing, some non-EUCAST rules are applied to improve the efficacy of the EUCAST rules. These non-EUCAST rules, that are applied to all isolates, are:
|
||||
#' \itemize{
|
||||
#' \item{Inherit amoxicillin (AMX) from ampicillin (AMP), where amoxicillin (AMX) is unavailable;}
|
||||
#' \item{Inherit ampicillin (AMP) from amoxicillin (AMX), where ampicillin (AMP) is unavailable;}
|
||||
#' \item{Set amoxicillin (AMX) = R where amoxicillin/clavulanic acid (AMC) = R;}
|
||||
#' \item{Set piperacillin (PIP) = R where piperacillin/tazobactam (TZP) = R;}
|
||||
#' \item{Set trimethoprim (TMP) = R where trimethoprim/sulfamethoxazole (SXT) = R;}
|
||||
#' \item{Set amoxicillin/clavulanic acid (AMC) = S where amoxicillin (AMX) = S;}
|
||||
#' \item{Set piperacillin/tazobactam (TZP) = S where piperacillin (PIP) = S;}
|
||||
#' \item{Set trimethoprim/sulfamethoxazole (SXT) = S where trimethoprim (TMP) = S.}
|
||||
#' }
|
||||
#' To \emph{not} use these rules, please use \code{eucast_rules(..., rules = c("breakpoints", "expert"))}.
|
||||
#' - Inherit amoxicillin (AMX) from ampicillin (AMP), where amoxicillin (AMX) is unavailable;
|
||||
#' - Inherit ampicillin (AMP) from amoxicillin (AMX), where ampicillin (AMP) is unavailable;
|
||||
#' - Set amoxicillin (AMX) = R where amoxicillin/clavulanic acid (AMC) = R;
|
||||
#' - Set piperacillin (PIP) = R where piperacillin/tazobactam (TZP) = R;
|
||||
#' - Set trimethoprim (TMP) = R where trimethoprim/sulfamethoxazole (SXT) = R;
|
||||
#' - Set amoxicillin/clavulanic acid (AMC) = S where amoxicillin (AMX) = S;
|
||||
#' - Set piperacillin/tazobactam (TZP) = S where piperacillin (PIP) = S;
|
||||
#' - Set trimethoprim/sulfamethoxazole (SXT) = S where trimethoprim (TMP) = S.
|
||||
#' To *not* use these rules, please use `eucast_rules(..., rules = c("breakpoints", "expert"))`.
|
||||
#'
|
||||
#' The file containing all EUCAST rules is located here: \url{https://gitlab.com/msberends/AMR/blob/master/data-raw/eucast_rules.tsv}.
|
||||
#' The file containing all EUCAST rules is located here: <https://gitlab.com/msberends/AMR/blob/master/data-raw/eucast_rules.tsv>.
|
||||
#'
|
||||
#' @section Antibiotics:
|
||||
#' To define antibiotics column names, leave as it is to determine it automatically with \code{\link{guess_ab_col}} or input a text (case-insensitive), or use \code{NULL} to skip a column (e.g. \code{TIC = NULL} to skip ticarcillin). Manually defined but non-existing columns will be skipped with a warning.
|
||||
#' To define antibiotics column names, leave as it is to determine it automatically with [guess_ab_col()] or input a text (case-insensitive), or use `NULL` to skip a column (e.g. `TIC = NULL` to skip ticarcillin). Manually defined but non-existing columns will be skipped with a warning.
|
||||
#'
|
||||
#' The following antibiotics are used for the functions \code{\link{eucast_rules}} and \code{\link{mdro}}. These are shown below in the format '\strong{antimicrobial ID}: name (\href{https://www.whocc.no/atc/structure_and_principles/}{ATC code})', sorted by name:
|
||||
#' The following antibiotics are used for the functions [eucast_rules()] and [mdro()]. These are shown below in the format '**antimicrobial ID**: name ([ATC code](https://www.whocc.no/atc/structure_and_principles/))', sorted by name:
|
||||
#'
|
||||
#' \strong{AMK}: amikacin (\href{https://www.whocc.no/atc_ddd_index/?code=J01GB06}{J01GB06}),
|
||||
#' \strong{AMX}: amoxicillin (\href{https://www.whocc.no/atc_ddd_index/?code=J01CA04}{J01CA04}),
|
||||
#' \strong{AMC}: amoxicillin/clavulanic acid (\href{https://www.whocc.no/atc_ddd_index/?code=J01CR02}{J01CR02}),
|
||||
#' \strong{AMP}: ampicillin (\href{https://www.whocc.no/atc_ddd_index/?code=J01CA01}{J01CA01}),
|
||||
#' \strong{SAM}: ampicillin/sulbactam (\href{https://www.whocc.no/atc_ddd_index/?code=J01CR01}{J01CR01}),
|
||||
#' \strong{AZM}: azithromycin (\href{https://www.whocc.no/atc_ddd_index/?code=J01FA10}{J01FA10}),
|
||||
#' \strong{AZL}: azlocillin (\href{https://www.whocc.no/atc_ddd_index/?code=J01CA09}{J01CA09}),
|
||||
#' \strong{ATM}: aztreonam (\href{https://www.whocc.no/atc_ddd_index/?code=J01DF01}{J01DF01}),
|
||||
#' \strong{CAP}: capreomycin (\href{https://www.whocc.no/atc_ddd_index/?code=J04AB30}{J04AB30}),
|
||||
#' \strong{RID}: cefaloridine (\href{https://www.whocc.no/atc_ddd_index/?code=J01DB02}{J01DB02}),
|
||||
#' \strong{CZO}: cefazolin (\href{https://www.whocc.no/atc_ddd_index/?code=J01DB04}{J01DB04}),
|
||||
#' \strong{FEP}: cefepime (\href{https://www.whocc.no/atc_ddd_index/?code=J01DE01}{J01DE01}),
|
||||
#' \strong{CTX}: cefotaxime (\href{https://www.whocc.no/atc_ddd_index/?code=J01DD01}{J01DD01}),
|
||||
#' \strong{CTT}: cefotetan (\href{https://www.whocc.no/atc_ddd_index/?code=J01DC05}{J01DC05}),
|
||||
#' \strong{FOX}: cefoxitin (\href{https://www.whocc.no/atc_ddd_index/?code=J01DC01}{J01DC01}),
|
||||
#' \strong{CPT}: ceftaroline (\href{https://www.whocc.no/atc_ddd_index/?code=J01DI02}{J01DI02}),
|
||||
#' \strong{CAZ}: ceftazidime (\href{https://www.whocc.no/atc_ddd_index/?code=J01DD02}{J01DD02}),
|
||||
#' \strong{CRO}: ceftriaxone (\href{https://www.whocc.no/atc_ddd_index/?code=J01DD04}{J01DD04}),
|
||||
#' \strong{CXM}: cefuroxime (\href{https://www.whocc.no/atc_ddd_index/?code=J01DC02}{J01DC02}),
|
||||
#' \strong{CED}: cephradine (\href{https://www.whocc.no/atc_ddd_index/?code=J01DB09}{J01DB09}),
|
||||
#' \strong{CHL}: chloramphenicol (\href{https://www.whocc.no/atc_ddd_index/?code=J01BA01}{J01BA01}),
|
||||
#' \strong{CIP}: ciprofloxacin (\href{https://www.whocc.no/atc_ddd_index/?code=J01MA02}{J01MA02}),
|
||||
#' \strong{CLR}: clarithromycin (\href{https://www.whocc.no/atc_ddd_index/?code=J01FA09}{J01FA09}),
|
||||
#' \strong{CLI}: clindamycin (\href{https://www.whocc.no/atc_ddd_index/?code=J01FF01}{J01FF01}),
|
||||
#' \strong{COL}: colistin (\href{https://www.whocc.no/atc_ddd_index/?code=J01XB01}{J01XB01}),
|
||||
#' \strong{DAP}: daptomycin (\href{https://www.whocc.no/atc_ddd_index/?code=J01XX09}{J01XX09}),
|
||||
#' \strong{DOR}: doripenem (\href{https://www.whocc.no/atc_ddd_index/?code=J01DH04}{J01DH04}),
|
||||
#' \strong{DOX}: doxycycline (\href{https://www.whocc.no/atc_ddd_index/?code=J01AA02}{J01AA02}),
|
||||
#' \strong{ETP}: ertapenem (\href{https://www.whocc.no/atc_ddd_index/?code=J01DH03}{J01DH03}),
|
||||
#' \strong{ERY}: erythromycin (\href{https://www.whocc.no/atc_ddd_index/?code=J01FA01}{J01FA01}),
|
||||
#' \strong{ETH}: ethambutol (\href{https://www.whocc.no/atc_ddd_index/?code=J04AK02}{J04AK02}),
|
||||
#' \strong{FLC}: flucloxacillin (\href{https://www.whocc.no/atc_ddd_index/?code=J01CF05}{J01CF05}),
|
||||
#' \strong{FOS}: fosfomycin (\href{https://www.whocc.no/atc_ddd_index/?code=J01XX01}{J01XX01}),
|
||||
#' \strong{FUS}: fusidic acid (\href{https://www.whocc.no/atc_ddd_index/?code=J01XC01}{J01XC01}),
|
||||
#' \strong{GAT}: gatifloxacin (\href{https://www.whocc.no/atc_ddd_index/?code=J01MA16}{J01MA16}),
|
||||
#' \strong{GEN}: gentamicin (\href{https://www.whocc.no/atc_ddd_index/?code=J01GB03}{J01GB03}),
|
||||
#' \strong{GEH}: gentamicin-high (no ATC code),
|
||||
#' \strong{IPM}: imipenem (\href{https://www.whocc.no/atc_ddd_index/?code=J01DH51}{J01DH51}),
|
||||
#' \strong{INH}: isoniazid (\href{https://www.whocc.no/atc_ddd_index/?code=J04AC01}{J04AC01}),
|
||||
#' \strong{KAN}: kanamycin (\href{https://www.whocc.no/atc_ddd_index/?code=J01GB04}{J01GB04}),
|
||||
#' \strong{LVX}: levofloxacin (\href{https://www.whocc.no/atc_ddd_index/?code=J01MA12}{J01MA12}),
|
||||
#' \strong{LIN}: lincomycin (\href{https://www.whocc.no/atc_ddd_index/?code=J01FF02}{J01FF02}),
|
||||
#' \strong{LNZ}: linezolid (\href{https://www.whocc.no/atc_ddd_index/?code=J01XX08}{J01XX08}),
|
||||
#' \strong{MEM}: meropenem (\href{https://www.whocc.no/atc_ddd_index/?code=J01DH02}{J01DH02}),
|
||||
#' \strong{MTR}: metronidazole (\href{https://www.whocc.no/atc_ddd_index/?code=J01XD01}{J01XD01}),
|
||||
#' \strong{MEZ}: mezlocillin (\href{https://www.whocc.no/atc_ddd_index/?code=J01CA10}{J01CA10}),
|
||||
#' \strong{MNO}: minocycline (\href{https://www.whocc.no/atc_ddd_index/?code=J01AA08}{J01AA08}),
|
||||
#' \strong{MFX}: moxifloxacin (\href{https://www.whocc.no/atc_ddd_index/?code=J01MA14}{J01MA14}),
|
||||
#' \strong{NAL}: nalidixic acid (\href{https://www.whocc.no/atc_ddd_index/?code=J01MB02}{J01MB02}),
|
||||
#' \strong{NEO}: neomycin (\href{https://www.whocc.no/atc_ddd_index/?code=J01GB05}{J01GB05}),
|
||||
#' \strong{NET}: netilmicin (\href{https://www.whocc.no/atc_ddd_index/?code=J01GB07}{J01GB07}),
|
||||
#' \strong{NIT}: nitrofurantoin (\href{https://www.whocc.no/atc_ddd_index/?code=J01XE01}{J01XE01}),
|
||||
#' \strong{NOR}: norfloxacin (\href{https://www.whocc.no/atc_ddd_index/?code=J01MA06}{J01MA06}),
|
||||
#' \strong{NOV}: novobiocin (\href{https://www.whocc.no/atc_ddd_index/?code=QJ01XX95}{QJ01XX95}),
|
||||
#' \strong{OFX}: ofloxacin (\href{https://www.whocc.no/atc_ddd_index/?code=J01MA01}{J01MA01}),
|
||||
#' \strong{OXA}: oxacillin (\href{https://www.whocc.no/atc_ddd_index/?code=J01CF04}{J01CF04}),
|
||||
#' \strong{PEN}: penicillin G (\href{https://www.whocc.no/atc_ddd_index/?code=J01CE01}{J01CE01}),
|
||||
#' \strong{PIP}: piperacillin (\href{https://www.whocc.no/atc_ddd_index/?code=J01CA12}{J01CA12}),
|
||||
#' \strong{TZP}: piperacillin/tazobactam (\href{https://www.whocc.no/atc_ddd_index/?code=J01CR05}{J01CR05}),
|
||||
#' \strong{PLB}: polymyxin B (\href{https://www.whocc.no/atc_ddd_index/?code=J01XB02}{J01XB02}),
|
||||
#' \strong{PRI}: pristinamycin (\href{https://www.whocc.no/atc_ddd_index/?code=J01FG01}{J01FG01}),
|
||||
#' \strong{PZA}: pyrazinamide (\href{https://www.whocc.no/atc_ddd_index/?code=J04AK01}{J04AK01}),
|
||||
#' \strong{QDA}: quinupristin/dalfopristin (\href{https://www.whocc.no/atc_ddd_index/?code=J01FG02}{J01FG02}),
|
||||
#' \strong{RIB}: rifabutin (\href{https://www.whocc.no/atc_ddd_index/?code=J04AB04}{J04AB04}),
|
||||
#' \strong{RIF}: rifampicin (\href{https://www.whocc.no/atc_ddd_index/?code=J04AB02}{J04AB02}),
|
||||
#' \strong{RFP}: rifapentine (\href{https://www.whocc.no/atc_ddd_index/?code=J04AB05}{J04AB05}),
|
||||
#' \strong{RXT}: roxithromycin (\href{https://www.whocc.no/atc_ddd_index/?code=J01FA06}{J01FA06}),
|
||||
#' \strong{SIS}: sisomicin (\href{https://www.whocc.no/atc_ddd_index/?code=J01GB08}{J01GB08}),
|
||||
#' \strong{STH}: streptomycin-high (no ATC code),
|
||||
#' \strong{TEC}: teicoplanin (\href{https://www.whocc.no/atc_ddd_index/?code=J01XA02}{J01XA02}),
|
||||
#' \strong{TLV}: telavancin (\href{https://www.whocc.no/atc_ddd_index/?code=J01XA03}{J01XA03}),
|
||||
#' \strong{TCY}: tetracycline (\href{https://www.whocc.no/atc_ddd_index/?code=J01AA07}{J01AA07}),
|
||||
#' \strong{TIC}: ticarcillin (\href{https://www.whocc.no/atc_ddd_index/?code=J01CA13}{J01CA13}),
|
||||
#' \strong{TCC}: ticarcillin/clavulanic acid (\href{https://www.whocc.no/atc_ddd_index/?code=J01CR03}{J01CR03}),
|
||||
#' \strong{TGC}: tigecycline (\href{https://www.whocc.no/atc_ddd_index/?code=J01AA12}{J01AA12}),
|
||||
#' \strong{TOB}: tobramycin (\href{https://www.whocc.no/atc_ddd_index/?code=J01GB01}{J01GB01}),
|
||||
#' \strong{TMP}: trimethoprim (\href{https://www.whocc.no/atc_ddd_index/?code=J01EA01}{J01EA01}),
|
||||
#' \strong{SXT}: trimethoprim/sulfamethoxazole (\href{https://www.whocc.no/atc_ddd_index/?code=J01EE01}{J01EE01}),
|
||||
#' \strong{VAN}: vancomycin (\href{https://www.whocc.no/atc_ddd_index/?code=J01XA01}{J01XA01}).
|
||||
#' **AMK**: amikacin ([J01GB06](https://www.whocc.no/atc_ddd_index/?code=J01GB06)),
|
||||
#' **AMX**: amoxicillin ([J01CA04](https://www.whocc.no/atc_ddd_index/?code=J01CA04)),
|
||||
#' **AMC**: amoxicillin/clavulanic acid ([J01CR02](https://www.whocc.no/atc_ddd_index/?code=J01CR02)),
|
||||
#' **AMP**: ampicillin ([J01CA01](https://www.whocc.no/atc_ddd_index/?code=J01CA01)),
|
||||
#' **SAM**: ampicillin/sulbactam ([J01CR01](https://www.whocc.no/atc_ddd_index/?code=J01CR01)),
|
||||
#' **AZM**: azithromycin ([J01FA10](https://www.whocc.no/atc_ddd_index/?code=J01FA10)),
|
||||
#' **AZL**: azlocillin ([J01CA09](https://www.whocc.no/atc_ddd_index/?code=J01CA09)),
|
||||
#' **ATM**: aztreonam ([J01DF01](https://www.whocc.no/atc_ddd_index/?code=J01DF01)),
|
||||
#' **CAP**: capreomycin ([J04AB30](https://www.whocc.no/atc_ddd_index/?code=J04AB30)),
|
||||
#' **RID**: cefaloridine ([J01DB02](https://www.whocc.no/atc_ddd_index/?code=J01DB02)),
|
||||
#' **CZO**: cefazolin ([J01DB04](https://www.whocc.no/atc_ddd_index/?code=J01DB04)),
|
||||
#' **FEP**: cefepime ([J01DE01](https://www.whocc.no/atc_ddd_index/?code=J01DE01)),
|
||||
#' **CTX**: cefotaxime ([J01DD01](https://www.whocc.no/atc_ddd_index/?code=J01DD01)),
|
||||
#' **CTT**: cefotetan ([J01DC05](https://www.whocc.no/atc_ddd_index/?code=J01DC05)),
|
||||
#' **FOX**: cefoxitin ([J01DC01](https://www.whocc.no/atc_ddd_index/?code=J01DC01)),
|
||||
#' **CPT**: ceftaroline ([J01DI02](https://www.whocc.no/atc_ddd_index/?code=J01DI02)),
|
||||
#' **CAZ**: ceftazidime ([J01DD02](https://www.whocc.no/atc_ddd_index/?code=J01DD02)),
|
||||
#' **CRO**: ceftriaxone ([J01DD04](https://www.whocc.no/atc_ddd_index/?code=J01DD04)),
|
||||
#' **CXM**: cefuroxime ([J01DC02](https://www.whocc.no/atc_ddd_index/?code=J01DC02)),
|
||||
#' **CED**: cephradine ([J01DB09](https://www.whocc.no/atc_ddd_index/?code=J01DB09)),
|
||||
#' **CHL**: chloramphenicol ([J01BA01](https://www.whocc.no/atc_ddd_index/?code=J01BA01)),
|
||||
#' **CIP**: ciprofloxacin ([J01MA02](https://www.whocc.no/atc_ddd_index/?code=J01MA02)),
|
||||
#' **CLR**: clarithromycin ([J01FA09](https://www.whocc.no/atc_ddd_index/?code=J01FA09)),
|
||||
#' **CLI**: clindamycin ([J01FF01](https://www.whocc.no/atc_ddd_index/?code=J01FF01)),
|
||||
#' **COL**: colistin ([J01XB01](https://www.whocc.no/atc_ddd_index/?code=J01XB01)),
|
||||
#' **DAP**: daptomycin ([J01XX09](https://www.whocc.no/atc_ddd_index/?code=J01XX09)),
|
||||
#' **DOR**: doripenem ([J01DH04](https://www.whocc.no/atc_ddd_index/?code=J01DH04)),
|
||||
#' **DOX**: doxycycline ([J01AA02](https://www.whocc.no/atc_ddd_index/?code=J01AA02)),
|
||||
#' **ETP**: ertapenem ([J01DH03](https://www.whocc.no/atc_ddd_index/?code=J01DH03)),
|
||||
#' **ERY**: erythromycin ([J01FA01](https://www.whocc.no/atc_ddd_index/?code=J01FA01)),
|
||||
#' **ETH**: ethambutol ([J04AK02](https://www.whocc.no/atc_ddd_index/?code=J04AK02)),
|
||||
#' **FLC**: flucloxacillin ([J01CF05](https://www.whocc.no/atc_ddd_index/?code=J01CF05)),
|
||||
#' **FOS**: fosfomycin ([J01XX01](https://www.whocc.no/atc_ddd_index/?code=J01XX01)),
|
||||
#' **FUS**: fusidic acid ([J01XC01](https://www.whocc.no/atc_ddd_index/?code=J01XC01)),
|
||||
#' **GAT**: gatifloxacin ([J01MA16](https://www.whocc.no/atc_ddd_index/?code=J01MA16)),
|
||||
#' **GEN**: gentamicin ([J01GB03](https://www.whocc.no/atc_ddd_index/?code=J01GB03)),
|
||||
#' **GEH**: gentamicin-high (no ATC code),
|
||||
#' **IPM**: imipenem ([J01DH51](https://www.whocc.no/atc_ddd_index/?code=J01DH51)),
|
||||
#' **INH**: isoniazid ([J04AC01](https://www.whocc.no/atc_ddd_index/?code=J04AC01)),
|
||||
#' **KAN**: kanamycin ([J01GB04](https://www.whocc.no/atc_ddd_index/?code=J01GB04)),
|
||||
#' **LVX**: levofloxacin ([J01MA12](https://www.whocc.no/atc_ddd_index/?code=J01MA12)),
|
||||
#' **LIN**: lincomycin ([J01FF02](https://www.whocc.no/atc_ddd_index/?code=J01FF02)),
|
||||
#' **LNZ**: linezolid ([J01XX08](https://www.whocc.no/atc_ddd_index/?code=J01XX08)),
|
||||
#' **MEM**: meropenem ([J01DH02](https://www.whocc.no/atc_ddd_index/?code=J01DH02)),
|
||||
#' **MTR**: metronidazole ([J01XD01](https://www.whocc.no/atc_ddd_index/?code=J01XD01)),
|
||||
#' **MEZ**: mezlocillin ([J01CA10](https://www.whocc.no/atc_ddd_index/?code=J01CA10)),
|
||||
#' **MNO**: minocycline ([J01AA08](https://www.whocc.no/atc_ddd_index/?code=J01AA08)),
|
||||
#' **MFX**: moxifloxacin ([J01MA14](https://www.whocc.no/atc_ddd_index/?code=J01MA14)),
|
||||
#' **NAL**: nalidixic acid ([J01MB02](https://www.whocc.no/atc_ddd_index/?code=J01MB02)),
|
||||
#' **NEO**: neomycin ([J01GB05](https://www.whocc.no/atc_ddd_index/?code=J01GB05)),
|
||||
#' **NET**: netilmicin ([J01GB07](https://www.whocc.no/atc_ddd_index/?code=J01GB07)),
|
||||
#' **NIT**: nitrofurantoin ([J01XE01](https://www.whocc.no/atc_ddd_index/?code=J01XE01)),
|
||||
#' **NOR**: norfloxacin ([J01MA06](https://www.whocc.no/atc_ddd_index/?code=J01MA06)),
|
||||
#' **NOV**: novobiocin ([QJ01XX95](https://www.whocc.no/atc_ddd_index/?code=QJ01XX95)),
|
||||
#' **OFX**: ofloxacin ([J01MA01](https://www.whocc.no/atc_ddd_index/?code=J01MA01)),
|
||||
#' **OXA**: oxacillin ([J01CF04](https://www.whocc.no/atc_ddd_index/?code=J01CF04)),
|
||||
#' **PEN**: penicillin G ([J01CE01](https://www.whocc.no/atc_ddd_index/?code=J01CE01)),
|
||||
#' **PIP**: piperacillin ([J01CA12](https://www.whocc.no/atc_ddd_index/?code=J01CA12)),
|
||||
#' **TZP**: piperacillin/tazobactam ([J01CR05](https://www.whocc.no/atc_ddd_index/?code=J01CR05)),
|
||||
#' **PLB**: polymyxin B ([J01XB02](https://www.whocc.no/atc_ddd_index/?code=J01XB02)),
|
||||
#' **PRI**: pristinamycin ([J01FG01](https://www.whocc.no/atc_ddd_index/?code=J01FG01)),
|
||||
#' **PZA**: pyrazinamide ([J04AK01](https://www.whocc.no/atc_ddd_index/?code=J04AK01)),
|
||||
#' **QDA**: quinupristin/dalfopristin ([J01FG02](https://www.whocc.no/atc_ddd_index/?code=J01FG02)),
|
||||
#' **RIB**: rifabutin ([J04AB04](https://www.whocc.no/atc_ddd_index/?code=J04AB04)),
|
||||
#' **RIF**: rifampicin ([J04AB02](https://www.whocc.no/atc_ddd_index/?code=J04AB02)),
|
||||
#' **RFP**: rifapentine ([J04AB05](https://www.whocc.no/atc_ddd_index/?code=J04AB05)),
|
||||
#' **RXT**: roxithromycin ([J01FA06](https://www.whocc.no/atc_ddd_index/?code=J01FA06)),
|
||||
#' **SIS**: sisomicin ([J01GB08](https://www.whocc.no/atc_ddd_index/?code=J01GB08)),
|
||||
#' **STH**: streptomycin-high (no ATC code),
|
||||
#' **TEC**: teicoplanin ([J01XA02](https://www.whocc.no/atc_ddd_index/?code=J01XA02)),
|
||||
#' **TLV**: telavancin ([J01XA03](https://www.whocc.no/atc_ddd_index/?code=J01XA03)),
|
||||
#' **TCY**: tetracycline ([J01AA07](https://www.whocc.no/atc_ddd_index/?code=J01AA07)),
|
||||
#' **TIC**: ticarcillin ([J01CA13](https://www.whocc.no/atc_ddd_index/?code=J01CA13)),
|
||||
#' **TCC**: ticarcillin/clavulanic acid ([J01CR03](https://www.whocc.no/atc_ddd_index/?code=J01CR03)),
|
||||
#' **TGC**: tigecycline ([J01AA12](https://www.whocc.no/atc_ddd_index/?code=J01AA12)),
|
||||
#' **TOB**: tobramycin ([J01GB01](https://www.whocc.no/atc_ddd_index/?code=J01GB01)),
|
||||
#' **TMP**: trimethoprim ([J01EA01](https://www.whocc.no/atc_ddd_index/?code=J01EA01)),
|
||||
#' **SXT**: trimethoprim/sulfamethoxazole ([J01EE01](https://www.whocc.no/atc_ddd_index/?code=J01EE01)),
|
||||
#' **VAN**: vancomycin ([J01XA01](https://www.whocc.no/atc_ddd_index/?code=J01XA01)).
|
||||
#' @aliases EUCAST
|
||||
#' @rdname eucast_rules
|
||||
#' @export
|
||||
#' @importFrom dplyr %>% select pull mutate_at vars group_by summarise n
|
||||
#' @importFrom crayon bold bgGreen bgYellow bgRed black green blue italic strip_style white red make_style
|
||||
#' @importFrom utils menu
|
||||
#' @return The input of \code{x}, possibly with edited values of antibiotics. Or, if \code{verbose = TRUE}, a \code{data.frame} with all original and new values of the affected bug-drug combinations.
|
||||
#' @return The input of `x`, possibly with edited values of antibiotics. Or, if `verbose = TRUE`, a [`data.frame`] with all original and new values of the affected bug-drug combinations.
|
||||
#' @source
|
||||
#' \itemize{
|
||||
#' \item{
|
||||
#' EUCAST Expert Rules. Version 2.0, 2012. \cr
|
||||
#' Leclercq et al. \strong{EUCAST expert rules in antimicrobial susceptibility testing.} \emph{Clin Microbiol Infect.} 2013;19(2):141-60. \cr
|
||||
#' \url{https://doi.org/10.1111/j.1469-0691.2011.03703.x}
|
||||
#' }
|
||||
#' \item{
|
||||
#' EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes Tables. Version 3.1, 2016. \cr
|
||||
#' \url{http://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf}
|
||||
#' }
|
||||
#' \item{
|
||||
#' EUCAST Breakpoint tables for interpretation of MICs and zone diameters. Version 9.0, 2019. \cr
|
||||
#' \url{http://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Breakpoint_tables/v_9.0_Breakpoint_Tables.xlsx}
|
||||
#' }
|
||||
#' }
|
||||
#' - EUCAST Expert Rules. Version 2.0, 2012. \cr
|
||||
#' Leclercq et al. **EUCAST expert rules in antimicrobial susceptibility testing.** *Clin Microbiol Infect.* 2013;19(2):141-60. \cr
|
||||
#' <https://doi.org/10.1111/j.1469-0691.2011.03703.x>
|
||||
#' - EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes Tables. Version 3.1, 2016. \cr
|
||||
#' <http://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf>
|
||||
#' - EUCAST Breakpoint tables for interpretation of MICs and zone diameters. Version 9.0, 2019. \cr
|
||||
#' <http://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Breakpoint_tables/v_9.0_Breakpoint_Tables.xlsx>
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @examples
|
||||
#' \donttest{
|
||||
@ -548,7 +538,7 @@ eucast_rules <- function(x,
|
||||
streptogramins <- c(QDA, PRI) # should officially also be quinupristin/dalfopristin
|
||||
aminopenicillins <- c(AMP, AMX)
|
||||
cephalosporins <- c(FEP, CTX, FOX, CED, CAZ, CRO, CXM, CZO)
|
||||
cephalosporins_without_CAZ <- cephalosporins[cephalosporins != ifelse(is.null(CAZ), "", CAZ)]
|
||||
cephalosporins_except_CAZ <- cephalosporins[cephalosporins != ifelse(is.null(CAZ), "", CAZ)]
|
||||
carbapenems <- c(ETP, IPM, MEM)
|
||||
ureidopenicillins <- c(PIP, TZP, AZL, MEZ)
|
||||
all_betalactams <- c(aminopenicillins, cephalosporins, carbapenems, ureidopenicillins, AMC, OXA, FLC, PEN)
|
||||
@ -568,13 +558,16 @@ eucast_rules <- function(x,
|
||||
y[y != "" & y %in% colnames(df)]
|
||||
}
|
||||
get_antibiotic_names <- function(x) {
|
||||
x %>%
|
||||
x <- x %>%
|
||||
strsplit(",") %>%
|
||||
unlist() %>%
|
||||
trimws() %>%
|
||||
sapply(function(x) if (x %in% AMR::antibiotics$ab) ab_name(x, language = NULL, tolower = TRUE) else x) %>%
|
||||
sort() %>%
|
||||
paste(collapse = ", ")
|
||||
x <- gsub("_", " ", x, fixed = TRUE)
|
||||
x <- gsub("except CAZ", paste("except", ab_name("CAZ", language = NULL, tolower = TRUE)), x, fixed = TRUE)
|
||||
x
|
||||
}
|
||||
format_antibiotic_names <- function(ab_names, ab_results) {
|
||||
ab_names <- trimws(unlist(strsplit(ab_names, ",")))
|
||||
|
@ -23,11 +23,11 @@
|
||||
#'
|
||||
#' Filter isolates on results in specific antibiotic variables based on their class (ATC groups). This makes it easy to get a list of isolates that were tested for e.g. any aminoglycoside.
|
||||
#' @param x a data set
|
||||
#' @param ab_class an antimicrobial class, like \code{"carbapenems"}, as can be found in \code{AMR::antibiotics$group}
|
||||
#' @param ab_class an antimicrobial class, like `"carbapenems"`, as can be found in [`AMR::antibiotics$group`][antibiotics]
|
||||
#' @param result an antibiotic result: S, I or R (or a combination of more of them)
|
||||
#' @param scope the scope to check which variables to check, can be \code{"any"} (default) or \code{"all"}
|
||||
#' @param ... parameters passed on to \code{filter_at} from the \code{dplyr} package
|
||||
#' @details The \code{group} column in \code{\link{antibiotics}} data set will be searched for \code{ab_class} (case-insensitive). If no results are found, the \code{atc_group1} and \code{atc_group2} columns will be searched. Next, \code{x} will be checked for column names with a value in any abbreviations, codes or official names found in the \code{antibiotics} data set.
|
||||
#' @param scope the scope to check which variables to check, can be `"any"` (default) or `"all"`
|
||||
#' @param ... parameters passed on to `filter_at` from the `dplyr` package
|
||||
#' @details The `group` column in [antibiotics] data set will be searched for `ab_class` (case-insensitive). If no results are found, the `atc_group1` and `atc_group2` columns will be searched. Next, `x` will be checked for column names with a value in any abbreviations, codes or official names found in the [antibiotics] data set.
|
||||
#' @rdname filter_ab_class
|
||||
#' @importFrom dplyr filter_at %>% select vars any_vars all_vars
|
||||
#' @importFrom crayon bold blue
|
||||
|
@ -22,61 +22,65 @@
|
||||
#' Determine first (weighted) isolates
|
||||
#'
|
||||
#' Determine first (weighted) isolates of all microorganisms of every patient per episode and (if needed) per specimen type.
|
||||
#' @param x a \code{data.frame} containing isolates.
|
||||
#' @param x a [`data.frame`] containing isolates.
|
||||
#' @param col_date column name of the result date (or date that is was received on the lab), defaults to the first column of with a date class
|
||||
#' @param col_patient_id column name of the unique IDs of the patients, defaults to the first column that starts with 'patient' or 'patid' (case insensitive)
|
||||
#' @param col_mo column name of the IDs of the microorganisms (see \code{\link{as.mo}}), defaults to the first column of class \code{mo}. Values will be coerced using \code{\link{as.mo}}.
|
||||
#' @param col_testcode column name of the test codes. Use \code{col_testcode = NULL} to \strong{not} exclude certain test codes (like test codes for screening). In that case \code{testcodes_exclude} will be ignored.
|
||||
#' @param col_mo column name of the IDs of the microorganisms (see [as.mo()]), defaults to the first column of class [`mo`]. Values will be coerced using [as.mo()].
|
||||
#' @param col_testcode column name of the test codes. Use `col_testcode = NULL` to **not** exclude certain test codes (like test codes for screening). In that case `testcodes_exclude` will be ignored.
|
||||
#' @param col_specimen column name of the specimen type or group
|
||||
#' @param col_icu column name of the logicals (\code{TRUE}/\code{FALSE}) whether a ward or department is an Intensive Care Unit (ICU)
|
||||
#' @param col_keyantibiotics column name of the key antibiotics to determine first \emph{weighted} isolates, see \code{\link{key_antibiotics}}. Defaults to the first column that starts with 'key' followed by 'ab' or 'antibiotics' (case insensitive). Use \code{col_keyantibiotics = FALSE} to prevent this.
|
||||
#' @param col_icu column name of the logicals (`TRUE`/`FALSE`) whether a ward or department is an Intensive Care Unit (ICU)
|
||||
#' @param col_keyantibiotics column name of the key antibiotics to determine first *weighted* isolates, see [key_antibiotics()]. Defaults to the first column that starts with 'key' followed by 'ab' or 'antibiotics' (case insensitive). Use `col_keyantibiotics = FALSE` to prevent this.
|
||||
#' @param episode_days episode in days after which a genus/species combination will be determined as 'first isolate' again. The default of 365 days is based on the guideline by CLSI, see Source.
|
||||
#' @param testcodes_exclude character vector with test codes that should be excluded (case-insensitive)
|
||||
#' @param icu_exclude logical whether ICU isolates should be excluded (rows with value \code{TRUE} in column \code{col_icu})
|
||||
#' @param specimen_group value in column \code{col_specimen} to filter on
|
||||
#' @param type type to determine weighed isolates; can be \code{"keyantibiotics"} or \code{"points"}, see Details
|
||||
#' @param ignore_I logical to determine whether antibiotic interpretations with \code{"I"} will be ignored when \code{type = "keyantibiotics"}, see Details
|
||||
#' @param points_threshold points until the comparison of key antibiotics will lead to inclusion of an isolate when \code{type = "points"}, see Details
|
||||
#' @param icu_exclude logical whether ICU isolates should be excluded (rows with value `TRUE` in column `col_icu`)
|
||||
#' @param specimen_group value in column `col_specimen` to filter on
|
||||
#' @param type type to determine weighed isolates; can be `"keyantibiotics"` or `"points"`, see Details
|
||||
#' @param ignore_I logical to determine whether antibiotic interpretations with `"I"` will be ignored when `type = "keyantibiotics"`, see Details
|
||||
#' @param points_threshold points until the comparison of key antibiotics will lead to inclusion of an isolate when `type = "points"`, see Details
|
||||
#' @param info print progress
|
||||
#' @param include_unknown logical to determine whether 'unknown' microorganisms should be included too, i.e. microbial code \code{"UNKNOWN"}, which defaults to \code{FALSE}. For WHONET users, this means that all records with organism code \code{"con"} (\emph{contamination}) will be excluded at default. Isolates with a microbial ID of \code{NA} will always be excluded as first isolate.
|
||||
#' @param ... parameters passed on to the \code{first_isolate} function
|
||||
#' @details \strong{WHY THIS IS SO IMPORTANT} \cr
|
||||
#' To conduct an analysis of antimicrobial resistance, you should only include the first isolate of every patient per episode \href{https://www.ncbi.nlm.nih.gov/pubmed/17304462}{[1]}. If you would not do this, you could easily get an overestimate or underestimate of the resistance of an antibiotic. Imagine that a patient was admitted with an MRSA and that it was found in 5 different blood cultures the following week. The resistance percentage of oxacillin of all \emph{S. aureus} isolates would be overestimated, because you included this MRSA more than once. It would be \href{https://en.wikipedia.org/wiki/Selection_bias}{selection bias}.
|
||||
#' @param include_unknown logical to determine whether 'unknown' microorganisms should be included too, i.e. microbial code `"UNKNOWN"`, which defaults to `FALSE`. For WHONET users, this means that all records with organism code `"con"` (*contamination*) will be excluded at default. Isolates with a microbial ID of `NA` will always be excluded as first isolate.
|
||||
#' @param ... parameters passed on to the [first_isolate()] function
|
||||
#' @details **WHY THIS IS SO IMPORTANT** \cr
|
||||
#' To conduct an analysis of antimicrobial resistance, you should only include the first isolate of every patient per episode [[1]](https://www.ncbi.nlm.nih.gov/pubmed/17304462). If you would not do this, you could easily get an overestimate or underestimate of the resistance of an antibiotic. Imagine that a patient was admitted with an MRSA and that it was found in 5 different blood cultures the following week. The resistance percentage of oxacillin of all *S. aureus* isolates would be overestimated, because you included this MRSA more than once. It would be [selection bias](https://en.wikipedia.org/wiki/Selection_bias).
|
||||
#'
|
||||
#' All isolates with a microbial ID of \code{NA} will be excluded as first isolate.
|
||||
#' All isolates with a microbial ID of `NA` will be excluded as first isolate.
|
||||
#'
|
||||
#' The functions \code{filter_first_isolate} and \code{filter_first_weighted_isolate} are helper functions to quickly filter on first isolates. The function \code{filter_first_isolate} is essentially equal to:
|
||||
#' \preformatted{
|
||||
#' x \%>\%
|
||||
#' mutate(only_firsts = first_isolate(x, ...)) \%>\%
|
||||
#' filter(only_firsts == TRUE) \%>\%
|
||||
#' The functions [filter_first_isolate()] and [filter_first_weighted_isolate()] are helper functions to quickly filter on first isolates. The function [filter_first_isolate()] is essentially equal to:
|
||||
#' ```
|
||||
#' x %>%
|
||||
#' mutate(only_firsts = first_isolate(x, ...)) %>%
|
||||
#' filter(only_firsts == TRUE) %>%
|
||||
#' select(-only_firsts)
|
||||
#' }
|
||||
#' The function \code{filter_first_weighted_isolate} is essentially equal to:
|
||||
#' \preformatted{
|
||||
#' x \%>\%
|
||||
#' mutate(keyab = key_antibiotics(.)) \%>\%
|
||||
#' ```
|
||||
#' The function [filter_first_weighted_isolate()] is essentially equal to:
|
||||
#' ```
|
||||
#' x %>%
|
||||
#' mutate(keyab = key_antibiotics(.)) %>%
|
||||
#' mutate(only_weighted_firsts = first_isolate(x,
|
||||
#' col_keyantibiotics = "keyab", ...)) \%>\%
|
||||
#' filter(only_weighted_firsts == TRUE) \%>\%
|
||||
#' col_keyantibiotics = "keyab", ...)) %>%
|
||||
#' filter(only_weighted_firsts == TRUE) %>%
|
||||
#' select(-only_weighted_firsts)
|
||||
#' }
|
||||
#' ```
|
||||
#' @section Key antibiotics:
|
||||
#' There are two ways to determine whether isolates can be included as first \emph{weighted} isolates which will give generally the same results: \cr
|
||||
#' There are two ways to determine whether isolates can be included as first *weighted* isolates which will give generally the same results:
|
||||
#'
|
||||
#' \strong{1. Using} \code{type = "keyantibiotics"} \strong{and parameter} \code{ignore_I} \cr
|
||||
#' Any difference from S to R (or vice versa) will (re)select an isolate as a first weighted isolate. With \code{ignore_I = FALSE}, also differences from I to S|R (or vice versa) will lead to this. This is a reliable method and 30-35 times faster than method 2. Read more about this in the \code{\link{key_antibiotics}} function. \cr
|
||||
#'
|
||||
#' \strong{2. Using} \code{type = "points"} \strong{and parameter} \code{points_threshold} \cr
|
||||
#' A difference from I to S|R (or vice versa) means 0.5 points, a difference from S to R (or vice versa) means 1 point. When the sum of points exceeds \code{points_threshold}, which default to \code{2}, an isolate will be (re)selected as a first weighted isolate.
|
||||
#' 1. Using `type = "keyantibiotics"` and parameter `ignore_I`
|
||||
#'
|
||||
#' Any difference from S to R (or vice versa) will (re)select an isolate as a first weighted isolate. With `ignore_I = FALSE`, also differences from I to S|R (or vice versa) will lead to this. This is a reliable method and 30-35 times faster than method 2. Read more about this in the [key_antibiotics()] function.
|
||||
#'
|
||||
#' 2. Using `type = "points"` and parameter `points_threshold`
|
||||
#'
|
||||
#' A difference from I to S|R (or vice versa) means 0.5 points, a difference from S to R (or vice versa) means 1 point. When the sum of points exceeds `points_threshold`, which default to `2`, an isolate will be (re)selected as a first weighted isolate.
|
||||
#' @rdname first_isolate
|
||||
#' @seealso \code{\link{key_antibiotics}}
|
||||
#' @seealso [key_antibiotics()]
|
||||
#' @export
|
||||
#' @importFrom dplyr arrange_at lag between row_number filter mutate arrange pull ungroup
|
||||
#' @importFrom crayon blue bold silver
|
||||
# @importFrom clean percentage
|
||||
#' @return Logical vector
|
||||
#' @source Methodology of this function is based on: \strong{M39 Analysis and Presentation of Cumulative Antimicrobial Susceptibility Test Data, 4th Edition}, 2014, \emph{Clinical and Laboratory Standards Institute (CLSI)}. \url{https://clsi.org/standards/products/microbiology/documents/m39/}.
|
||||
#' @return A [`logical`] vector
|
||||
#' @source Methodology of this function is based on:
|
||||
#'
|
||||
#' **M39 Analysis and Presentation of Cumulative Antimicrobial Susceptibility Test Data, 4th Edition**, 2014, *Clinical and Laboratory Standards Institute (CLSI)*. <https://clsi.org/standards/products/microbiology/documents/m39/>.
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @examples
|
||||
#' # `example_isolates` is a dataset available in the AMR package.
|
||||
|
70
R/g.test.R
70
R/g.test.R
@ -19,56 +19,56 @@
|
||||
# Visit our website for more info: https://msberends.gitlab.io/AMR. #
|
||||
# ==================================================================== #
|
||||
|
||||
#' \emph{G}-test for Count Data
|
||||
#' *G*-test for Count Data
|
||||
#'
|
||||
#' \code{g.test} performs chi-squared contingency table tests and goodness-of-fit tests, just like \code{\link{chisq.test}} but is more reliable [1]. A \emph{G}-test can be used to see whether the number of observations in each category fits a theoretical expectation (called a \strong{\emph{G}-test of goodness-of-fit}), or to see whether the proportions of one variable are different for different values of the other variable (called a \strong{\emph{G}-test of independence}).
|
||||
#' [g.test()] performs chi-squared contingency table tests and goodness-of-fit tests, just like [chisq.test()] but is more reliable [1]. A *G*-test can be used to see whether the number of observations in each category fits a theoretical expectation (called a ***G*-test of goodness-of-fit**), or to see whether the proportions of one variable are different for different values of the other variable (called a ***G*-test of independence**).
|
||||
#' @inherit stats::chisq.test params return
|
||||
#' @details If \code{x} is a matrix with one row or column, or if \code{x} is a vector and \code{y} is not given, then a \emph{goodness-of-fit test} is performed (\code{x} is treated as a one-dimensional contingency table). The entries of \code{x} must be non-negative integers. In this case, the hypothesis tested is whether the population probabilities equal those in \code{p}, or are all equal if \code{p} is not given.
|
||||
#' @details If `x` is a matrix with one row or column, or if `x` is a vector and `y` is not given, then a *goodness-of-fit test* is performed (`x` is treated as a one-dimensional contingency table). The entries of `x` must be non-negative integers. In this case, the hypothesis tested is whether the population probabilities equal those in `p`, or are all equal if `p` is not given.
|
||||
#'
|
||||
#' If \code{x} is a matrix with at least two rows and columns, it is taken as a two-dimensional contingency table: the entries of \code{x} must be non-negative integers. Otherwise, \code{x} and \code{y} must be vectors or factors of the same length; cases with missing values are removed, the objects are coerced to factors, and the contingency table is computed from these. Then Pearson's chi-squared test is performed of the null hypothesis that the joint distribution of the cell counts in a 2-dimensional contingency table is the product of the row and column marginals.
|
||||
#' If `x` is a matrix with at least two rows and columns, it is taken as a two-dimensional contingency table: the entries of `x` must be non-negative integers. Otherwise, `x` and `y` must be vectors or factors of the same length; cases with missing values are removed, the objects are coerced to factors, and the contingency table is computed from these. Then Pearson's chi-squared test is performed of the null hypothesis that the joint distribution of the cell counts in a 2-dimensional contingency table is the product of the row and column marginals.
|
||||
#'
|
||||
#' The p-value is computed from the asymptotic chi-squared distribution of the test statistic.
|
||||
#' The p-value is computed from the asymptotic chi-squared distribution of the test statistic.
|
||||
#'
|
||||
#' In the contingency table case simulation is done by random sampling from the set of all contingency tables with given marginals, and works only if the marginals are strictly positive. Note that this is not the usual sampling situation assumed for a chi-squared test (like the \emph{G}-test) but rather that for Fisher's exact test.
|
||||
#' In the contingency table case simulation is done by random sampling from the set of all contingency tables with given marginals, and works only if the marginals are strictly positive. Note that this is not the usual sampling situation assumed for a chi-squared test (like the *G*-test) but rather that for Fisher's exact test.
|
||||
#'
|
||||
#' In the goodness-of-fit case simulation is done by random sampling from the discrete distribution specified by \code{p}, each sample being of size \code{n = sum(x)}. This simulation is done in \R and may be slow.
|
||||
#' @section \emph{G}-test of goodness-of-fit (likelihood ratio test):
|
||||
#' Use the \emph{G}-test of goodness-of-fit when you have one nominal variable with two or more values (such as male and female, or red, pink and white flowers). You compare the observed counts of numbers of observations in each category with the expected counts, which you calculate using some kind of theoretical expectation (such as a 1:1 sex ratio or a 1:2:1 ratio in a genetic cross).
|
||||
#' In the goodness-of-fit case simulation is done by random sampling from the discrete distribution specified by `p`, each sample being of size `n = sum(x)`. This simulation is done in \R and may be slow.
|
||||
#'
|
||||
#' ## *G*-test of goodness-of-fit (likelihood ratio test)
|
||||
#' Use the *G*-test of goodness-of-fit when you have one nominal variable with two or more values (such as male and female, or red, pink and white flowers). You compare the observed counts of numbers of observations in each category with the expected counts, which you calculate using some kind of theoretical expectation (such as a 1:1 sex ratio or a 1:2:1 ratio in a genetic cross).
|
||||
#'
|
||||
#' If the expected number of observations in any category is too small, the \emph{G}-test may give inaccurate results, and you should use an exact test instead (\code{\link{fisher.test}}).
|
||||
#' If the expected number of observations in any category is too small, the *G*-test may give inaccurate results, and you should use an exact test instead ([fisher.test()]).
|
||||
#'
|
||||
#' The \emph{G}-test of goodness-of-fit is an alternative to the chi-square test of goodness-of-fit (\code{\link{chisq.test}}); each of these tests has some advantages and some disadvantages, and the results of the two tests are usually very similar.
|
||||
#' The *G*-test of goodness-of-fit is an alternative to the chi-square test of goodness-of-fit ([chisq.test()]); each of these tests has some advantages and some disadvantages, and the results of the two tests are usually very similar.
|
||||
#'
|
||||
#' @section \emph{G}-test of independence:
|
||||
#' Use the \emph{G}-test of independence when you have two nominal variables, each with two or more possible values. You want to know whether the proportions for one variable are different among values of the other variable.
|
||||
#' ## *G*-test of independence
|
||||
#' Use the *G*-test of independence when you have two nominal variables, each with two or more possible values. You want to know whether the proportions for one variable are different among values of the other variable.
|
||||
#'
|
||||
#' It is also possible to do a \emph{G}-test of independence with more than two nominal variables. For example, Jackson et al. (2013) also had data for children under 3, so you could do an analysis of old vs. young, thigh vs. arm, and reaction vs. no reaction, all analyzed together.
|
||||
#' It is also possible to do a *G*-test of independence with more than two nominal variables. For example, Jackson et al. (2013) also had data for children under 3, so you could do an analysis of old vs. young, thigh vs. arm, and reaction vs. no reaction, all analyzed together.
|
||||
#'
|
||||
#' Fisher's exact test (\code{\link{fisher.test}}) is an \strong{exact} test, where the \emph{G}-test is still only an \strong{approximation}. For any 2x2 table, Fisher's Exact test may be slower but will still run in seconds, even if the sum of your observations is multiple millions.
|
||||
#' Fisher's exact test ([fisher.test()]) is an **exact** test, where the *G*-test is still only an **approximation**. For any 2x2 table, Fisher's Exact test may be slower but will still run in seconds, even if the sum of your observations is multiple millions.
|
||||
#'
|
||||
#' The \emph{G}-test of independence is an alternative to the chi-square test of independence (\code{\link{chisq.test}}), and they will give approximately the same results.
|
||||
#' @section How the test works:
|
||||
#' Unlike the exact test of goodness-of-fit (\code{\link{fisher.test}}), the \emph{G}-test does not directly calculate the probability of obtaining the observed results or something more extreme. Instead, like almost all statistical tests, the \emph{G}-test has an intermediate step; it uses the data to calculate a test statistic that measures how far the observed data are from the null expectation. You then use a mathematical relationship, in this case the chi-square distribution, to estimate the probability of obtaining that value of the test statistic.
|
||||
#' The *G*-test of independence is an alternative to the chi-square test of independence ([chisq.test()]), and they will give approximately the same results.
|
||||
#'
|
||||
#' The \emph{G}-test uses the log of the ratio of two likelihoods as the test statistic, which is why it is also called a likelihood ratio test or log-likelihood ratio test. The formula to calculate a \emph{G}-statistic is:
|
||||
#' ## How the test works
|
||||
#' Unlike the exact test of goodness-of-fit ([fisher.test()]), the *G*-test does not directly calculate the probability of obtaining the observed results or something more extreme. Instead, like almost all statistical tests, the *G*-test has an intermediate step; it uses the data to calculate a test statistic that measures how far the observed data are from the null expectation. You then use a mathematical relationship, in this case the chi-square distribution, to estimate the probability of obtaining that value of the test statistic.
|
||||
#'
|
||||
#' \code{G <- 2 * sum(x * log(x / E))}
|
||||
#' The *G*-test uses the log of the ratio of two likelihoods as the test statistic, which is why it is also called a likelihood ratio test or log-likelihood ratio test. The formula to calculate a *G*-statistic is:
|
||||
#'
|
||||
#' \eqn{G = 2 * sum(x * log(x / E))}
|
||||
#'
|
||||
#' where `E` are the expected values. Since this is chi-square distributed, the p value can be calculated in \R with:
|
||||
#' ```
|
||||
#' p <- stats::pchisq(G, df, lower.tail = FALSE)
|
||||
#' ```
|
||||
#' where `df` are the degrees of freedom.
|
||||
#'
|
||||
#' where \code{E} are the expected values. Since this is chi-square distributed, the p value can be calculated with:
|
||||
#'
|
||||
#' \code{p <- stats::pchisq(G, df, lower.tail = FALSE)}
|
||||
#'
|
||||
#' where \code{df} are the degrees of freedom.
|
||||
#'
|
||||
#' If there are more than two categories and you want to find out which ones are significantly different from their null expectation, you can use the same method of testing each category vs. the sum of all categories, with the Bonferroni correction. You use \emph{G}-tests for each category, of course.
|
||||
#' @seealso \code{\link{chisq.test}}
|
||||
#' @references [1] McDonald, J.H. 2014. \strong{Handbook of Biological Statistics (3rd ed.)}. Sparky House Publishing, Baltimore, Maryland. \url{http://www.biostathandbook.com/gtestgof.html}.
|
||||
#' @source This code is almost identical to \code{\link{chisq.test}}, except that:
|
||||
#' \itemize{
|
||||
#' \item{The calculation of the statistic was changed to \code{2 * sum(x * log(x / E))}}
|
||||
#' \item{Yates' continuity correction was removed as it does not apply to a \emph{G}-test}
|
||||
#' \item{The possibility to simulate p values with \code{simulate.p.value} was removed}
|
||||
#' }
|
||||
#' If there are more than two categories and you want to find out which ones are significantly different from their null expectation, you can use the same method of testing each category vs. the sum of all categories, with the Bonferroni correction. You use *G*-tests for each category, of course.
|
||||
#' @seealso [chisq.test()]
|
||||
#' @references [1] McDonald, J.H. 2014. **Handbook of Biological Statistics (3rd ed.)**. Sparky House Publishing, Baltimore, Maryland. <http://www.biostathandbook.com/gtestgof.html>.
|
||||
#' @source The code for this function is identical to that of [chisq.test()], except that:
|
||||
#' - The calculation of the statistic was changed to \eqn{2 * sum(x * log(x / E))}
|
||||
#' - Yates' continuity correction was removed as it does not apply to a *G*-test
|
||||
#' - The possibility to simulate p values with `simulate.p.value` was removed
|
||||
#' @export
|
||||
#' @importFrom stats pchisq complete.cases
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
|
@ -19,20 +19,20 @@
|
||||
# Visit our website for more info: https://msberends.gitlab.io/AMR. #
|
||||
# ==================================================================== #
|
||||
|
||||
#' AMR plots with \code{ggplot2}
|
||||
#' AMR plots with `ggplot2`
|
||||
#'
|
||||
#' Use these functions to create bar plots for antimicrobial resistance analysis. All functions rely on internal \code{\link[ggplot2]{ggplot}2} functions.
|
||||
#' @param data a \code{data.frame} with column(s) of class \code{"rsi"} (see \code{\link{as.rsi}})
|
||||
#' @param position position adjustment of bars, either \code{"fill"}, \code{"stack"} or \code{"dodge"}
|
||||
#' @param x variable to show on x axis, either \code{"antibiotic"} (default) or \code{"interpretation"} or a grouping variable
|
||||
#' @param fill variable to categorise using the plots legend, either \code{"antibiotic"} (default) or \code{"interpretation"} or a grouping variable
|
||||
#' Use these functions to create bar plots for antimicrobial resistance analysis. All functions rely on internal [ggplot2][ggplot2::ggplot()] functions.
|
||||
#' @param data a [`data.frame`] with column(s) of class [`rsi`] (see [as.rsi()])
|
||||
#' @param position position adjustment of bars, either `"fill"`, `"stack"` or `"dodge"`
|
||||
#' @param x variable to show on x axis, either `"antibiotic"` (default) or `"interpretation"` or a grouping variable
|
||||
#' @param fill variable to categorise using the plots legend, either `"antibiotic"` (default) or `"interpretation"` or a grouping variable
|
||||
#' @param breaks numeric vector of positions
|
||||
#' @param limits numeric vector of length two providing limits of the scale, use \code{NA} to refer to the existing minimum or maximum
|
||||
#' @param facet variable to split plots by, either \code{"interpretation"} (default) or \code{"antibiotic"} or a grouping variable
|
||||
#' @param limits numeric vector of length two providing limits of the scale, use `NA` to refer to the existing minimum or maximum
|
||||
#' @param facet variable to split plots by, either `"interpretation"` (default) or `"antibiotic"` or a grouping variable
|
||||
#' @inheritParams proportion
|
||||
#' @param nrow (when using \code{facet}) number of rows
|
||||
#' @param colours a named vector with colours for the bars. The names must be one or more of: S, SI, I, IR, R or be \code{FALSE} to use default \code{ggplot2} colours.
|
||||
#' @param datalabels show datalabels using \code{labels_rsi_count}
|
||||
#' @param nrow (when using `facet`) number of rows
|
||||
#' @param colours a named vector with colours for the bars. The names must be one or more of: S, SI, I, IR, R or be `FALSE` to use default [ggplot2][[ggplot2::ggplot()] colours.
|
||||
#' @param datalabels show datalabels using [labels_rsi_count()]
|
||||
#' @param datalabels.size size of the datalabels
|
||||
#' @param datalabels.colour colour of the datalabels
|
||||
#' @param title text to show as title of the plot
|
||||
@ -40,23 +40,23 @@
|
||||
#' @param caption text to show as caption of the plot
|
||||
#' @param x.title text to show as x axis description
|
||||
#' @param y.title text to show as y axis description
|
||||
#' @param ... other parameters passed on to \code{geom_rsi}
|
||||
#' @details At default, the names of antibiotics will be shown on the plots using \code{\link{ab_name}}. This can be set with the \code{translate_ab} parameter. See \code{\link{count_df}}.
|
||||
#' @param ... other parameters passed on to [geom_rsi()]
|
||||
#' @details At default, the names of antibiotics will be shown on the plots using [ab_name()]. This can be set with the `translate_ab` parameter. See [count_df()].
|
||||
#'
|
||||
#' \strong{The functions}\cr
|
||||
#' \code{geom_rsi} will take any variable from the data that has an \code{rsi} class (created with \code{\link{as.rsi}}) using \code{\link{rsi_df}} and will plot bars with the percentage R, I and S. The default behaviour is to have the bars stacked and to have the different antibiotics on the x axis.
|
||||
#' ## The functions
|
||||
#' [geom_rsi()] will take any variable from the data that has an [`rsi`] class (created with [as.rsi()]) using [rsi_df()] and will plot bars with the percentage R, I and S. The default behaviour is to have the bars stacked and to have the different antibiotics on the x axis.
|
||||
#'
|
||||
#' \code{facet_rsi} creates 2d plots (at default based on S/I/R) using \code{\link[ggplot2]{facet_wrap}}.
|
||||
#' [facet_rsi()] creates 2d plots (at default based on S/I/R) using [ggplot2::facet_wrap()].
|
||||
#'
|
||||
#' \code{scale_y_percent} transforms the y axis to a 0 to 100\% range using \code{\link[ggplot2]{scale_continuous}}.
|
||||
#' [scale_y_percent()] transforms the y axis to a 0 to 100% range using [ggplot2::scale_continuous()].
|
||||
#'
|
||||
#' \code{scale_rsi_colours} sets colours to the bars: pastel blue for S, pastel turquoise for I and pastel red for R, using \code{\link[ggplot2]{scale_brewer}}.
|
||||
#' [scale_rsi_colours()] sets colours to the bars: pastel blue for S, pastel turquoise for I and pastel red for R, using [ggplot2::scale_brewer()].
|
||||
#'
|
||||
#' \code{theme_rsi} is a \code{ggplot \link[ggplot2]{theme}} with minimal distraction.
|
||||
#' [theme_rsi()] is a [ggplot2 theme][[ggplot2::theme()] with minimal distraction.
|
||||
#'
|
||||
#' \code{labels_rsi_count} print datalabels on the bars with percentage and amount of isolates using \code{\link[ggplot2]{geom_text}}
|
||||
#' [labels_rsi_count()] print datalabels on the bars with percentage and amount of isolates using [ggplot2::geom_text()]
|
||||
#'
|
||||
#' \code{ggplot_rsi} is a wrapper around all above functions that uses data as first input. This makes it possible to use this function after a pipe (\code{\%>\%}). See Examples.
|
||||
#' [ggplot_rsi()] is a wrapper around all above functions that uses data as first input. This makes it possible to use this function after a pipe (`%>%`). See Examples.
|
||||
#' @rdname ggplot_rsi
|
||||
#' @export
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
|
@ -21,14 +21,14 @@
|
||||
|
||||
#' Guess antibiotic column
|
||||
#'
|
||||
#' This tries to find a column name in a data set based on information from the \code{\link{antibiotics}} data set. Also supports WHONET abbreviations.
|
||||
#' @param x a \code{data.frame}
|
||||
#' @param search_string a text to search \code{x} for, will be checked with \code{\link{as.ab}} if this value is not a column in \code{x}
|
||||
#' This tries to find a column name in a data set based on information from the [antibiotics] data set. Also supports WHONET abbreviations.
|
||||
#' @param x a [`data.frame`]
|
||||
#' @param search_string a text to search `x` for, will be checked with [as.ab()] if this value is not a column in `x`
|
||||
#' @param verbose a logical to indicate whether additional info should be printed
|
||||
#' @details You can look for an antibiotic (trade) name or abbreviation and it will search \code{x} and the \code{\link{antibiotics}} data set for any column containing a name or code of that antibiotic. \strong{Longer columns names take precendence over shorter column names.}
|
||||
#' @details You can look for an antibiotic (trade) name or abbreviation and it will search `x` and the [antibiotics] data set for any column containing a name or code of that antibiotic. **Longer columns names take precendence over shorter column names.**
|
||||
#' @importFrom dplyr %>% select filter_all any_vars
|
||||
#' @importFrom crayon blue
|
||||
#' @return A column name of \code{x}, or \code{NULL} when no result is found.
|
||||
#' @return A column name of `x`, or `NULL` when no result is found.
|
||||
#' @export
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @examples
|
||||
|
@ -19,17 +19,17 @@
|
||||
# Visit our website for more info: https://msberends.gitlab.io/AMR. #
|
||||
# ==================================================================== #
|
||||
|
||||
#' Join a table with \code{microorganisms}
|
||||
#' Join a table with [microorganisms]
|
||||
#'
|
||||
#' Join the dataset \code{\link{microorganisms}} easily to an existing table or character vector.
|
||||
#' Join the data set [microorganisms] easily to an existing table or character vector.
|
||||
#' @rdname join
|
||||
#' @name join
|
||||
#' @aliases join inner_join
|
||||
#' @param x existing table to join, or character vector
|
||||
#' @param by a variable to join by - if left empty will search for a column with class \code{mo} (created with \code{\link{as.mo}}) or will be \code{"mo"} if that column name exists in \code{x}, could otherwise be a column name of \code{x} with values that exist in \code{microorganisms$mo} (like \code{by = "bacteria_id"}), or another column in \code{\link{microorganisms}} (but then it should be named, like \code{by = c("my_genus_species" = "fullname")})
|
||||
#' @param suffix if there are non-joined duplicate variables in \code{x} and \code{y}, these suffixes will be added to the output to disambiguate them. Should be a character vector of length 2.
|
||||
#' @param ... other parameters to pass on to \code{dplyr::\link[dplyr]{join}}.
|
||||
#' @details \strong{Note:} As opposed to the \code{\link[dplyr]{join}} functions of \code{dplyr}, characters vectors are supported and at default existing columns will get a suffix \code{"2"} and the newly joined columns will not get a suffix. See \code{\link[dplyr]{join}} for more information.
|
||||
#' @param by a variable to join by - if left empty will search for a column with class [`mo`] (created with [as.mo()]) or will be `"mo"` if that column name exists in `x`, could otherwise be a column name of `x` with values that exist in `microorganisms$mo` (like `by = "bacteria_id"`), or another column in [microorganisms] (but then it should be named, like `by = c("my_genus_species" = "fullname")`)
|
||||
#' @param suffix if there are non-joined duplicate variables in `x` and `y`, these suffixes will be added to the output to disambiguate them. Should be a character vector of length 2.
|
||||
#' @param ... other parameters to pass on to [dplyr::join()]
|
||||
#' @details **Note:** As opposed to the [dplyr::join()] functions of `dplyr`, [`characters`] vectors are supported and at default existing columns will get a suffix `"2"` and the newly joined columns will not get a suffix. See [dplyr::join()] for more information.
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @export
|
||||
#' @examples
|
||||
|
@ -19,33 +19,54 @@
|
||||
# Visit our website for more info: https://msberends.gitlab.io/AMR. #
|
||||
# ==================================================================== #
|
||||
|
||||
#' Key antibiotics for first \emph{weighted} isolates
|
||||
#' Key antibiotics for first *weighted* isolates
|
||||
#'
|
||||
#' These function can be used to determine first isolates (see \code{\link{first_isolate}}). Using key antibiotics to determine first isolates is more reliable than without key antibiotics. These selected isolates will then be called first \emph{weighted} isolates.
|
||||
#' @param x table with antibiotics coloms, like \code{AMX} or \code{amox}
|
||||
#' These function can be used to determine first isolates (see [first_isolate()]). Using key antibiotics to determine first isolates is more reliable than without key antibiotics. These selected isolates will then be called first *weighted* isolates.
|
||||
#' @param x table with antibiotics coloms, like `AMX` or `amox`
|
||||
#' @param y,z characters to compare
|
||||
#' @inheritParams first_isolate
|
||||
#' @param universal_1,universal_2,universal_3,universal_4,universal_5,universal_6 column names of \strong{broad-spectrum} antibiotics, case-insensitive. At default, the columns containing these antibiotics will be guessed with \code{\link{guess_ab_col}}.
|
||||
#' @param GramPos_1,GramPos_2,GramPos_3,GramPos_4,GramPos_5,GramPos_6 column names of antibiotics for \strong{Gram-positives}, case-insensitive. At default, the columns containing these antibiotics will be guessed with \code{\link{guess_ab_col}}.
|
||||
#' @param GramNeg_1,GramNeg_2,GramNeg_3,GramNeg_4,GramNeg_5,GramNeg_6 column names of antibiotics for \strong{Gram-negatives}, case-insensitive. At default, the columns containing these antibiotics will be guessed with \code{\link{guess_ab_col}}.
|
||||
#' @param universal_1,universal_2,universal_3,universal_4,universal_5,universal_6 column names of **broad-spectrum** antibiotics, case-insensitive. At default, the columns containing these antibiotics will be guessed with [guess_ab_col()].
|
||||
#' @param GramPos_1,GramPos_2,GramPos_3,GramPos_4,GramPos_5,GramPos_6 column names of antibiotics for **Gram-positives**, case-insensitive. At default, the columns containing these antibiotics will be guessed with [guess_ab_col()].
|
||||
#' @param GramNeg_1,GramNeg_2,GramNeg_3,GramNeg_4,GramNeg_5,GramNeg_6 column names of antibiotics for **Gram-negatives**, case-insensitive. At default, the columns containing these antibiotics will be guessed with [guess_ab_col()].
|
||||
#' @param warnings give warning about missing antibiotic columns, they will anyway be ignored
|
||||
#' @param ... other parameters passed on to function
|
||||
#' @details The function \code{key_antibiotics} returns a character vector with 12 antibiotic results for every isolate. These isolates can then be compared using \code{key_antibiotics_equal}, to check if two isolates have generally the same antibiogram. Missing and invalid values are replaced with a dot (\code{"."}). The \code{\link{first_isolate}} function only uses this function on the same microbial species from the same patient. Using this, an MRSA will be included after a susceptible \emph{S. aureus} (MSSA) found within the same episode (see \code{episode} parameter of \code{\link{first_isolate}}). Without key antibiotic comparison it would not.
|
||||
#' @details The function [key_antibiotics()] returns a character vector with 12 antibiotic results for every isolate. These isolates can then be compared using [key_antibiotics_equal()], to check if two isolates have generally the same antibiogram. Missing and invalid values are replaced with a dot (`"."`). The [first_isolate()] function only uses this function on the same microbial species from the same patient. Using this, an MRSA will be included after a susceptible *S. aureus* (MSSA) found within the same episode (see `episode` parameter of [first_isolate()]). Without key antibiotic comparison it would not.
|
||||
#'
|
||||
#' At default, the antibiotics that are used for \strong{Gram-positive bacteria} are: \cr
|
||||
#' amoxicillin, amoxicillin/clavulanic acid, cefuroxime, piperacillin/tazobactam, ciprofloxacin, trimethoprim/sulfamethoxazole (until here is universal), vancomycin, teicoplanin, tetracycline, erythromycin, oxacillin, rifampin.
|
||||
#' At default, the antibiotics that are used for **Gram-positive bacteria** are:
|
||||
#' - Amoxicillin
|
||||
#' - Amoxicillin/clavulanic acid
|
||||
#' - Cefuroxime
|
||||
#' - Piperacillin/tazobactam
|
||||
#' - Ciprofloxacin
|
||||
#' - Trimethoprim/sulfamethoxazole
|
||||
#' - Vancomycin
|
||||
#' - Teicoplanin
|
||||
#' - Tetracycline
|
||||
#' - Erythromycin
|
||||
#' - Oxacillin
|
||||
#' - Rifampin
|
||||
#'
|
||||
#' At default, the antibiotics that are used for \strong{Gram-negative bacteria} are: \cr
|
||||
#' amoxicillin, amoxicillin/clavulanic acid, cefuroxime, piperacillin/tazobactam, ciprofloxacin, trimethoprim/sulfamethoxazole (until here is universal), gentamicin, tobramycin, colistin, cefotaxime, ceftazidime, meropenem.
|
||||
#'
|
||||
#'
|
||||
#' The function \code{key_antibiotics_equal} checks the characters returned by \code{key_antibiotics} for equality, and returns a logical vector.
|
||||
#' At default the antibiotics that are used for **Gram-negative bacteria** are:
|
||||
#' - Amoxicillin
|
||||
#' - Amoxicillin/clavulanic acid
|
||||
#' - Cefuroxime
|
||||
#' - Piperacillin/tazobactam
|
||||
#' - Ciprofloxacin
|
||||
#' - Trimethoprim/sulfamethoxazole
|
||||
#' - Gentamicin
|
||||
#' - Tobramycin
|
||||
#' - Colistin
|
||||
#' - Cefotaxime
|
||||
#' - Ceftazidime
|
||||
#' - Meropenem
|
||||
#'
|
||||
#' The function [key_antibiotics_equal()] checks the characters returned by [key_antibiotics()] for equality, and returns a [`logical`] vector.
|
||||
#' @inheritSection first_isolate Key antibiotics
|
||||
#' @rdname key_antibiotics
|
||||
#' @export
|
||||
#' @importFrom dplyr %>% mutate if_else pull
|
||||
#' @importFrom crayon blue bold
|
||||
#' @seealso \code{\link{first_isolate}}
|
||||
#' @seealso [first_isolate()]
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @examples
|
||||
#' # `example_isolates` is a dataset available in the AMR package.
|
||||
|
@ -22,11 +22,10 @@
|
||||
#' Kurtosis of the sample
|
||||
#'
|
||||
#' @description Kurtosis is a measure of the "tailedness" of the probability distribution of a real-valued random variable.
|
||||
#'
|
||||
#' @param x a vector of values, a \code{matrix} or a \code{data frame}
|
||||
#' @param na.rm a logical value indicating whether \code{NA} values should be stripped before the computation proceeds.
|
||||
#' @param x a vector of values, a [`matrix`] or a [`data frame`]
|
||||
#' @param na.rm a logical value indicating whether `NA` values should be stripped before the computation proceeds.
|
||||
#' @exportMethod kurtosis
|
||||
#' @seealso \code{\link{skewness}}
|
||||
#' @seealso [skewness()]
|
||||
#' @rdname kurtosis
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @export
|
||||
|
10
R/like.R
10
R/like.R
@ -21,15 +21,15 @@
|
||||
|
||||
#' Pattern Matching
|
||||
#'
|
||||
#' Convenient wrapper around \code{\link[base]{grep}} to match a pattern: \code{a \%like\% b}. It always returns a \code{logical} vector and is always case-insensitive (use \code{a \%like_case\% b} for case-sensitive matching). Also, \code{pattern} (\code{b}) can be as long as \code{x} (\code{a}) to compare items of each index in both vectors, or can both have the same length to iterate over all cases.
|
||||
#' Convenient wrapper around [base::grep()] to match a pattern: `a %like% b`. It always returns a [`logical`] vector and is always case-insensitive (use `a %like_case% b` for case-sensitive matching). Also, `pattern` (*b*) can be as long as `x` (*a*) to compare items of each index in both vectors, or can both have the same length to iterate over all cases.
|
||||
#' @inheritParams base::grepl
|
||||
#' @return A \code{logical} vector
|
||||
#' @return A [`logical`] vector
|
||||
#' @name like
|
||||
#' @rdname like
|
||||
#' @export
|
||||
#' @details Using RStudio? This function can also be inserted from the Addins menu and can have its own Keyboard Shortcut like Ctrl+Shift+L or Cmd+Shift+L (see Tools > Modify Keyboard Shortcuts...).
|
||||
#' @source Idea from the \href{https://github.com/Rdatatable/data.table/blob/master/R/like.R}{\code{like} function from the \code{data.table} package}, but made it case insensitive at default and let it support multiple patterns. Also, if the regex fails the first time, it tries again with \code{perl = TRUE}.
|
||||
#' @seealso \code{\link[base]{grep}}
|
||||
#' @details Using RStudio? This function can also be inserted from the Addins menu and can have its own Keyboard Shortcut like `Ctrl+Shift+L` or `Cmd+Shift+L` (see `Tools` > `Modify Keyboard Shortcuts...`).
|
||||
#' @source Idea from the [`like` function from the `data.table` package](https://github.com/Rdatatable/data.table/blob/master/R/like.R), but made it case insensitive at default and let it support multiple patterns. Also, if the regex fails the first time, it tries again with `perl = TRUE`.
|
||||
#' @seealso [base::grep()]
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @examples
|
||||
#' # simple test
|
||||
|
53
R/mdro.R
53
R/mdro.R
@ -22,35 +22,42 @@
|
||||
#' Determine multidrug-resistant organisms (MDRO)
|
||||
#'
|
||||
#' Determine which isolates are multidrug-resistant organisms (MDRO) according to international and national guidelines.
|
||||
#' @param guideline a specific guideline to follow. When left empty, the publication by Magiorakos \emph{et al.} (2012, Clinical Microbiology and Infection) will be followed, see Details.
|
||||
#' @param info print progress
|
||||
#' @param guideline a specific guideline to follow. When left empty, the publication by Magiorakos *et al.* (2012, Clinical Microbiology and Infection) will be followed, please see *Details*.
|
||||
#' @param info a logical to indicate whether progress should be printed to the console
|
||||
#' @inheritParams eucast_rules
|
||||
#' @param pct_required_classes minimal required percentage of antimicrobial classes that must be available per isolate, rounded down. For example, with the default guideline, 17 antimicrobial classes must be available for \emph{S. aureus}. Setting this \code{pct_required_classes} argument to \code{0.5} (default) means that for every \emph{S. aureus} isolate at least 8 different classes must be available. Any lower number of available classes will return \code{NA} for that isolate.
|
||||
#' @param combine_SI a logical to indicate whether all values of S and I must be merged into one, so resistance is only considered when isolates are R, not I. As this is the default behaviour of the \code{mdro()} function, it follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see section 'Interpretation of S, I and R' below. When using \code{combine_SI = FALSE}, resistance is considered when isolates are R or I.
|
||||
#' @param pct_required_classes minimal required percentage of antimicrobial classes that must be available per isolate, rounded down. For example, with the default guideline, 17 antimicrobial classes must be available for *S. aureus*. Setting this `pct_required_classes` argument to `0.5` (default) means that for every *S. aureus* isolate at least 8 different classes must be available. Any lower number of available classes will return `NA` for that isolate.
|
||||
#' @param combine_SI a logical to indicate whether all values of S and I must be merged into one, so resistance is only considered when isolates are R, not I. As this is the default behaviour of the [mdro()] function, it follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see section 'Interpretation of S, I and R' below. When using `combine_SI = FALSE`, resistance is considered when isolates are R or I.
|
||||
#' @param verbose a logical to turn Verbose mode on and off (default is off). In Verbose mode, the function does not return the MDRO results, but instead returns a data set in logbook form with extensive info about which isolates would be MDRO-positive, or why they are not.
|
||||
#' @inheritSection eucast_rules Antibiotics
|
||||
#' @details
|
||||
#' For the \code{pct_required_classes} argument, values above 1 will be divided by 100. This is to support both fractions (\code{0.75} or \code{3/4}) and percentages (\code{75}).
|
||||
#' For the `pct_required_classes` argument, values above 1 will be divided by 100. This is to support both fractions (`0.75` or `3/4`) and percentages (`75`).
|
||||
#'
|
||||
#' Currently supported guidelines are (case-insensitive):
|
||||
#' \itemize{
|
||||
#' \item{\code{guideline = "CMI2012"}: Magiorakos AP, Srinivasan A \emph{et al.} "Multidrug-resistant, extensively drug-resistant and pandrug-resistant bacteria: an international expert proposal for interim standard definitions for acquired resistance." Clinical Microbiology and Infection (2012) (\href{https://www.clinicalmicrobiologyandinfection.com/article/S1198-743X(14)61632-3/fulltext}{link})}
|
||||
#' \item{\code{guideline = "EUCAST"}: The European international guideline - EUCAST Expert Rules Version 3.1 "Intrinsic Resistance and Exceptional Phenotypes Tables" (\href{http://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf}{link})}
|
||||
#' \item{\code{guideline = "TB"}: The international guideline for multi-drug resistant tuberculosis - World Health Organization "Companion handbook to the WHO guidelines for the programmatic management of drug-resistant tuberculosis" (\href{https://www.who.int/tb/publications/pmdt_companionhandbook/en/}{link})}
|
||||
#' \item{\code{guideline = "MRGN"}: The German national guideline - Mueller et al. (2015) Antimicrobial Resistance and Infection Control 4:7. DOI: 10.1186/s13756-015-0047-6}
|
||||
#' \item{\code{guideline = "BRMO"}: The Dutch national guideline - Rijksinstituut voor Volksgezondheid en Milieu "WIP-richtlijn BRMO (Bijzonder Resistente Micro-Organismen) [ZKH]" (\href{https://www.rivm.nl/Documenten_en_publicaties/Professioneel_Praktisch/Richtlijnen/Infectieziekten/WIP_Richtlijnen/WIP_Richtlijnen/Ziekenhuizen/WIP_richtlijn_BRMO_Bijzonder_Resistente_Micro_Organismen_ZKH}{link})}
|
||||
#' }
|
||||
#'
|
||||
#' Please suggest your own (country-specific) guidelines by letting us know: \url{https://gitlab.com/msberends/AMR/issues/new}.
|
||||
#'
|
||||
#' \strong{Note:} Every test that involves the Enterobacteriaceae family, will internally be performed using its newly named order Enterobacterales, since the Enterobacteriaceae family has been taxonomically reclassified by Adeolu \emph{et al.} in 2016. Before that, Enterobacteriaceae was the only family under the Enterobacteriales (with an i) order. All species under the old Enterobacteriaceae family are still under the new Enterobacterales (without an i) order, but divided into multiple families. The way tests are performed now by this \code{mdro()} function makes sure that results from before 2016 and after 2016 are identical.
|
||||
#' - `guideline = "CMI2012"`\cr
|
||||
#' Magiorakos AP, Srinivasan A *et al.* "Multidrug-resistant, extensively drug-resistant and pandrug-resistant bacteria: an international expert proposal for interim standard definitions for acquired resistance." Clinical Microbiology and Infection (2012) ([link](https://www.clinicalmicrobiologyandinfection.com/article/S1198-743X(14)61632-3/fulltext))
|
||||
#' - `guideline = "EUCAST"`\cr
|
||||
#' The European international guideline - EUCAST Expert Rules Version 3.1 "Intrinsic Resistance and Exceptional Phenotypes Tables" ([link](http://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf))
|
||||
#' - `guideline = "TB"`\cr
|
||||
#' The international guideline for multi-drug resistant tuberculosis - World Health Organization "Companion handbook to the WHO guidelines for the programmatic management of drug-resistant tuberculosis" ([link](https://www.who.int/tb/publications/pmdt_companionhandbook/en/))
|
||||
#' - `guideline = "MRGN"`\cr
|
||||
#' The German national guideline - Mueller et al. (2015) Antimicrobial Resistance and Infection Control 4:7. DOI: 10.1186/s13756-015-0047-6
|
||||
#' - `guideline = "BRMO"`\cr
|
||||
#' The Dutch national guideline - Rijksinstituut voor Volksgezondheid en Milieu "WIP-richtlijn BRMO (Bijzonder Resistente Micro-Organismen) [ZKH]" ([link](https://www.rivm.nl/Documenten_en_publicaties/Professioneel_Praktisch/Richtlijnen/Infectieziekten/WIP_Richtlijnen/WIP_Richtlijnen/Ziekenhuizen/WIP_richtlijn_BRMO_Bijzonder_Resistente_Micro_Organismen_ZKH))
|
||||
#'
|
||||
#' Please suggest your own (country-specific) guidelines by letting us know: <https://gitlab.com/msberends/AMR/issues/new>.
|
||||
#'
|
||||
#' **Note:** Every test that involves the Enterobacteriaceae family, will internally be performed using its newly named order Enterobacterales, since the Enterobacteriaceae family has been taxonomically reclassified by Adeolu *et al.* in 2016. Before that, Enterobacteriaceae was the only family under the Enterobacteriales (with an i) order. All species under the old Enterobacteriaceae family are still under the new Enterobacterales (without an i) order, but divided into multiple families. The way tests are performed now by this [mdro()] function makes sure that results from before 2016 and after 2016 are identical.
|
||||
#' @inheritSection as.rsi Interpretation of S, I and R
|
||||
#' @return \itemize{
|
||||
#' \item{CMI 2012 paper - function \code{mdr_cmi2012()} or \code{mdro()}:\cr Ordered factor with levels \code{Negative < Multi-drug-resistant (MDR) < Extensively drug-resistant (XDR) < Pandrug-resistant (PDR)}}
|
||||
#' \item{TB guideline - function \code{mdr_tb()} or \code{mdro(..., guideline = "TB")}:\cr Ordered factor with levels \code{Negative < Mono-resistant < Poly-resistant < Multi-drug-resistant < Extensively drug-resistant}}
|
||||
#' \item{German guideline - function \code{mrgn()} or \code{mdro(..., guideline = "MRGN")}:\cr Ordered factor with levels \code{Negative < 3MRGN < 4MRGN}}
|
||||
#' \item{Everything else:\cr Ordered factor with levels \code{Negative < Positive, unconfirmed < Positive}. The value \code{"Positive, unconfirmed"} means that, according to the guideline, it is not entirely sure if the isolate is multi-drug resistant and this should be confirmed with additional (e.g. molecular) tests}
|
||||
#' }
|
||||
#' @return
|
||||
#' - CMI 2012 paper - function [mdr_cmi2012()] or [mdro()]:\cr
|
||||
#' Ordered [`factor`] with levels `Negative` < `Multi-drug-resistant (MDR)` < `Extensively drug-resistant (XDR)` < `Pandrug-resistant (PDR)`
|
||||
#' - TB guideline - function [mdr_tb()] or [`mdro(..., guideline = "TB")`][mdro()]:\cr
|
||||
#' Ordered [`factor`] with levels `Negative` < `Mono-resistant` < `Poly-resistant` < `Multi-drug-resistant` < `Extensively drug-resistant`
|
||||
#' - German guideline - function [mrgn()] or [`mdro(..., guideline = "MRGN")`][mdro()]:\cr
|
||||
#' Ordered [`factor`] with levels `Negative` < `3MRGN` < `4MRGN`
|
||||
#' - Everything else:\cr
|
||||
#' Ordered [`factor`] with levels `Negative` < `Positive, unconfirmed` < `Positive`. The value `"Positive, unconfirmed"` means that, according to the guideline, it is not entirely sure if the isolate is multi-drug resistant and this should be confirmed with additional (e.g. molecular) tests
|
||||
#' @rdname mdro
|
||||
#' @aliases MDR XDR PDR BRMO 3MRGN 4MRGN
|
||||
#' @importFrom dplyr %>% filter_at vars all_vars pull mutate_at
|
||||
@ -59,7 +66,7 @@
|
||||
#' @export
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @source
|
||||
#' Please see Details for the list of publications used for this function.
|
||||
#' Please see *Details* for the list of publications used for this function.
|
||||
#' @examples
|
||||
#' \donttest{
|
||||
#' library(dplyr)
|
||||
@ -74,7 +81,7 @@
|
||||
#' MRGN = mrgn(.))
|
||||
#' }
|
||||
mdro <- function(x,
|
||||
guideline = NULL,
|
||||
guideline = "CMI2012",
|
||||
col_mo = NULL,
|
||||
info = TRUE,
|
||||
pct_required_classes = 0.5,
|
||||
|
8
R/mic.R
8
R/mic.R
@ -21,16 +21,16 @@
|
||||
|
||||
#' Class 'mic'
|
||||
#'
|
||||
#' This transforms a vector to a new class \code{mic}, which is an ordered factor with valid MIC values as levels. Invalid MIC values will be translated as \code{NA} with a warning.
|
||||
#' This transforms a vector to a new class [`mic`], which is an ordered [`factor`] with valid MIC values as levels. Invalid MIC values will be translated as `NA` with a warning.
|
||||
#' @rdname as.mic
|
||||
#' @param x vector
|
||||
#' @param na.rm a logical indicating whether missing values should be removed
|
||||
#' @details Interpret MIC values as RSI values with \code{\link{as.rsi}}. It supports guidelines from EUCAST and CLSI.
|
||||
#' @return Ordered factor with new class \code{mic}
|
||||
#' @details To interpret MIC values as RSI values, use [as.rsi()] on MIC values. It supports guidelines from EUCAST and CLSI.
|
||||
#' @return Ordered [`factor`] with new class [`mic`]
|
||||
#' @aliases MIC
|
||||
#' @export
|
||||
#' @importFrom dplyr %>%
|
||||
#' @seealso \code{\link{as.rsi}}
|
||||
#' @seealso [as.rsi()]
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @examples
|
||||
#' mic_data <- as.mic(c(">=32", "1.0", "1", "1.00", 8, "<=0.128", "8", "16", "16"))
|
||||
|
121
R/mo.R
121
R/mo.R
@ -21,24 +21,25 @@
|
||||
|
||||
#' Transform to microorganism ID
|
||||
#'
|
||||
#' Use this function to determine a valid microorganism ID (\code{mo}). Determination is done using intelligent rules and the complete taxonomic kingdoms Bacteria, Chromista, Protozoa, Archaea and most microbial species from the kingdom Fungi (see Source). The input can be almost anything: a full name (like \code{"Staphylococcus aureus"}), an abbreviated name (like \code{"S. aureus"}), an abbreviation known in the field (like \code{"MRSA"}), or just a genus. Please see Examples.
|
||||
#' @param x a character vector or a \code{data.frame} with one or two columns
|
||||
#' @param Becker a logical to indicate whether \emph{Staphylococci} should be categorised into coagulase-negative \emph{Staphylococci} ("CoNS") and coagulase-positive \emph{Staphylococci} ("CoPS") instead of their own species, according to Karsten Becker \emph{et al.} [1,2]. Note that this does not include species that were newly named after these publications, like \emph{S. caeli}.
|
||||
#' Use this function to determine a valid microorganism ID ([`mo`]). Determination is done using intelligent rules and the complete taxonomic kingdoms Bacteria, Chromista, Protozoa, Archaea and most microbial species from the kingdom Fungi (see Source). The input can be almost anything: a full name (like `"Staphylococcus aureus"`), an abbreviated name (like `"S. aureus"`), an abbreviation known in the field (like `"MRSA"`), or just a genus. Please see *Examples*.
|
||||
#' @param x a character vector or a [`data.frame`] with one or two columns
|
||||
#' @param Becker a logical to indicate whether *Staphylococci* should be categorised into coagulase-negative *Staphylococci* ("CoNS") and coagulase-positive *Staphylococci* ("CoPS") instead of their own species, according to Karsten Becker *et al.* (1,2). Note that this does not include species that were newly named after these publications, like *S. caeli*.
|
||||
#'
|
||||
#' This excludes \emph{Staphylococcus aureus} at default, use \code{Becker = "all"} to also categorise \emph{S. aureus} as "CoPS".
|
||||
#' @param Lancefield a logical to indicate whether beta-haemolytic \emph{Streptococci} should be categorised into Lancefield groups instead of their own species, according to Rebecca C. Lancefield [3]. These \emph{Streptococci} will be categorised in their first group, e.g. \emph{Streptococcus dysgalactiae} will be group C, although officially it was also categorised into groups G and L.
|
||||
#' This excludes *Staphylococcus aureus* at default, use `Becker = "all"` to also categorise *S. aureus* as "CoPS".
|
||||
#' @param Lancefield a logical to indicate whether beta-haemolytic *Streptococci* should be categorised into Lancefield groups instead of their own species, according to Rebecca C. Lancefield (3). These *Streptococci* will be categorised in their first group, e.g. *Streptococcus dysgalactiae* will be group C, although officially it was also categorised into groups G and L.
|
||||
#'
|
||||
#' This excludes \emph{Enterococci} at default (who are in group D), use \code{Lancefield = "all"} to also categorise all \emph{Enterococci} as group D.
|
||||
#' @param allow_uncertain a number between 0 (or "none") and 3 (or "all"), or TRUE (= 2) or FALSE (= 0) to indicate whether the input should be checked for less probable results, see Details
|
||||
#' @param reference_df a \code{data.frame} to use for extra reference when translating \code{x} to a valid \code{mo}. See \code{\link{set_mo_source}} and \code{\link{get_mo_source}} to automate the usage of your own codes (e.g. used in your analysis or organisation).
|
||||
#' This excludes *Enterococci* at default (who are in group D), use `Lancefield = "all"` to also categorise all *Enterococci* as group D.
|
||||
#' @param allow_uncertain a number between `0` (or `"none"`) and `3` (or `"all"`), or `TRUE` (= `2`) or `FALSE` (= `0`) to indicate whether the input should be checked for less probable results, please see *Details*
|
||||
#' @param reference_df a [`data.frame`] to use for extra reference when translating `x` to a valid [`mo`]. See [set_mo_source()] and [get_mo_source()] to automate the usage of your own codes (e.g. used in your analysis or organisation).
|
||||
#' @param ... other parameters passed on to functions
|
||||
#' @rdname as.mo
|
||||
#' @aliases mo
|
||||
#' @keywords mo Becker becker Lancefield lancefield guess
|
||||
#' @details
|
||||
#' \strong{General info} \cr
|
||||
#' A microorganism ID from this package (class: \code{mo}) typically looks like these examples:\cr
|
||||
#' \preformatted{
|
||||
#' ## General info
|
||||
#'
|
||||
#' A microorganism ID from this package (class: [`mo`]) typically looks like these examples:
|
||||
#' ```
|
||||
#' Code Full name
|
||||
#' --------------- --------------------------------------
|
||||
#' B_KLBSL Klebsiella
|
||||
@ -51,81 +52,71 @@
|
||||
#' | ----> genus, a 5-7 letter acronym
|
||||
#' ----> taxonomic kingdom: A (Archaea), AN (Animalia), B (Bacteria),
|
||||
#' C (Chromista), F (Fungi), P (Protozoa)
|
||||
#' }
|
||||
#' ```
|
||||
#'
|
||||
#' Values that cannot be coered will be considered 'unknown' and will get the MO code \code{UNKNOWN}.
|
||||
#' Values that cannot be coered will be considered 'unknown' and will get the MO code `UNKNOWN`.
|
||||
#'
|
||||
#' Use the \code{\link{mo_property}_*} functions to get properties based on the returned code, see Examples.
|
||||
#' Use the [`mo_property_*`][mo_property()] functions to get properties based on the returned code, see Examples.
|
||||
#'
|
||||
#' The algorithm uses data from the Catalogue of Life (see below) and from one other source (see \code{\link{microorganisms}}).
|
||||
#' The algorithm uses data from the Catalogue of Life (see below) and from one other source (see [microorganisms]).
|
||||
#'
|
||||
#' The \code{as.mo()} function uses several coercion rules for fast and logical results. It assesses the input matching criteria in the following order:
|
||||
|
||||
#' \itemize{
|
||||
#' \item{Human pathogenic prevalence: the function starts with more prevalent microorganisms, followed by less prevalent ones;}
|
||||
#' \item{Taxonomic kingdom: the function starts with determining Bacteria, then Fungi, then Protozoa, then others;}
|
||||
#' \item{Breakdown of input values to identify possible matches.}
|
||||
#' }
|
||||
#'
|
||||
#' This will lead to the effect that e.g. \code{"E. coli"} (a highly prevalent microorganism found in humans) will return the microbial ID of \emph{Escherichia coli} and not \emph{Entamoeba coli} (a less prevalent microorganism in humans), although the latter would alphabetically come first.
|
||||
#' The [as.mo()] function uses several coercion rules for fast and logical results. It assesses the input matching criteria in the following order:
|
||||
#'
|
||||
#' \strong{Coping with uncertain results} \cr
|
||||
#' In addition, the \code{as.mo()} function can differentiate four levels of uncertainty to guess valid results:
|
||||
#' 1. Human pathogenic prevalence: the function starts with more prevalent microorganisms, followed by less prevalent ones;
|
||||
#' 2. Taxonomic kingdom: the function starts with determining Bacteria, then Fungi, then Protozoa, then others;
|
||||
#' 3. Breakdown of input values to identify possible matches.
|
||||
#'
|
||||
#' This will lead to the effect that e.g. `"E. coli"` (a highly prevalent microorganism found in humans) will return the microbial ID of *Escherichia coli* and not *Entamoeba coli* (a less prevalent microorganism in humans), although the latter would alphabetically come first.
|
||||
#'
|
||||
#' \itemize{
|
||||
#' \item{Uncertainty level 0: no additional rules are applied;}
|
||||
#' \item{Uncertainty level 1: allow previously accepted (but now invalid) taxonomic names and minor spelling errors;}
|
||||
#' \item{Uncertainty level 2: allow all of level 1, strip values between brackets, inverse the words of the input, strip off text elements from the end keeping at least two elements;}
|
||||
#' \item{Uncertainty level 3: allow all of level 1 and 2, strip off text elements from the end, allow any part of a taxonomic name.}
|
||||
#' }
|
||||
#' ## Coping with uncertain results
|
||||
#'
|
||||
#' In addition, the [as.mo()] function can differentiate four levels of uncertainty to guess valid results:
|
||||
#' - Uncertainty level 0: no additional rules are applied;
|
||||
#' - Uncertainty level 1: allow previously accepted (but now invalid) taxonomic names and minor spelling errors;
|
||||
#' - Uncertainty level 2: allow all of level 1, strip values between brackets, inverse the words of the input, strip off text elements from the end keeping at least two elements;
|
||||
#' - Uncertainty level 3: allow all of level 1 and 2, strip off text elements from the end, allow any part of a taxonomic name.
|
||||
#'
|
||||
#' This leads to e.g.:
|
||||
#'
|
||||
#' \itemize{
|
||||
#' \item{\code{"Streptococcus group B (known as S. agalactiae)"}. The text between brackets will be removed and a warning will be thrown that the result \emph{Streptococcus group B} (\code{B_STRPT_GRPB}) needs review.}
|
||||
#' \item{\code{"S. aureus - please mind: MRSA"}. The last word will be stripped, after which the function will try to find a match. If it does not, the second last word will be stripped, etc. Again, a warning will be thrown that the result \emph{Staphylococcus aureus} (\code{B_STPHY_AURS}) needs review.}
|
||||
#' \item{\code{"Fluoroquinolone-resistant Neisseria gonorrhoeae"}. The first word will be stripped, after which the function will try to find a match. A warning will be thrown that the result \emph{Neisseria gonorrhoeae} (\code{B_NESSR_GNRR}) needs review.}
|
||||
#' }
|
||||
#' - `"Streptococcus group B (known as S. agalactiae)"`. The text between brackets will be removed and a warning will be thrown that the result *Streptococcus group B* (`B_STRPT_GRPB`) needs review.
|
||||
#' - `"S. aureus - please mind: MRSA"`. The last word will be stripped, after which the function will try to find a match. If it does not, the second last word will be stripped, etc. Again, a warning will be thrown that the result *Staphylococcus aureus* (`B_STPHY_AURS`) needs review.
|
||||
#' - `"Fluoroquinolone-resistant Neisseria gonorrhoeae"`. The first word will be stripped, after which the function will try to find a match. A warning will be thrown that the result *Neisseria gonorrhoeae* (`B_NESSR_GNRR`) needs review.
|
||||
#'
|
||||
#' The level of uncertainty can be set using the argument \code{allow_uncertain}. The default is \code{allow_uncertain = TRUE}, which is equal to uncertainty level 2. Using \code{allow_uncertain = FALSE} is equal to uncertainty level 0 and will skip all rules. You can also use e.g. \code{as.mo(..., allow_uncertain = 1)} to only allow up to level 1 uncertainty.
|
||||
#' The level of uncertainty can be set using the argument `allow_uncertain`. The default is `allow_uncertain = TRUE`, which is equal to uncertainty level 2. Using `allow_uncertain = FALSE` is equal to uncertainty level 0 and will skip all rules. You can also use e.g. `as.mo(..., allow_uncertain = 1)` to only allow up to level 1 uncertainty.
|
||||
#'
|
||||
#' There are three helper functions that can be run after then \code{as.mo()} function:
|
||||
#' \itemize{
|
||||
#' \item{Use \code{mo_uncertainties()} to get a \code{data.frame} with all values that were coerced to a valid value, but with uncertainty. The output contains a score, that is calculated as \code{(n - 0.5 * L) / n}, where \emph{n} is the number of characters of the returned full name of the microorganism, and \emph{L} is the \href{https://en.wikipedia.org/wiki/Levenshtein_distance}{Levenshtein distance} between that full name and the user input.}
|
||||
#' \item{Use \code{mo_failures()} to get a vector with all values that could not be coerced to a valid value.}
|
||||
#' \item{Use \code{mo_renamed()} to get a \code{data.frame} with all values that could be coerced based on an old, previously accepted taxonomic name.}
|
||||
#' }
|
||||
#' There are three helper functions that can be run after then [as.mo()] function:
|
||||
#' - Use [mo_uncertainties()] to get a [`data.frame`] with all values that were coerced to a valid value, but with uncertainty. The output contains a score, that is calculated as \eqn{(n - 0.5 * L) / n}, where *n* is the number of characters of the returned full name of the microorganism, and *L* is the [Levenshtein distance](https://en.wikipedia.org/wiki/Levenshtein_distance) between that full name and the user input.
|
||||
#' - Use [mo_failures()] to get a [`vector`] with all values that could not be coerced to a valid value.
|
||||
#' - Use [mo_renamed()] to get a [`data.frame`] with all values that could be coerced based on an old, previously accepted taxonomic name.
|
||||
#'
|
||||
#' \strong{Microbial prevalence of pathogens in humans} \cr
|
||||
#' The intelligent rules consider the prevalence of microorganisms in humans grouped into three groups, which is available as the \code{prevalence} columns in the \code{\link{microorganisms}} and \code{\link{microorganisms.old}} data sets. The grouping into prevalence groups is based on experience from several microbiological laboratories in the Netherlands in conjunction with international reports on pathogen prevalence.
|
||||
#' ## Microbial prevalence of pathogens in humans
|
||||
#'
|
||||
#' Group 1 (most prevalent microorganisms) consists of all microorganisms where the taxonomic class is Gammaproteobacteria or where the taxonomic genus is \emph{Enterococcus}, \emph{Staphylococcus} or \emph{Streptococcus}. This group consequently contains all common Gram-negative bacteria, such as \emph{Pseudomonas} and \emph{Legionella} and all species within the order Enterobacteriales.
|
||||
#' The intelligent rules consider the prevalence of microorganisms in humans grouped into three groups, which is available as the `prevalence` columns in the [microorganisms] and [microorganisms.old] data sets. The grouping into prevalence groups is based on experience from several microbiological laboratories in the Netherlands in conjunction with international reports on pathogen prevalence.
|
||||
#'
|
||||
#' Group 2 consists of all microorganisms where the taxonomic phylum is Proteobacteria, Firmicutes, Actinobacteria or Sarcomastigophora, or where the taxonomic genus is \emph{Aspergillus}, \emph{Bacteroides}, \emph{Candida}, \emph{Capnocytophaga}, \emph{Chryseobacterium}, \emph{Cryptococcus}, \emph{Elisabethkingia}, \emph{Flavobacterium}, \emph{Fusobacterium}, \emph{Giardia}, \emph{Leptotrichia}, \emph{Mycoplasma}, \emph{Prevotella}, \emph{Rhodotorula}, \emph{Treponema}, \emph{Trichophyton} or \emph{Ureaplasma}.
|
||||
#' Group 1 (most prevalent microorganisms) consists of all microorganisms where the taxonomic class is Gammaproteobacteria or where the taxonomic genus is *Enterococcus*, *Staphylococcus* or *Streptococcus*. This group consequently contains all common Gram-negative bacteria, such as *Pseudomonas* and *Legionella* and all species within the order Enterobacteriales.
|
||||
#'
|
||||
#' Group 2 consists of all microorganisms where the taxonomic phylum is Proteobacteria, Firmicutes, Actinobacteria or Sarcomastigophora, or where the taxonomic genus is *Aspergillus*, *Bacteroides*, *Candida*, *Capnocytophaga*, *Chryseobacterium*, *Cryptococcus*, *Elisabethkingia*, *Flavobacterium*, *Fusobacterium*, *Giardia*, *Leptotrichia*, *Mycoplasma*, *Prevotella*, *Rhodotorula*, *Treponema*, *Trichophyton* or *Ureaplasma*.
|
||||
#'
|
||||
#' Group 3 (least prevalent microorganisms) consists of all other microorganisms.
|
||||
#'
|
||||
#' \strong{Self-learning algorithm} \cr
|
||||
#' The \code{as.mo()} function gains experience from previously determined microorganism IDs and learns from it. This drastically improves both speed and reliability. Use \code{clear_mo_history()} to reset the algorithms. Only experience from your current \code{AMR} package version is used. This is done because in the future the taxonomic tree (which is included in this package) may change for any organism and it consequently has to rebuild its knowledge.
|
||||
#' ## Self-learning algorithm
|
||||
#'
|
||||
#' The [as.mo()] function gains experience from previously determined microorganism IDs and learns from it. This drastically improves both speed and reliability. Use [clear_mo_history()] to reset the algorithms. Only experience from your current `AMR` package version is used. This is done because in the future the taxonomic tree (which is included in this package) may change for any organism and it consequently has to rebuild its knowledge.
|
||||
#'
|
||||
#' Usually, any guess after the first try runs 80-95\% faster than the first try.
|
||||
#'
|
||||
# \emph{For now, learning only works per session. If R is closed or terminated, the algorithms reset. This might be resolved in a future version.}
|
||||
#' This resets with every update of this \code{AMR} package since results are saved to your local package library folder.
|
||||
#' Usually, any guess after the first try runs 80-95% faster than the first try.
|
||||
#'
|
||||
#' This resets with every update of this `AMR` package since results are saved to your local package library folder.
|
||||
#' @inheritSection catalogue_of_life Catalogue of Life
|
||||
# (source as a section here, so it can be inherited by other man pages:)
|
||||
#' @section Source:
|
||||
#' [1] Becker K \emph{et al.} \strong{Coagulase-Negative Staphylococci}. 2014. Clin Microbiol Rev. 27(4): 870–926. \url{https://dx.doi.org/10.1128/CMR.00109-13}
|
||||
#'
|
||||
#' [2] Becker K \emph{et al.} \strong{Implications of identifying the recently defined members of the \emph{S. aureus} complex, \emph{S. argenteus} and \emph{S. schweitzeri}: A position paper of members of the ESCMID Study Group for staphylococci and Staphylococcal Diseases (ESGS).} 2019. Clin Microbiol Infect. \url{https://doi.org/10.1016/j.cmi.2019.02.028}
|
||||
#'
|
||||
#' [3] Lancefield RC \strong{A serological differentiation of human and other groups of hemolytic streptococci}. 1933. J Exp Med. 57(4): 571–95. \url{https://dx.doi.org/10.1084/jem.57.4.571}
|
||||
#'
|
||||
#' [4] Catalogue of Life: Annual Checklist (public online taxonomic database), \url{http://www.catalogueoflife.org} (check included annual version with \code{\link{catalogue_of_life_version}()}).
|
||||
#' 1. Becker K *et al.* **Coagulase-Negative Staphylococci**. 2014. Clin Microbiol Rev. 27(4): 870–926. <https://dx.doi.org/10.1128/CMR.00109-13>
|
||||
#' 2. Becker K *et al.* **Implications of identifying the recently defined members of the *S. aureus* complex, *S. argenteus* and *S. schweitzeri*: A position paper of members of the ESCMID Study Group for staphylococci and Staphylococcal Diseases (ESGS).** 2019. Clin Microbiol Infect. <https://doi.org/10.1016/j.cmi.2019.02.028>
|
||||
#' 3. Lancefield RC **A serological differentiation of human and other groups of hemolytic streptococci**. 1933. J Exp Med. 57(4): 571–95. <https://dx.doi.org/10.1084/jem.57.4.571>
|
||||
#' 4. Catalogue of Life: Annual Checklist (public online taxonomic database), <http://www.catalogueoflife.org> (check included annual version with [catalogue_of_life_version()]).
|
||||
#' @export
|
||||
#' @return Character (vector) with class \code{"mo"}
|
||||
#' @seealso \code{\link{microorganisms}} for the \code{data.frame} that is being used to determine ID's. \cr
|
||||
#' The \code{\link{mo_property}} functions (like \code{\link{mo_genus}}, \code{\link{mo_gramstain}}) to get properties based on the returned code.
|
||||
#' @return A [`character`] vector with class [`mo`]
|
||||
#' @seealso [microorganisms] for the [`data.frame`] that is being used to determine ID's.
|
||||
#'
|
||||
#' The [mo_property()] functions (like [mo_genus()], [mo_gramstain()]) to get properties based on the returned code.
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @importFrom dplyr %>% pull left_join
|
||||
#' @examples
|
||||
|
@ -48,19 +48,6 @@ set_mo_history <- function(x, mo, uncertainty_level, force = FALSE, disable = FA
|
||||
if (NROW(mo_hist[base::which(mo_hist$x == x[i] &
|
||||
mo_hist$uncertainty_level >= uncertainty_level &
|
||||
mo_hist$package_version == utils::packageVersion("AMR")), ]) == 0) {
|
||||
# # Not using the file system:
|
||||
# tryCatch(options(mo_remembered_results = rbind(mo_hist,
|
||||
# data.frame(
|
||||
# x = x[i],
|
||||
# mo = mo[i],
|
||||
# uncertainty_level = uncertainty_level,
|
||||
# package_version = base::as.character(utils::packageVersion("AMR")),
|
||||
# stringsAsFactors = FALSE))),
|
||||
# error = function(e) base::invisible())
|
||||
# # don't remember more than 1,000 different input values
|
||||
# if (tryCatch(nrow(getOption("mo_remembered_results")), error = function(e) 1001) > 1000) {
|
||||
# return(base::invisible())
|
||||
# }
|
||||
if (is.null(mo_hist) & interactive()) {
|
||||
warning_new_write <- TRUE
|
||||
}
|
||||
@ -113,9 +100,6 @@ read_mo_history <- function(uncertainty_level = 2, force = FALSE, unfiltered = F
|
||||
}
|
||||
uncertainty_level_param <- uncertainty_level
|
||||
|
||||
# # Not using the file system:
|
||||
# history <- tryCatch(getOption("mo_remembered_results"),
|
||||
# error = function(e) NULL)
|
||||
history <- tryCatch(read.csv(mo_history_file(), stringsAsFactors = FALSE),
|
||||
warning = function(w) invisible(),
|
||||
error = function(e) NULL)
|
||||
@ -159,9 +143,7 @@ clear_mo_history <- function(...) {
|
||||
return(invisible())
|
||||
}
|
||||
}
|
||||
# # Not using the file system:
|
||||
# success <- tryCatch(options(mo_remembered_results = NULL),
|
||||
# error = function(e) FALSE)
|
||||
|
||||
success <- create_blank_mo_history()
|
||||
if (!isFALSE(success)) {
|
||||
cat(red(paste("File", mo_history_file(), "cleared.")))
|
||||
|
@ -21,36 +21,33 @@
|
||||
|
||||
#' Property of a microorganism
|
||||
#'
|
||||
#' Use these functions to return a specific property of a microorganism. All input values will be evaluated internally with \code{\link{as.mo}}, which makes it possible for input of these functions to use microbial abbreviations, codes and names. See Examples.
|
||||
#' @param x any (vector of) text that can be coerced to a valid microorganism code with \code{\link{as.mo}}
|
||||
#' @param property one of the column names of the \code{\link{microorganisms}} data set or \code{"shortname"}
|
||||
#' @param language language of the returned text, defaults to system language (see \code{\link{get_locale}}) and can also be set with \code{\link{getOption}("AMR_locale")}. Use \code{language = NULL} or \code{language = ""} to prevent translation.
|
||||
#' @param ... other parameters passed on to \code{\link{as.mo}}
|
||||
#' @param open browse the URL using \code{\link[utils]{browseURL}()}
|
||||
#' @details All functions will return the most recently known taxonomic property according to the Catalogue of Life, except for \code{mo_ref}, \code{mo_authors} and \code{mo_year}. This leads to the following results:
|
||||
#' \itemize{
|
||||
#' \item{\code{mo_name("Chlamydia psittaci")} will return \code{"Chlamydophila psittaci"} (with a warning about the renaming)}
|
||||
#' \item{\code{mo_ref("Chlamydia psittaci")} will return \code{"Page, 1968"} (with a warning about the renaming)}
|
||||
#' \item{\code{mo_ref("Chlamydophila psittaci")} will return \code{"Everett et al., 1999"} (without a warning)}
|
||||
#' }
|
||||
#' Use these functions to return a specific property of a microorganism. All input values will be evaluated internally with [as.mo()], which makes it possible for input of these functions to use microbial abbreviations, codes and names. See Examples.
|
||||
#' @param x any (vector of) text that can be coerced to a valid microorganism code with [as.mo()]
|
||||
#' @param property one of the column names of the [microorganisms] data set or `"shortname"`
|
||||
#' @param language language of the returned text, defaults to system language (see [get_locale()]) and can also be set with `getOption("AMR_locale")`. Use `language = NULL` or `language = ""` to prevent translation.
|
||||
#' @param ... other parameters passed on to [as.mo()]
|
||||
#' @param open browse the URL using [utils::browseURL()]
|
||||
#' @details All functions will return the most recently known taxonomic property according to the Catalogue of Life, except for [mo_ref()], [mo_authors()] and [mo_year()]. This leads to the following results:
|
||||
#' - `mo_name("Chlamydia psittaci")` will return `"Chlamydophila psittaci"` (with a warning about the renaming)
|
||||
#' - `mo_ref("Chlamydia psittaci")` will return `"Page, 1968"` (with a warning about the renaming)
|
||||
#' - `mo_ref("Chlamydophila psittaci")` will return `"Everett et al., 1999"` (without a warning)
|
||||
#'
|
||||
#' The Gram stain - \code{mo_gramstain()} - will be determined on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002) who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram positive - all other bacteria are considered Gram negative. Species outside the kingdom of Bacteria will return a value \code{NA}.
|
||||
#' The Gram stain - [mo_gramstain()] - will be determined on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002) who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram positive - all other bacteria are considered Gram negative. Species outside the kingdom of Bacteria will return a value `NA`.
|
||||
#'
|
||||
#' All output will be \link{translate}d where possible.
|
||||
#' All output will be [translate]d where possible.
|
||||
#'
|
||||
#' The function \code{mo_url()} will return the direct URL to the online database entry, which also shows the scientific reference of the concerned species.
|
||||
#' The function [mo_url()] will return the direct URL to the online database entry, which also shows the scientific reference of the concerned species.
|
||||
#' @inheritSection catalogue_of_life Catalogue of Life
|
||||
#' @inheritSection as.mo Source
|
||||
#' @rdname mo_property
|
||||
#' @name mo_property
|
||||
#' @return \itemize{
|
||||
#' \item{An \code{integer} in case of \code{mo_year}}
|
||||
#' \item{A \code{list} in case of \code{mo_taxonomy}}
|
||||
#' \item{A named \code{character} in case of \code{mo_url}}
|
||||
#' \item{A \code{character} in all other cases}
|
||||
#' }
|
||||
#' @return
|
||||
#' - An [`integer`] in case of [mo_year()]
|
||||
#' - A [`list`] in case of [mo_taxonomy()]
|
||||
#' - A named [`character`] in case of [mo_url()]
|
||||
#' - A [`character`] in all other cases
|
||||
#' @export
|
||||
#' @seealso \code{\link{microorganisms}}
|
||||
#' @seealso [microorganisms]
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @examples
|
||||
#' # taxonomic tree -----------------------------------------------------------
|
||||
@ -132,7 +129,7 @@
|
||||
#'
|
||||
#' # get a list with the complete taxonomy (from kingdom to subspecies)
|
||||
#' mo_taxonomy("E. coli")
|
||||
#' # get a list with the taxonomy, the authors and the URL to the online database
|
||||
#' # get a list with the taxonomy, the authors, Gram-stain and URL to the online database
|
||||
#' mo_info("E. coli")
|
||||
#' }
|
||||
mo_name <- function(x, language = get_locale(), ...) {
|
||||
@ -336,6 +333,7 @@ mo_info <- function(x, language = get_locale(), ...) {
|
||||
info <- lapply(x, function(y)
|
||||
c(mo_taxonomy(y, language = language),
|
||||
list(synonyms = mo_synonyms(y),
|
||||
gramstain = mo_gramstain(y, language = language),
|
||||
url = unname(mo_url(y, open = FALSE)),
|
||||
ref = mo_ref(y))))
|
||||
if (length(info) > 1) {
|
||||
|
@ -21,79 +21,81 @@
|
||||
|
||||
#' Use predefined reference data set
|
||||
#'
|
||||
#' @description These functions can be used to predefine your own reference to be used in \code{\link{as.mo}} and consequently all \code{mo_*} functions like \code{\link{mo_genus}} and \code{\link{mo_gramstain}}.
|
||||
#' @description These functions can be used to predefine your own reference to be used in [as.mo()] and consequently all `mo_*` functions like [mo_genus()] and [mo_gramstain()].
|
||||
#'
|
||||
#' This is \strong{the fastest way} to have your organisation (or analysis) specific codes picked up and translated by this package.
|
||||
#' This is **the fastest way** to have your organisation (or analysis) specific codes picked up and translated by this package.
|
||||
#' @param path location of your reference file, see Details
|
||||
#' @rdname mo_source
|
||||
#' @name mo_source
|
||||
#' @aliases set_mo_source get_mo_source
|
||||
#' @details The reference file can be a text file seperated with commas (CSV) or tabs or pipes, an Excel file (either 'xls' or 'xlsx' format) or an R object file (extension '.rds'). To use an Excel file, you need to have the \code{readxl} package installed.
|
||||
#' @details The reference file can be a text file seperated with commas (CSV) or tabs or pipes, an Excel file (either 'xls' or 'xlsx' format) or an R object file (extension '.rds'). To use an Excel file, you need to have the `readxl` package installed.
|
||||
#'
|
||||
#' \code{set_mo_source} will check the file for validity: it must be a \code{data.frame}, must have a column named \code{"mo"} which contains values from \code{microorganisms$mo} and must have a reference column with your own defined values. If all tests pass, \code{set_mo_source} will read the file into R and export it to \code{"~/.mo_source.rds"}. This compressed data file will then be used at default for MO determination (function \code{\link{as.mo}} and consequently all \code{mo_*} functions like \code{\link{mo_genus}} and \code{\link{mo_gramstain}}). The location of the original file will be saved as option with \code{\link{options}(mo_source = path)}. Its timestamp will be saved with \code{\link{options}(mo_source_datetime = ...)}.
|
||||
#' [set_mo_source()] will check the file for validity: it must be a [`data.frame`], must have a column named `"mo"` which contains values from [`microorganisms$mo`][microorganisms] and must have a reference column with your own defined values. If all tests pass, [set_mo_source()] will read the file into R and export it to `"~/.mo_source.rds"`. This compressed data file will then be used at default for MO determination (function [as.mo()] and consequently all `mo_*` functions like [mo_genus()] and [mo_gramstain()]). The location of the original file will be saved as option with `options(mo_source = path)`. Its timestamp will be saved with `options(mo_source_datetime = ...)`.
|
||||
#'
|
||||
#' \code{get_mo_source} will return the data set by reading \code{"~/.mo_source.rds"} with \code{\link{readRDS}}. If the original file has changed (the file defined with \code{path}), it will call \code{set_mo_source} to update the data file automatically.
|
||||
#' [get_mo_source()] will return the data set by reading `"~/.mo_source.rds"` with [readRDS()]. If the original file has changed (the file defined with `path`), it will call [set_mo_source()] to update the data file automatically.
|
||||
#'
|
||||
#' Reading an Excel file (\code{.xlsx}) with only one row has a size of 8-9 kB. The compressed file used by this package will have a size of 0.1 kB and can be read by \code{get_mo_source} in only a couple of microseconds (a millionth of a second).
|
||||
#' @section How it works:
|
||||
#' Reading an Excel file (`.xlsx`) with only one row has a size of 8-9 kB. The compressed file used by this package will have a size of 0.1 kB and can be read by [get_mo_source()] in only a couple of microseconds (a millionth of a second).
|
||||
#'
|
||||
#' ## How it works
|
||||
#'
|
||||
#' Imagine this data on a sheet of an Excel file (mo codes were looked up in the `microorganisms` data set). The first column contains the organisation specific codes, the second column contains an MO code from this package:
|
||||
#' \preformatted{
|
||||
#' ```
|
||||
#' | A | B |
|
||||
#' --|--------------------|-------------|
|
||||
#' 1 | Organisation XYZ | mo |
|
||||
#' 2 | lab_mo_ecoli | B_ESCHR_COL |
|
||||
#' 3 | lab_mo_kpneumoniae | B_KLBSL_PNE |
|
||||
#' 4 | | |
|
||||
#' }
|
||||
#' ```
|
||||
#'
|
||||
#' We save it as \code{'home/me/ourcodes.xlsx'}. Now we have to set it as a source:
|
||||
#' \preformatted{
|
||||
#' We save it as `"home/me/ourcodes.xlsx"`. Now we have to set it as a source:
|
||||
#' ```
|
||||
#' set_mo_source("home/me/ourcodes.xlsx")
|
||||
#' # Created mo_source file '~/.mo_source.rds' from 'home/me/ourcodes.xlsx'.
|
||||
#' }
|
||||
#' ```
|
||||
#'
|
||||
#' It has now created a file "~/.mo_source.rds" with the contents of our Excel file, but only the first column with foreign values and the 'mo' column will be kept.
|
||||
#' It has now created a file `"~/.mo_source.rds"` with the contents of our Excel file, but only the first column with foreign values and the 'mo' column will be kept.
|
||||
#'
|
||||
#' And now we can use it in our functions:
|
||||
#' \preformatted{
|
||||
#' ```
|
||||
#' as.mo("lab_mo_ecoli")
|
||||
#' [1] B_ESCHR_COL
|
||||
#' \[1\] B_ESCHR_COLI
|
||||
#'
|
||||
#' mo_genus("lab_mo_kpneumoniae")
|
||||
#' [1] "Klebsiella"
|
||||
#'
|
||||
#' # other input values still work too
|
||||
#' as.mo(c("Escherichia coli", "E. coli", "lab_mo_ecoli"))
|
||||
#' [1] B_ESCHR_COL B_ESCHR_COL B_ESCHR_COL
|
||||
#' }
|
||||
#' [1] B_ESCHR_COLI B_ESCHR_COLI B_ESCHR_COLI
|
||||
#' ```
|
||||
#'
|
||||
#' If we edit the Excel file to, let's say, this:
|
||||
#' \preformatted{
|
||||
#' | A | B |
|
||||
#' --|--------------------|-------------|
|
||||
#' 1 | Organisation XYZ | mo |
|
||||
#' 2 | lab_mo_ecoli | B_ESCHR_COL |
|
||||
#' 3 | lab_mo_kpneumoniae | B_KLBSL_PNE |
|
||||
#' 4 | lab_Staph_aureus | B_STPHY_AUR |
|
||||
#' 5 | | |
|
||||
#' }
|
||||
#' ```
|
||||
#' | A | B |
|
||||
#' --|--------------------|--------------|
|
||||
#' 1 | Organisation XYZ | mo |
|
||||
#' 2 | lab_mo_ecoli | B_ESCHR_COLI |
|
||||
#' 3 | lab_mo_kpneumoniae | B_KLBSL_PNMN |
|
||||
#' 4 | lab_Staph_aureus | B_STPHY_AURS |
|
||||
#' 5 | | |
|
||||
#' ```
|
||||
#'
|
||||
#' ...any new usage of an MO function in this package will update your data:
|
||||
#' \preformatted{
|
||||
#' ```
|
||||
#' as.mo("lab_mo_ecoli")
|
||||
#' # Updated mo_source file '~/.mo_source.rds' from 'home/me/ourcodes.xlsx'.
|
||||
#' [1] B_ESCHR_COL
|
||||
#' [1] B_ESCHR_COLI
|
||||
#'
|
||||
#' mo_genus("lab_Staph_aureus")
|
||||
#' [1] "Staphylococcus"
|
||||
#' }
|
||||
#' ```
|
||||
#'
|
||||
#' To remove the reference completely, just use any of these:
|
||||
#' \preformatted{
|
||||
#' ```
|
||||
#' set_mo_source("")
|
||||
#' set_mo_source(NULL)
|
||||
#' # Removed mo_source file '~/.mo_source.rds'.
|
||||
#' }
|
||||
#' ```
|
||||
#' @importFrom dplyr select everything
|
||||
#' @export
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
|
@ -19,11 +19,11 @@
|
||||
# Visit our website for more info: https://msberends.gitlab.io/AMR. #
|
||||
# ==================================================================== #
|
||||
|
||||
#' Symbol of a p value
|
||||
#' Symbol of a p-value
|
||||
#'
|
||||
#' Return the symbol related to the p value: 0 '***' 0.001 '**' 0.01 '*' 0.05 '.' 0.1 ' ' 1. Values above \code{p = 1} will return \code{NA}.
|
||||
#' Return the symbol related to the p-value: 0 '`***`' 0.001 '`**`' 0.01 '`*`' 0.05 '`.`' 0.1 ' ' 1. Values above `p = 1` will return `NA`.
|
||||
#' @param p p value
|
||||
#' @param emptychar text to show when \code{p > 0.1}
|
||||
#' @param emptychar text to show when `p > 0.1`
|
||||
#' @return Text
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @export
|
||||
|
@ -21,31 +21,31 @@
|
||||
|
||||
#' Calculate microbial resistance
|
||||
#'
|
||||
#' @description These functions can be used to calculate the (co-)resistance or susceptibility of microbial isolates (i.e. percentage of S, SI, I, IR or R). All functions support quasiquotation with pipes, can be used in \code{dplyr}s \code{\link[dplyr]{summarise}} and support grouped variables, see \emph{Examples}.
|
||||
#' @description These functions can be used to calculate the (co-)resistance or susceptibility of microbial isolates (i.e. percentage of S, SI, I, IR or R). All functions support quasiquotation with pipes, can be used in [dplyr::summarise()] and support grouped variables, please see *Examples*.
|
||||
#'
|
||||
#' \code{resistance()} should be used to calculate resistance, \code{susceptibility()} should be used to calculate susceptibility.\cr
|
||||
#' @param ... one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with \code{\link{as.rsi}} if needed. Use multiple columns to calculate (the lack of) co-resistance: the probability where one of two drugs have a resistant or susceptible result. See Examples.
|
||||
#' @param minimum the minimum allowed number of available (tested) isolates. Any isolate count lower than \code{minimum} will return \code{NA} with a warning. The default number of \code{30} isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source.
|
||||
#' @param as_percent a logical to indicate whether the output must be returned as a hundred fold with \% sign (a character). A value of \code{0.123456} will then be returned as \code{"12.3\%"}.
|
||||
#' @param only_all_tested (for combination therapies, i.e. using more than one variable for \code{...}) a logical to indicate that isolates must be tested for all antibiotics, see section \emph{Combination therapy} below
|
||||
#' @param data a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}})
|
||||
#' @param translate_ab a column name of the \code{\link{antibiotics}} data set to translate the antibiotic abbreviations to, using \code{\link{ab_property}}
|
||||
#' [resistance()] should be used to calculate resistance, [susceptibility()] should be used to calculate susceptibility.\cr
|
||||
#' @param ... one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with [as.rsi()] if needed. Use multiple columns to calculate (the lack of) co-resistance: the probability where one of two drugs have a resistant or susceptible result. See Examples.
|
||||
#' @param minimum the minimum allowed number of available (tested) isolates. Any isolate count lower than `minimum` will return `NA` with a warning. The default number of `30` isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source.
|
||||
#' @param as_percent a logical to indicate whether the output must be returned as a hundred fold with % sign (a character). A value of `0.123456` will then be returned as `"12.3%"`.
|
||||
#' @param only_all_tested (for combination therapies, i.e. using more than one variable for `...`): a logical to indicate that isolates must be tested for all antibiotics, see section *Combination therapy* below
|
||||
#' @param data a [`data.frame`] containing columns with class [`rsi`] (see [as.rsi()])
|
||||
#' @param translate_ab a column name of the [antibiotics] data set to translate the antibiotic abbreviations to, using [ab_property()]
|
||||
#' @inheritParams ab_property
|
||||
#' @param combine_SI a logical to indicate whether all values of S and I must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter \code{combine_IR}, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see section 'Interpretation of S, I and R' below. Default is \code{TRUE}.
|
||||
#' @param combine_IR a logical to indicate whether all values of I and R must be merged into one, so the output only consists of S vs. I+R (susceptible vs. non-susceptible). This is outdated, see parameter \code{combine_SI}.
|
||||
#' @param combine_SI a logical to indicate whether all values of S and I must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter `combine_IR`, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see section 'Interpretation of S, I and R' below. Default is `TRUE`.
|
||||
#' @param combine_IR a logical to indicate whether all values of I and R must be merged into one, so the output only consists of S vs. I+R (susceptible vs. non-susceptible). This is outdated, see parameter `combine_SI`.
|
||||
#' @inheritSection as.rsi Interpretation of S, I and R
|
||||
#' @details
|
||||
#' The function \code{resistance()} is equal to the function \code{proportion_R()}. The function \code{susceptibility()} is equal to the function \code{proportion_SI()}.
|
||||
#' The function [resistance()] is equal to the function [proportion_R()]. The function [susceptibility()] is equal to the function [proportion_SI()].
|
||||
#'
|
||||
#' \strong{Remember that you should filter your table to let it contain only first isolates!} This is needed to exclude duplicates and to reduce selection bias. Use \code{\link{first_isolate}} to determine them in your data set.
|
||||
#' **Remember that you should filter your table to let it contain only first isolates!** This is needed to exclude duplicates and to reduce selection bias. Use [first_isolate()] to determine them in your data set.
|
||||
#'
|
||||
#' These functions are not meant to count isolates, but to calculate the proportion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. The function \code{susceptibility()} is essentially equal to \code{count_susceptible() / count_all()}. \emph{Low counts can infuence the outcome - the \code{proportion} functions may camouflage this, since they only return the proportion (albeit being dependent on the \code{minimum} parameter).}
|
||||
#' These functions are not meant to count isolates, but to calculate the proportion of resistance/susceptibility. Use the [AMR::count()] functions to count isolates. The function [susceptibility()] is essentially equal to `count_susceptible() / count_all()`. *Low counts can infuence the outcome - the `proportion` functions may camouflage this, since they only return the proportion (albeit being dependent on the `minimum` parameter).*
|
||||
#'
|
||||
#' The function \code{proportion_df()} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}()}) and calculates the proportions R, I and S. The function \code{rsi_df()} works exactly like \code{proportion_df()}, but adds the number of isolates.
|
||||
#' The function [proportion_df()] takes any variable from `data` that has an [`rsi`] class (created with [as.rsi()]) and calculates the proportions R, I and S. The function [rsi_df()] works exactly like [proportion_df()], but adds the number of isolates.
|
||||
#' @section Combination therapy:
|
||||
#' When using more than one variable for \code{...} (= combination therapy)), use \code{only_all_tested} to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antibiotics, Antibiotic A and Antibiotic B, about how \code{susceptibility} works to calculate the \%SI:
|
||||
#' When using more than one variable for `...` (= combination therapy)), use `only_all_tested` to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antibiotics, Antibiotic A and Antibiotic B, about how [susceptibility()] works to calculate the %SI:
|
||||
#'
|
||||
#' \preformatted{
|
||||
#' ```
|
||||
#' --------------------------------------------------------------------
|
||||
#' only_all_tested = FALSE only_all_tested = TRUE
|
||||
#' ----------------------- -----------------------
|
||||
@ -62,23 +62,23 @@
|
||||
#' R <NA> - - - -
|
||||
#' <NA> <NA> - - - -
|
||||
#' --------------------------------------------------------------------
|
||||
#' }
|
||||
#' ```
|
||||
#'
|
||||
#' Please note that, in combination therapies, for \code{only_all_tested = TRUE} applies that:
|
||||
#' \preformatted{
|
||||
#' Please note that, in combination therapies, for `only_all_tested = TRUE` applies that:
|
||||
#' ```
|
||||
#' count_S() + count_I() + count_R() = count_all()
|
||||
#' proportion_S() + proportion_I() + proportion_R() = 1
|
||||
#' }
|
||||
#' and that, in combination therapies, for \code{only_all_tested = FALSE} applies that:
|
||||
#' \preformatted{
|
||||
#' ```
|
||||
#' and that, in combination therapies, for `only_all_tested = FALSE` applies that:
|
||||
#' ```
|
||||
#' count_S() + count_I() + count_R() >= count_all()
|
||||
#' proportion_S() + proportion_I() + proportion_R() >= 1
|
||||
#' }
|
||||
#' ```
|
||||
#'
|
||||
#' Using \code{only_all_tested} has no impact when only using one antibiotic as input.
|
||||
#' @source \strong{M39 Analysis and Presentation of Cumulative Antimicrobial Susceptibility Test Data, 4th Edition}, 2014, \emph{Clinical and Laboratory Standards Institute (CLSI)}. \url{https://clsi.org/standards/products/microbiology/documents/m39/}.
|
||||
#' @seealso \code{\link[AMR]{count}_*} to count resistant and susceptible isolates.
|
||||
#' @return Double or, when \code{as_percent = TRUE}, a character.
|
||||
#' Using `only_all_tested` has no impact when only using one antibiotic as input.
|
||||
#' @source **M39 Analysis and Presentation of Cumulative Antimicrobial Susceptibility Test Data, 4th Edition**, 2014, *Clinical and Laboratory Standards Institute (CLSI)*. <https://clsi.org/standards/products/microbiology/documents/m39/>.
|
||||
#' @seealso [AMR::count()] to count resistant and susceptible isolates.
|
||||
#' @return A [`double`] or, when `as_percent = TRUE`, a [`character`].
|
||||
#' @rdname proportion
|
||||
#' @aliases portion
|
||||
#' @name proportion
|
||||
|
@ -18,12 +18,12 @@
|
||||
# ANY WARRANTY OR LIABILITY. #
|
||||
# Visit our website for more info: https://msberends.gitlab.io/AMR. #
|
||||
# ==================================================================== #
|
||||
|
||||
#
|
||||
#' Read data from 4D database
|
||||
#'
|
||||
#' This function is only useful for the MMB department of the UMCG. Use this function to \strong{import data by just defining the \code{file} parameter}. It will automatically transform birth dates and calculate patients age, translate the column names to English, transform the MO codes with \code{\link{as.mo}} and transform all antimicrobial columns with \code{\link{as.rsi}}.
|
||||
#' This function is only useful for the MMB department of the UMCG. Use this function to **import data by just defining the `file` parameter**. It will automatically transform birth dates and calculate patients age, translate the column names to English, transform the MO codes with [as.mo()] and transform all antimicrobial columns with [as.rsi()].
|
||||
#' @inheritParams utils::read.table
|
||||
#' @param info a logical to indicate whether info about the import should be printed, defaults to \code{TRUE} in interactive sessions
|
||||
#' @param info a logical to indicate whether info about the import should be printed, defaults to `TRUE` in interactive sessions
|
||||
#' @details Column names will be transformed, but the original column names are set as a "label" attribute and can be seen in e.g. RStudio Viewer.
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @export
|
||||
@ -84,7 +84,7 @@ read.4D <- function(file,
|
||||
|
||||
colnames(data_4D) <- tolower(colnames(data_4D))
|
||||
if (all(c("afnamedat", "gebdatum") %in% colnames(data_4D))) {
|
||||
# add age
|
||||
# add age column
|
||||
data_4D$age <- NA_integer_
|
||||
}
|
||||
cols_wanted <- c("patientnr", "gebdatum", "age", "mv", "monsternr", "afnamedat", "bepaling",
|
||||
|
@ -21,41 +21,40 @@
|
||||
|
||||
#' Predict antimicrobial resistance
|
||||
#'
|
||||
#' Create a prediction model to predict antimicrobial resistance for the next years on statistical solid ground. Standard errors (SE) will be returned as columns \code{se_min} and \code{se_max}. See Examples for a real live example.
|
||||
#' @param col_ab column name of \code{x} with antimicrobial interpretations (\code{R}, \code{I} and \code{S})
|
||||
#' Create a prediction model to predict antimicrobial resistance for the next years on statistical solid ground. Standard errors (SE) will be returned as columns `se_min` and `se_max`. See *Examples* for a real live example.
|
||||
#' @param col_ab column name of `x` containing antimicrobial interpretations (`"R"`, `"I"` and `"S"`)
|
||||
#' @param col_date column name of the date, will be used to calculate years if this column doesn't consist of years already, defaults to the first column of with a date class
|
||||
#' @param year_min lowest year to use in the prediction model, dafaults to the lowest year in \code{col_date}
|
||||
#' @param year_min lowest year to use in the prediction model, dafaults to the lowest year in `col_date`
|
||||
#' @param year_max highest year to use in the prediction model, defaults to 10 years after today
|
||||
#' @param year_every unit of sequence between lowest year found in the data and \code{year_max}
|
||||
#' @param year_every unit of sequence between lowest year found in the data and `year_max`
|
||||
#' @param minimum minimal amount of available isolates per year to include. Years containing less observations will be estimated by the model.
|
||||
#' @param model the statistical model of choice. This could be a generalised linear regression model with binomial distribution (i.e. using \code{\link{glm}(..., family = \link{binomial})}), assuming that a period of zero resistance was followed by a period of increasing resistance leading slowly to more and more resistance. See Details for all valid options.
|
||||
#' @param I_as_S a logical to indicate whether values \code{I} should be treated as \code{S} (will otherwise be treated as \code{R}). The default, \code{TRUE}, follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see section 'Interpretation of S, I and R' below.
|
||||
#' @param preserve_measurements a logical to indicate whether predictions of years that are actually available in the data should be overwritten by the original data. The standard errors of those years will be \code{NA}.
|
||||
#' @param info a logical to indicate whether textual analysis should be printed with the name and \code{\link{summary}} of the statistical model.
|
||||
#' @param model the statistical model of choice. This could be a generalised linear regression model with binomial distribution (i.e. using `glm(..., family = binomial)``, assuming that a period of zero resistance was followed by a period of increasing resistance leading slowly to more and more resistance. See Details for all valid options.
|
||||
#' @param I_as_S a logical to indicate whether values `I` should be treated as `S` (will otherwise be treated as `R`). The default, `TRUE`, follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see section *Interpretation of S, I and R* below.
|
||||
#' @param preserve_measurements a logical to indicate whether predictions of years that are actually available in the data should be overwritten by the original data. The standard errors of those years will be `NA`.
|
||||
#' @param info a logical to indicate whether textual analysis should be printed with the name and [summary()] of the statistical model.
|
||||
#' @param main title of the plot
|
||||
#' @param ribbon a logical to indicate whether a ribbon should be shown (default) or error bars
|
||||
#' @param ... parameters passed on to functions
|
||||
#' @inheritSection as.rsi Interpretation of S, I and R
|
||||
#' @inheritParams first_isolate
|
||||
#' @inheritParams graphics::plot
|
||||
#' @details Valid options for the statistical model are:
|
||||
#' \itemize{
|
||||
#' \item{\code{"binomial"} or \code{"binom"} or \code{"logit"}: a generalised linear regression model with binomial distribution}
|
||||
#' \item{\code{"loglin"} or \code{"poisson"}: a generalised log-linear regression model with poisson distribution}
|
||||
#' \item{\code{"lin"} or \code{"linear"}: a linear regression model}
|
||||
#' }
|
||||
#' @return \code{data.frame} with extra class \code{"resistance_predict"} with columns:
|
||||
#' \itemize{
|
||||
#' \item{\code{year}}
|
||||
#' \item{\code{value}, the same as \code{estimated} when \code{preserve_measurements = FALSE}, and a combination of \code{observed} and \code{estimated} otherwise}
|
||||
#' \item{\code{se_min}, the lower bound of the standard error with a minimum of \code{0} (so the standard error will never go below 0\%)}
|
||||
#' \item{\code{se_max} the upper bound of the standard error with a maximum of \code{1} (so the standard error will never go above 100\%)}
|
||||
#' \item{\code{observations}, the total number of available observations in that year, i.e. S + I + R}
|
||||
#' \item{\code{observed}, the original observed resistant percentages}
|
||||
#' \item{\code{estimated}, the estimated resistant percentages, calculated by the model}
|
||||
#' }
|
||||
#' Furthermore, the model itself is available as an attribute: \code{attributes(x)$model}, see Examples.
|
||||
#' @seealso The \code{\link{portion}} function to calculate resistance, \cr \code{\link{lm}} \code{\link{glm}}
|
||||
#' @details Valid options for the statistical model (parameter `model`) are:
|
||||
#' - `"binomial"` or `"binom"` or `"logit"`: a generalised linear regression model with binomial distribution
|
||||
#' - `"loglin"` or `"poisson"`: a generalised log-linear regression model with poisson distribution
|
||||
#' - `"lin"` or `"linear"`: a linear regression model
|
||||
#' @return A [`data.frame`] with extra class [`resistance_predict`] with columns:
|
||||
#' - `year`
|
||||
#' - `value`, the same as `estimated` when `preserve_measurements = FALSE`, and a combination of `observed` and `estimated` otherwise
|
||||
#' - `se_min`, the lower bound of the standard error with a minimum of `0` (so the standard error will never go below 0%)
|
||||
#' - `se_max` the upper bound of the standard error with a maximum of `1` (so the standard error will never go above 100%)
|
||||
#' - `observations`, the total number of available observations in that year, i.e. \eqn{S + I + R}
|
||||
#' - `observed`, the original observed resistant percentages
|
||||
#' - `estimated`, the estimated resistant percentages, calculated by the model
|
||||
#'
|
||||
#' Furthermore, the model itself is available as an attribute: `attributes(x)$model`, please see *Examples*.
|
||||
#' @seealso The [proportion()] functions to calculate resistance
|
||||
#'
|
||||
#' Models: [lm()] [glm()]
|
||||
#' @rdname resistance_predict
|
||||
#' @export
|
||||
#' @importFrom stats predict glm lm
|
||||
@ -63,7 +62,10 @@
|
||||
#' @importFrom tidyr pivot_wider
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @examples
|
||||
#' x <- resistance_predict(example_isolates, col_ab = "AMX", year_min = 2010, model = "binomial")
|
||||
#' x <- resistance_predict(example_isolates,
|
||||
#' col_ab = "AMX",
|
||||
#' year_min = 2010,
|
||||
#' model = "binomial")
|
||||
#' plot(x)
|
||||
#' ggplot_rsi_predict(x)
|
||||
#'
|
||||
@ -102,9 +104,9 @@
|
||||
#' scale_y_continuous(limits = c(0, 1),
|
||||
#' breaks = seq(0, 1, 0.1),
|
||||
#' labels = paste0(seq(0, 100, 10), "%")) +
|
||||
#' labs(title = expression(paste("Forecast of amoxicillin resistance in ",
|
||||
#' labs(title = expression(paste("Forecast of Amoxicillin Resistance in ",
|
||||
#' italic("E. coli"))),
|
||||
#' y = "%IR",
|
||||
#' y = "%R",
|
||||
#' x = "Year") +
|
||||
#' theme_minimal(base_size = 13)
|
||||
#' }
|
||||
|
34
R/rsi.R
34
R/rsi.R
@ -21,37 +21,35 @@
|
||||
|
||||
#' Class 'rsi'
|
||||
#'
|
||||
#' Interpret MIC values according to EUCAST or CLSI, or clean up existing RSI values. This transforms the input to a new class \code{rsi}, which is an ordered factor with levels \code{S < I < R}. Invalid antimicrobial interpretations will be translated as \code{NA} with a warning.
|
||||
#' Interpret MIC values and disk diffusion diameters according to EUCAST or CLSI, or clean up existing RSI values. This transforms the input to a new class [`rsi`], which is an ordered factor with levels `S < I < R`. Invalid antimicrobial interpretations will be translated as `NA` with a warning.
|
||||
#' @rdname as.rsi
|
||||
#' @param x vector of values (for class \code{mic}: an MIC value in mg/L, for class \code{disk}: a disk diffusion radius in millimeters)
|
||||
#' @param mo a microorganism code, generated with \code{\link{as.mo}}
|
||||
#' @param ab an antimicrobial code, generated with \code{\link{as.ab}}
|
||||
#' @param x vector of values (for class [`mic`]: an MIC value in mg/L, for class [`disk`]: a disk diffusion radius in millimeters)
|
||||
#' @param mo a microorganism code, generated with [as.mo()]
|
||||
#' @param ab an antimicrobial code, generated with [as.ab()]
|
||||
#' @inheritParams first_isolate
|
||||
#' @param guideline defaults to the latest included EUCAST guideline, run \code{unique(AMR::rsi_translation$guideline)} for all options
|
||||
#' @param threshold maximum fraction of invalid antimicrobial interpretations of \code{x}, see Examples
|
||||
#' @param guideline defaults to the latest included EUCAST guideline, run `unique(AMR::rsi_translation$guideline)` for all options
|
||||
#' @param threshold maximum fraction of invalid antimicrobial interpretations of `x`, please see *Examples*
|
||||
#' @param ... parameters passed on to methods
|
||||
#' @details Run \code{unique(AMR::rsi_translation$guideline)} for a list of all supported guidelines.
|
||||
#' @details Run `unique(AMR::rsi_translation$guideline)` for a list of all supported guidelines.
|
||||
#'
|
||||
#' After using \code{as.rsi}, you can use \code{\link{eucast_rules}} to (1) apply inferred susceptibility and resistance based on results of other antimicrobials and (2) apply intrinsic resistance based on taxonomic properties of a microorganism.
|
||||
#' After using [as.rsi()], you can use [eucast_rules()] to (1) apply inferred susceptibility and resistance based on results of other antimicrobials and (2) apply intrinsic resistance based on taxonomic properties of a microorganism.
|
||||
#'
|
||||
#' The function \code{is.rsi.eligible} returns \code{TRUE} when a columns contains at most 5\% invalid antimicrobial interpretations (not S and/or I and/or R), and \code{FALSE} otherwise. The threshold of 5\% can be set with the \code{threshold} parameter.
|
||||
#' The function [is.rsi.eligible()] returns `TRUE` when a columns contains at most 5% invalid antimicrobial interpretations (not S and/or I and/or R), and `FALSE` otherwise. The threshold of 5% can be set with the `threshold` parameter.
|
||||
#' @section Interpretation of S, I and R:
|
||||
#' In 2019, the European Committee on Antimicrobial Susceptibility Testing (EUCAST) has decided to change the definitions of susceptibility testing categories S, I and R as shown below (\url{http://www.eucast.org/newsiandr/}). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".
|
||||
#' In 2019, the European Committee on Antimicrobial Susceptibility Testing (EUCAST) has decided to change the definitions of susceptibility testing categories S, I and R as shown below (<http://www.eucast.org/newsiandr/>). Results of several consultations on the new definitions are available on the EUCAST website under "Consultations".
|
||||
#'
|
||||
#' \itemize{
|
||||
#' \item{\strong{S} - }{Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.}
|
||||
#' \item{\strong{I} - }{Susceptible, increased exposure: A microorganism is categorised as "Susceptible, Increased exposure" when there is a high likelihood of therapeutic success because exposure to the agent is increased by adjusting the dosing regimen or by its concentration at the site of infection.}
|
||||
#' \item{\strong{R} - }{Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.}
|
||||
#' }
|
||||
#' - **S** - Susceptible, standard dosing regimen: A microorganism is categorised as "Susceptible, standard dosing regimen", when there is a high likelihood of therapeutic success using a standard dosing regimen of the agent.
|
||||
#' - **I** - Susceptible, increased exposure: A microorganism is categorised as "Susceptible, Increased exposure" when there is a high likelihood of therapeutic success because exposure to the agent is increased by adjusting the dosing regimen or by its concentration at the site of infection.
|
||||
#' - **R** - Resistant: A microorganism is categorised as "Resistant" when there is a high likelihood of therapeutic failure even when there is increased exposure.
|
||||
#'
|
||||
#' Exposure is a function of how the mode of administration, dose, dosing interval, infusion time, as well as distribution and excretion of the antimicrobial agent will influence the infecting organism at the site of infection.
|
||||
#'
|
||||
#' This AMR package honours this new insight. Use \code{\link{susceptibility}()} (equal to \code{\link{proportion_SI}()}) to determine antimicrobial susceptibility and \code{\link{count_susceptible}()} (equal to \code{\link{count_SI}()}) to count susceptible isolates.
|
||||
#' @return Ordered factor with new class \code{rsi}
|
||||
#' This AMR package honours this new insight. Use [susceptibility()] (equal to [proportion_SI()]) to determine antimicrobial susceptibility and [count_susceptible()] (equal to [count_SI()]) to count susceptible isolates.
|
||||
#' @return Ordered factor with new class [`rsi`]
|
||||
#' @aliases RSI
|
||||
#' @export
|
||||
#' @importFrom dplyr %>% desc arrange filter
|
||||
#' @seealso \code{\link{as.mic}}
|
||||
#' @seealso [as.mic()]
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @examples
|
||||
#' rsi_data <- as.rsi(c(rep("S", 474), rep("I", 36), rep("R", 370)))
|
||||
|
@ -19,8 +19,7 @@
|
||||
# Visit our website for more info: https://msberends.gitlab.io/AMR. #
|
||||
# ==================================================================== #
|
||||
|
||||
#' @rdname proportion
|
||||
#' @rdname count
|
||||
#' @rdname proportion
|
||||
#' @export
|
||||
rsi_df <- function(data,
|
||||
translate_ab = "name",
|
||||
|
@ -24,10 +24,10 @@
|
||||
#' @description Skewness is a measure of the asymmetry of the probability distribution of a real-valued random variable about its mean.
|
||||
#'
|
||||
#' When negative: the left tail is longer; the mass of the distribution is concentrated on the right of the figure. When positive: the right tail is longer; the mass of the distribution is concentrated on the left of the figure.
|
||||
#' @param x a vector of values, a \code{matrix} or a \code{data frame}
|
||||
#' @param na.rm a logical value indicating whether \code{NA} values should be stripped before the computation proceeds.
|
||||
#' @param x a vector of values, a [`matrix`] or a [`data.frame`]
|
||||
#' @param na.rm a logical value indicating whether `NA` values should be stripped before the computation proceeds.
|
||||
#' @exportMethod skewness
|
||||
#' @seealso \code{\link{kurtosis}}
|
||||
#' @seealso [kurtosis()]
|
||||
#' @rdname skewness
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @export
|
||||
|
BIN
R/sysdata.rda
BIN
R/sysdata.rda
Binary file not shown.
@ -21,16 +21,16 @@
|
||||
|
||||
#' Translate strings from AMR package
|
||||
#'
|
||||
#' For language-dependent output of AMR functions, like \code{\link{mo_name}}, \code{\link{mo_type}} and \code{\link{ab_name}}.
|
||||
#' @details Strings will be translated to foreign languages if they are defined in a local translation file. Additions to this file can be suggested at our repository. The file can be found here: \url{https://gitlab.com/msberends/AMR/blob/master/data-raw/translations.tsv}.
|
||||
#' For language-dependent output of AMR functions, like [mo_name()], [mo_type()] and [ab_name()].
|
||||
#' @details Strings will be translated to foreign languages if they are defined in a local translation file. Additions to this file can be suggested at our repository. The file can be found here: <https://gitlab.com/msberends/AMR/blob/master/data-raw/translations.tsv>.
|
||||
#'
|
||||
#' Currently supported languages can be found if running: \code{unique(AMR:::translations_file$lang)}.
|
||||
#' Currently supported languages can be found if running: `unique(AMR:::translations_file$lang)`.
|
||||
#'
|
||||
#' Please suggest your own translations \href{https://gitlab.com/msberends/AMR/issues/new?issue[title]=Translation\%20suggestion}{by creating a new issue on our repository}.
|
||||
#' Please suggest your own translations [by creating a new issue on our repository](https://gitlab.com/msberends/AMR/issues/new?issue[title]=Translation\%20suggestion).
|
||||
#'
|
||||
#' This file will be read by all functions where a translated output can be desired, like all \code{\link{mo_property}} functions (\code{\link{mo_fullname}}, \code{\link{mo_type}}, etc.).
|
||||
#' This file will be read by all functions where a translated output can be desired, like all [mo_property()] functions ([mo_fullname()], [mo_type()], etc.).
|
||||
#'
|
||||
#' The system language will be used at default, if that language is supported. The system language can be overwritten with \code{\link{getOption}("AMR_locale")}.
|
||||
#' The system language will be used at default, if that language is supported. The system language can be overwritten with `Sys.setenv(AMR_locale = yourlanguage)`.
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @rdname translate
|
||||
#' @name translate
|
||||
|
@ -24,13 +24,13 @@
|
||||
#' All antimicrobial drugs and their official names, ATC codes, ATC groups and defined daily dose (DDD) are included in this package, using the WHO Collaborating Centre for Drug Statistics Methodology.
|
||||
#' @section WHOCC:
|
||||
#' \if{html}{\figure{logo_who.png}{options: height=60px style=margin-bottom:5px} \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{http://ec.europa.eu/health/documents/community-register/html/atc.htm}).
|
||||
#' This package contains **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, <https://www.whocc.no>) and the Pharmaceuticals Community Register of the European Commission (<http://ec.europa.eu/health/documents/community-register/html/atc.htm>).
|
||||
#'
|
||||
#' These have become the gold standard for international drug utilisation monitoring and research.
|
||||
#'
|
||||
#' The WHOCC is located in Oslo at the Norwegian Institute of Public Health and funded by the Norwegian government. The European Commission is the executive of the European Union and promotes its general interest.
|
||||
#'
|
||||
#' \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/}.}
|
||||
#' **NOTE: The WHOCC copyright does not allow use for commercial purposes, unlike any other info from this package.** See <https://www.whocc.no/copyright_disclaimer/.>
|
||||
#' @inheritSection AMR Read more on our website!
|
||||
#' @name WHOCC
|
||||
#' @rdname WHOCC
|
||||
|
Reference in New Issue
Block a user