diff --git a/DESCRIPTION b/DESCRIPTION
index bc1c573c2..482fa3427 100644
--- a/DESCRIPTION
+++ b/DESCRIPTION
@@ -1,6 +1,6 @@
Package: AMR
-Version: 1.4.0.9062
-Date: 2021-01-04
+Version: 1.5.0
+Date: 2021-01-05
Title: Antimicrobial Resistance Analysis
Authors@R: c(
person(role = c("aut", "cre"),
diff --git a/NEWS.md b/NEWS.md
index e6862e4aa..8acfbb5b6 100755
--- a/NEWS.md
+++ b/NEWS.md
@@ -1,5 +1,7 @@
-# AMR 1.4.0.9062
-## Last updated: 4 January 2021
+# AMR 1.5.0
+
+*Note: the rules of 'EUCAST Clinical Breakpoints v11.0 (2021)' will be added in the next release, to be expected in February/March 2021.*
+
### New
* Functions `get_episode()` and `is_new_episode()` to determine (patient) episodes which are not necessarily based on microorganisms. The `get_episode()` function returns the index number of the episode per group, while the `is_new_episode()` function returns values `TRUE`/`FALSE` to indicate whether an item in a vector is the start of a new episode. They also support `dplyr`s grouping (i.e. using `group_by()`):
```r
@@ -45,7 +47,7 @@
select(mo, cephalosporins(), aminoglycosides()) %>%
as_tibble()
```
-* For antibiotic selection functions (such as `cephalosporins()`, `aminoglycosides()`) to select columns based on a certain antibiotic group, the dependency on the `tidyselect` package was removed, meaning that they can now also be used without the need to have this package installed and now also work in base R function calls:
+* For antibiotic selection functions (such as `cephalosporins()`, `aminoglycosides()`) to select columns based on a certain antibiotic group, the dependency on the `tidyselect` package was removed, meaning that they can now also be used without the need to have this package installed and now also work in base R function calls (they rely on R 3.2 or later):
```r
# above example in base R:
example_isolates[which(first_isolate() & mo_is_gram_negative()),
diff --git a/R/ab_class_selectors.R b/R/ab_class_selectors.R
index 0d06d6f62..80befcd37 100644
--- a/R/ab_class_selectors.R
+++ b/R/ab_class_selectors.R
@@ -27,7 +27,7 @@
#'
#' These functions help to select the columns of antibiotics that are of a specific antibiotic class, without the need to define the columns or antibiotic abbreviations.
#' @inheritParams filter_ab_class
-#' @details These functions only work in R 3.2 (2015) and later.
+#' @details \strong{\Sexpr{ifelse(as.double(R.Version()$major) + (as.double(R.Version()$minor) / 10) < 3.2, paste0("NOTE: THESE FUNCTIONS DO NOT WORK ON YOUR CURRENT R VERSION. These functions require R version 3.2 or later - you have ", R.version.string, "."), "")}}
#'
#' All columns will be searched for known antibiotic names, abbreviations, brand names and codes (ATC, EARS-Net, WHO, etc.) in the [antibiotics] data set. This means that a selector like e.g. [aminoglycosides()] will pick up column names like 'gen', 'genta', 'J01GB03', 'tobra', 'Tobracin', etc.
#' @rdname antibiotic_class_selectors
@@ -165,7 +165,9 @@ ab_selector <- function(ab_class, function_name) {
meet_criteria(function_name, allow_class = "character", has_length = 1, .call_depth = 1)
if (as.double(R.Version()$major) + (as.double(R.Version()$minor) / 10) < 3.2) {
- warning_(function_name, "() can only be used in R >= 3.2", call = FALSE)
+ warning_("antibiotic class selectors such as ", function_name,
+ "() require R version 3.2 or later - you have ", R.version.string,
+ call = FALSE)
return(NULL)
}
@@ -194,10 +196,11 @@ ab_selector <- function(ab_class, function_name) {
if (length(agents) == 0) {
message_("No antimicrobial agents of class ", ab_group, " found", examples, ".")
} else {
- message_("Selecting ", ab_group, ": ",
- paste(paste0("column '", font_bold(agents, collapse = NULL),
- "' (", ab_name(names(agents), tolower = TRUE, language = NULL), ")"),
- collapse = ", "),
+ agents_formatted <- paste0("column '", font_bold(agents, collapse = NULL), "'")
+ agents_names <- ab_name(names(agents), tolower = TRUE, language = NULL)
+ agents_formatted[agents != agents_names] <- paste0(agents_formatted[agents != agents_names],
+ " (", agents_names[agents != agents_names], ")")
+ message_("Selecting ", ab_group, ": ", paste(agents_formatted, collapse = ", "),
as_note = FALSE,
extra_indent = nchar(paste0("Selecting ", ab_group, ": ")))
}
diff --git a/R/catalogue_of_life.R b/R/catalogue_of_life.R
index f84d781b5..ec4e00567 100755
--- a/R/catalogue_of_life.R
+++ b/R/catalogue_of_life.R
@@ -44,7 +44,7 @@ format_included_data_number <- function(data) {
#' 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 (CoL, ). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, [lpsn.dsmz.de](https://lpsn.dsmz.de)). This supplementation is needed until the [CoL+ project](https://github.com/Sp2000/colplus) is finished, which we await.
+#' This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, ). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, [lpsn.dsmz.de](https://lpsn.dsmz.de)). This supplementation is needed until the [CoL+ project](https://github.com/CatalogueOfLife/general) is finished, which we await.
#'
#' [Click here][catalogue_of_life] for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with [catalogue_of_life_version()].
#' @section Included taxa:
diff --git a/R/data.R b/R/data.R
index ab2a733d4..866f2eb08 100755
--- a/R/data.R
+++ b/R/data.R
@@ -120,7 +120,7 @@
#' In February 2020, the DSMZ records were merged with the List of Prokaryotic names with Standing in Nomenclature (LPSN).
#' @source Catalogue of Life: Annual Checklist (public online taxonomic database), (check included annual version with [catalogue_of_life_version()]).
#'
-#' Parte, A.C. (2018). LPSN — List of Prokaryotic names with Standing in Nomenclature (bacterio.net), 20 years on. International Journal of Systematic and Evolutionary Microbiology, 68, 1825-1829; doi: 10.1099/ijsem.0.002786
+#' Parte, A.C. (2018). LPSN — List of Prokaryotic names with Standing in Nomenclature (bacterio.net), 20 years on. International Journal of Systematic and Evolutionary Microbiology, 68, 1825-1829; \doi{10.1099/ijsem.0.002786}
#'
#' Leibniz Institute DSMZ-German Collection of Microorganisms and Cell Cultures, Germany, Prokaryotic Nomenclature Up-to-Date, and (check included version with [catalogue_of_life_version()]).
#' @inheritSection AMR Reference data publicly available
@@ -147,7 +147,7 @@ catalogue_of_life <- list(
#' - `prevalence`\cr Prevalence of the microorganism, see [as.mo()]
#' @source Catalogue of Life: Annual Checklist (public online taxonomic database), (check included annual version with [catalogue_of_life_version()]).
#'
-#' Parte, A.C. (2018). LPSN — List of Prokaryotic names with Standing in Nomenclature (bacterio.net), 20 years on. International Journal of Systematic and Evolutionary Microbiology, 68, 1825-1829; doi: 10.1099/ijsem.0.002786
+#' Parte, A.C. (2018). LPSN — List of Prokaryotic names with Standing in Nomenclature (bacterio.net), 20 years on. International Journal of Systematic and Evolutionary Microbiology, 68, 1825-1829; \doi{10.1099/ijsem.0.002786}
#' @inheritSection AMR Reference data publicly available
#' @inheritSection AMR Read more on our website!
#' @seealso [as.mo()] [mo_property()] [microorganisms]
diff --git a/R/eucast_rules.R b/R/eucast_rules.R
index 4544bd90c..790374425 100755
--- a/R/eucast_rules.R
+++ b/R/eucast_rules.R
@@ -83,7 +83,7 @@ format_eucast_version_nr <- function(version, markdown = TRUE) {
#'
#' Important examples include amoxicillin and amoxicillin/clavulanic acid, and trimethoprim and trimethoprim/sulfamethoxazole. Needless to say, for these rules to work, both drugs must be available in the data set.
#'
-#' Since these rules are not officially approved by EUCAST, they are not applied at default. To use these rules, include `"other"` to the `rules` argument, or use `eucast_rules(..., rules = "all")`.
+#' Since these rules are not officially approved by EUCAST, they are not applied at default. To use these rules, include `"other"` to the `rules` argument, or use `eucast_rules(..., rules = "all")`. You can also set the option `AMR_eucastrules`, i.e. run `options(AMR_eucastrules = "all")`.
#' @section Antibiotics:
#' 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.
#'
@@ -96,7 +96,7 @@ format_eucast_version_nr <- function(version, markdown = TRUE) {
#' @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
#' - 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. [(link)](https://doi.org/10.1111/j.1469-0691.2011.03703.x)
+#' Leclercq et al. **EUCAST expert rules in antimicrobial susceptibility testing.** *Clin Microbiol Infect.* 2013;19(2):141-60; \doi{https://doi.org/10.1111/j.1469-0691.2011.03703.x}
#' - EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes Tables. Version 3.1, 2016. [(link)](https://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf)
#' - EUCAST Intrinsic Resistance and Unusual Phenotypes. Version 3.2, 2020. [(link)](https://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/2020/Intrinsic_Resistance_and_Unusual_Phenotypes_Tables_v3.2_20200225.pdf)
#' - EUCAST Breakpoint tables for interpretation of MICs and zone diameters. Version 9.0, 2019. [(link)](https://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Breakpoint_tables/v_9.0_Breakpoint_Tables.xlsx)
diff --git a/R/mdro.R b/R/mdro.R
index 51ed7a54d..6f4510b60 100755
--- a/R/mdro.R
+++ b/R/mdro.R
@@ -59,7 +59,7 @@
#'
#' * `guideline = "MRGN"`
#'
-#' The German national guideline - Mueller et al. (2015) Antimicrobial Resistance and Infection Control 4:7. DOI: 10.1186/s13756-015-0047-6
+#' The German national guideline - Mueller et al. (2015) Antimicrobial Resistance and Infection Control 4:7; \doi{10.1186/s13756-015-0047-6}
#'
#' * `guideline = "BRMO"`
#'
@@ -193,7 +193,7 @@ mdro <- function(x,
guideline$name <- "Multidrug-resistant, extensively drug-resistant and pandrug-resistant bacteria: an international expert proposal for interim standard definitions for acquired resistance."
guideline$author <- "Magiorakos AP, Srinivasan A, Carey RB, ..., Vatopoulos A, Weber JT, Monnet DL"
guideline$version <- NA
- guideline$source_url <- "Clinical Microbiology and Infection 18:3, 2012. DOI: 10.1111/j.1469-0691.2011.03570.x"
+ guideline$source_url <- "Clinical Microbiology and Infection 18:3, 2012; doi: 10.1111/j.1469-0691.2011.03570.x"
guideline$type <- "MDRs/XDRs/PDRs"
} else if (guideline$code == "eucast3.1") {
@@ -222,7 +222,7 @@ mdro <- function(x,
guideline$name <- "Cross-border comparison of the Dutch and German guidelines on multidrug-resistant Gram-negative microorganisms"
guideline$author <- "M\u00fcller J, Voss A, K\u00f6ck R, ..., Kern WV, Wendt C, Friedrich AW"
guideline$version <- NA
- guideline$source_url <- "Antimicrobial Resistance and Infection Control 4:7, 2015. DOI: 10.1186/s13756-015-0047-6"
+ guideline$source_url <- "Antimicrobial Resistance and Infection Control 4:7, 2015; doi: 10.1186/s13756-015-0047-6"
guideline$type <- "MRGNs"
} else if (guideline$code == "brmo") {
diff --git a/R/mo.R b/R/mo.R
index 4aeaf127a..2b24c34c2 100755
--- a/R/mo.R
+++ b/R/mo.R
@@ -102,10 +102,10 @@
#' @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 *et al.* **Coagulase-Negative Staphylococci**. 2014. Clin Microbiol Rev. 27(4): 870–926.
-#' 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.
-#' 3. Becker K *et al.* **Emergence of coagulase-negative staphylococci** 2020. Expert Rev Anti Infect Ther. 18(4):349-366.
-#' 4. Lancefield RC **A serological differentiation of human and other groups of hemolytic streptococci**. 1933. J Exp Med. 57(4): 571–95.
+#' 1. Becker K *et al.* **Coagulase-Negative Staphylococci**. 2014. Clin Microbiol Rev. 27(4): 870–926; \doi{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; \doi{10.1016/j.cmi.2019.02.028}
+#' 3. Becker K *et al.* **Emergence of coagulase-negative staphylococci** 2020. Expert Rev Anti Infect Ther. 18(4):349-366; \doi{10.1080/14787210.2020.1730813}
+#' 4. Lancefield RC **A serological differentiation of human and other groups of hemolytic streptococci**. 1933. J Exp Med. 57(4): 571–95; \doi{10.1084/jem.57.4.571}
#' 5. Catalogue of Life: Annual Checklist (public online taxonomic database), (check included annual version with [catalogue_of_life_version()]).
#' @export
#' @return A [character] [vector] with additional class [`mo`]
diff --git a/data-raw/AMR_1.4.0.9062.tar.gz b/data-raw/AMR_1.5.0.tar.gz
similarity index 76%
rename from data-raw/AMR_1.4.0.9062.tar.gz
rename to data-raw/AMR_1.5.0.tar.gz
index 81e8a2756..d987293df 100644
Binary files a/data-raw/AMR_1.4.0.9062.tar.gz and b/data-raw/AMR_1.5.0.tar.gz differ
diff --git a/docs/404.html b/docs/404.html
index 5c610abbc..44b8b7d2a 100644
--- a/docs/404.html
+++ b/docs/404.html
@@ -81,7 +81,7 @@
AMR (for R)
- 1.4.0.9062
+ 1.5.0
diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html
index 2afb34b21..d1028e1db 100644
--- a/docs/LICENSE-text.html
+++ b/docs/LICENSE-text.html
@@ -81,7 +81,7 @@
AMR (for R)
- 1.4.0.9062
+ 1.5.0
diff --git a/docs/articles/index.html b/docs/articles/index.html
index 4c6f7946b..0047bd5d1 100644
--- a/docs/articles/index.html
+++ b/docs/articles/index.html
@@ -81,7 +81,7 @@
AMR (for R)
- 1.4.0.9062
+ 1.5.0
diff --git a/docs/authors.html b/docs/authors.html
index 7b6ce0a86..199230b91 100644
--- a/docs/authors.html
+++ b/docs/authors.html
@@ -81,7 +81,7 @@
AMR (for R)
- 1.4.0.9062
+ 1.5.0
diff --git a/docs/index.html b/docs/index.html
index 90126aab6..f328198dd 100644
--- a/docs/index.html
+++ b/docs/index.html
@@ -43,7 +43,7 @@
AMR (for R)
- 1.4.0.9062
+ 1.5.0
@@ -197,6 +197,7 @@
+Note: the rules of ‘EUCAST Clinical Breakpoints v11.0 (2021)’ will be added in the next release, to be expected in February/March 2021.
PLEASE TAKE PART IN OUR SURVEY!
Since you are one of our users, we would like to know how you use the package and what it brought you or your organisation. If you have a minute, please anonymously fill in this short questionnaire. Your valuable input will help to improve the package and its functionalities. You can answer the open questions in either English, Spanish, French, Dutch, or German. Thank you very much in advance!
Take me to the 5-min survey!
@@ -222,9 +223,9 @@ Since you are one of our users, we would like to know how you use the package an
library(dplyr)
example_isolates %>%
- mutate(mo = mo_fullname(mo)) %>%
- filter(mo_is_gram_negative(), mo_is_intrinsic_resistant(ab = "cefotax")) %>%
- select(mo, aminoglycosides(), carbapenems())
+ mutate(mo = mo_fullname(mo)) %>%
+ filter(mo_is_gram_negative(), mo_is_intrinsic_resistant(ab = "cefotax")) %>%
+ select(mo, aminoglycosides(), carbapenems())
#> NOTE: Using column 'mo' as input for mo_is_gram_negative()
#> NOTE: Using column 'mo' as input for mo_is_intrinsic_resistant()
#> NOTE: Determining intrinsic resistance based on 'EUCAST Expert Rules' and
@@ -359,7 +360,7 @@ Since you are one of our users, we would like to know how you use the package an
The latest and unpublished development version can be installed from GitHub using:
+remotes::install_github("msberends/AMR")
@@ -420,7 +421,7 @@ Since you are one of our users, we would like to know how you use the package an
It analyses the data with convenient functions that use well-known methods.
-- Calculate the microbial susceptibility or resistance (and even co-resistance) with the
susceptibility()
and resistance()
functions, or be even more specific with the proportion_R()
, proportion_IR()
, proportion_I()
, proportion_SI()
and proportion_S()
functions. Similarly, the number of isolates can be determined with the count_resistant()
, count_susceptible()
and count_all()
functions. All these functions can be used with the dplyr
package (e.g. in conjunction with summarise()
)
+- Calculate the microbial susceptibility or resistance (and even co-resistance) with the
susceptibility()
and resistance()
functions, or be even more specific with the proportion_R()
, proportion_IR()
, proportion_I()
, proportion_SI()
and proportion_S()
functions. Similarly, the number of isolates can be determined with the count_resistant()
, count_susceptible()
and count_all()
functions. All these functions can be used with the dplyr
package (e.g. in conjunction with summarise()
)
- Plot AMR results with
geom_rsi()
, a function made for the ggplot2
package
- Predict antimicrobial resistance for the nextcoming years using logistic regression models with the
resistance_predict()
function
diff --git a/docs/news/index.html b/docs/news/index.html
index c16a3159e..eea0d198c 100644
--- a/docs/news/index.html
+++ b/docs/news/index.html
@@ -81,7 +81,7 @@
AMR (for R)
- 1.4.0.9062
+ 1.5.0
@@ -236,26 +236,23 @@
Source: NEWS.md
-
-
Support for veterinary ATC codes
@@ -390,16 +386,16 @@
Improvements for as.rsi()
:
-
-
Support for using dplyr
’s across()
to interpret MIC values or disk zone diameters, which also automatically determines the column with microorganism names or codes.
+Support for using dplyr
’s across()
to interpret MIC values or disk zone diameters, which also automatically determines the column with microorganism names or codes.
# until dplyr 1.0.0
-your_data %>% mutate_if(is.mic, as.rsi)
-your_data %>% mutate_if(is.disk, as.rsi)
+your_data %>% mutate_if(is.mic, as.rsi)
+your_data %>% mutate_if(is.disk, as.rsi)
# since dplyr 1.0.0
-your_data %>% mutate(across(where(is.mic), as.rsi))
-your_data %>% mutate(across(where(is.disk), as.rsi))
+your_data %>% mutate(across(where(is.mic), as.rsi))
+your_data %>% mutate(across(where(is.disk), as.rsi))
Cleaning columns in a data.frame now allows you to specify those columns with tidy selection, e.g. as.rsi(df, col1:col9)
Big speed improvement for interpreting MIC values and disk zone diameters. When interpreting 5,000 MIC values of two antibiotics (10,000 values in total), our benchmarks showed a total run time going from 80.7-85.1 seconds to 1.8-2.0 seconds.
@@ -469,14 +465,14 @@
Function ab_from_text()
to retrieve antimicrobial drug names, doses and forms of administration from clinical texts in e.g. health care records, which also corrects for misspelling since it uses as.ab()
internally
-
-
Tidyverse selection helpers for antibiotic classes, that help to select the columns of antibiotics that are of a specific antibiotic class, without the need to define the columns or antibiotic abbreviations. They can be used in any function that allows selection helpers, like dplyr::select()
and tidyr::pivot_longer()
:
+Tidyverse selection helpers for antibiotic classes, that help to select the columns of antibiotics that are of a specific antibiotic class, without the need to define the columns or antibiotic abbreviations. They can be used in any function that allows selection helpers, like dplyr::select()
and tidyr::pivot_longer()
:
Added mo_domain()
as an alias to mo_kingdom()
@@ -658,14 +654,14 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
Fixed important floating point error for some MIC comparisons in EUCAST 2020 guideline
-
-
Interpretation from MIC values (and disk zones) to R/SI can now be used with mutate_at()
of the dplyr
package:
+Interpretation from MIC values (and disk zones) to R/SI can now be used with mutate_at()
of the dplyr
package:
yourdata %>%
- mutate_at(vars(antibiotic1:antibiotic25), as.rsi, mo = "E. coli")
+ mutate_at(vars(antibiotic1:antibiotic25), as.rsi, mo = "E. coli")
yourdata %>%
- mutate_at(vars(antibiotic1:antibiotic25), as.rsi, mo = .$mybacteria)
+ mutate_at(vars(antibiotic1:antibiotic25), as.rsi, mo = .$mybacteria)
Added antibiotic abbreviations for a laboratory manufacturer (GLIMS) for cefuroxime, cefotaxime, ceftazidime, cefepime, cefoxitin and trimethoprim/sulfamethoxazole
Added uti
(as abbreviation of urinary tract infections) as argument to as.rsi()
, so interpretation of MIC values and disk zones can be made dependent on isolates specifically from UTIs
@@ -786,10 +782,10 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
library(dplyr)
example_isolates %>%
- group_by(bug = mo_name(mo)) %>%
- summarise(amoxicillin = resistance(AMX),
+ group_by(bug = mo_name(mo)) %>%
+ summarise(amoxicillin = resistance(AMX),
amox_clav = resistance(AMC)) %>%
- filter(!is.na(amoxicillin) | !is.na(amox_clav))
+ filter(!is.na(amoxicillin) | !is.na(amox_clav))
-
Support for a new MDRO guideline: 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).
@@ -958,7 +954,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
# (run this on your own console, as this page does not support colour printing)
library(dplyr)
example_isolates %>%
- select(mo:AMC) %>%
+ select(mo:AMC) %>%
as_tibble()
@@ -1039,7 +1035,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
septic_patients %>%
- select(AMX, CIP) %>%
+ select(AMX, CIP) %>%
rsi_df()
# antibiotic interpretation value isolates
# 1 Amoxicillin SI 0.4442636 546
@@ -1175,7 +1171,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
boxplot()
# grouped boxplots:
septic_patients %>%
- group_by(hospital_id) %>%
+ group_by(hospital_id) %>%
freq(age) %>%
boxplot()
@@ -1324,9 +1320,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
+ mutate(only_firsts = first_isolate(septic_patients, ...)) %>%
+ filter(only_firsts == TRUE) %>%
+ select(-only_firsts)
New function availability()
to check the number of available (non-empty) results in a data.frame
New vignettes about how to conduct AMR analysis, predict antimicrobial resistance, use the G-test and more. These are also available (and even easier readable) on our website: https://msberends.gitlab.io/AMR.
@@ -1436,7 +1432,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
# Determine genus of microorganisms (mo) in `septic_patients` data set:
# OLD WAY
septic_patients %>%
- mutate(genus = mo_genus(mo)) %>%
+ mutate(genus = mo_genus(mo)) %>%
freq(genus)
# NEW WAY
septic_patients %>%
@@ -1444,7 +1440,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
# Even supports grouping variables:
septic_patients %>%
- group_by(gender) %>%
+ group_by(gender) %>%
freq(mo_genus(mo))
Header info is now available as a list, with the header
function
@@ -1455,7 +1451,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
Fix for header text where all observations are NA
New argument droplevels
to exclude empty factor levels when input is a factor
Factor levels will be in header when present in input data (maximum of 5)
-Fix for using select()
on frequency tables
+Fix for using select()
on frequency tables
- Function
scale_y_percent()
now contains the limits
argument
@@ -1535,7 +1531,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
septic_patients %>%
- group_by(hospital_id) %>%
+ group_by(hospital_id) %>%
freq(gender)
-
@@ -1544,7 +1540,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
septic_patients %>%
freq(hospital_id) %>%
- select(-count, -cum_count) # only get item, percent, cum_percent
+ select(-count, -cum_count) # only get item, percent, cum_percent
Check for hms::is.hms
Now prints in markdown at default in non-interactive sessions
@@ -1708,7 +1704,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
Support for quasiquotation in the functions series count_*
and portions_*
, and n_rsi
. This allows to check for more than 2 vectors or columns.
-septic_patients %>% select(amox, cipr) %>% count_IR()
+septic_patients %>% select(amox, cipr) %>% count_IR()
# which is the same as:
septic_patients %>% count_IR(amox, cipr)
@@ -1894,7 +1890,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
- Full support for Windows, Linux and macOS
- Full support for old R versions, only R-3.0.0 (April 2013) or later is needed (needed packages may have other dependencies)
-- Function
n_rsi
to count cases where antibiotic test results were available, to be used in conjunction with dplyr::summarise
, see ?rsi
+- Function
n_rsi
to count cases where antibiotic test results were available, to be used in conjunction with dplyr::summarise
, see ?rsi
- Function
guess_bactid
to determine the ID of a microorganism based on genus/species or known abbreviations like MRSA
- Function
guess_atc
to determine the ATC of an antibiotic based on name, trade name, or known abbreviations
- Function
freq
to create frequency tables, with additional info in a header
diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml
index c801664b7..3d893184f 100644
--- a/docs/pkgdown.yml
+++ b/docs/pkgdown.yml
@@ -12,7 +12,7 @@ articles:
datasets: datasets.html
resistance_predict: resistance_predict.html
welcome_to_AMR: welcome_to_AMR.html
-last_built: 2021-01-04T13:44Z
+last_built: 2021-01-05T08:44Z
urls:
reference: https://msberends.github.io/AMR//reference
article: https://msberends.github.io/AMR//articles
diff --git a/docs/reference/antibiotic_class_selectors.html b/docs/reference/antibiotic_class_selectors.html
index 5a6123b0c..5d1d71868 100644
--- a/docs/reference/antibiotic_class_selectors.html
+++ b/docs/reference/antibiotic_class_selectors.html
@@ -82,7 +82,7 @@
AMR (for R)
- 1.4.0.9059
+ 1.5.0
@@ -281,7 +281,8 @@
Details
- These functions only work in R 3.2 (2015) and later.
+
+
All columns will be searched for known antibiotic names, abbreviations, brand names and codes (ATC, EARS-Net, WHO, etc.) in the antibiotics data set. This means that a selector like e.g. aminoglycosides()
will pick up column names like 'gen', 'genta', 'J01GB03', 'tobra', 'Tobracin', etc.
Reference data publicly available
diff --git a/docs/reference/as.mo.html b/docs/reference/as.mo.html
index f562904d8..01b5a0ad3 100644
--- a/docs/reference/as.mo.html
+++ b/docs/reference/as.mo.html
@@ -368,10 +368,10 @@
-Becker K et al. Coagulase-Negative Staphylococci. 2014. Clin Microbiol Rev. 27(4): 870–926. https://dx.doi.org/10.1128/CMR.00109-13
-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
-Becker K et al. Emergence of coagulase-negative staphylococci 2020. Expert Rev Anti Infect Ther. 18(4):349-366. https://dx.doi.org/10.1080/14787210.2020.1730813
-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
+Becker K et al. Coagulase-Negative Staphylococci. 2014. Clin Microbiol Rev. 27(4): 870–926; doi: 10.1128/CMR.00109-13
+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; doi: 10.1016/j.cmi.2019.02.028
+Becker K et al. Emergence of coagulase-negative staphylococci 2020. Expert Rev Anti Infect Ther. 18(4):349-366; doi: 10.1080/14787210.2020.1730813
+Lancefield RC A serological differentiation of human and other groups of hemolytic streptococci. 1933. J Exp Med. 57(4): 571–95; doi: 10.1084/jem.57.4.571
Catalogue of Life: Annual Checklist (public online taxonomic database), http://www.catalogueoflife.org (check included annual version with catalogue_of_life_version()
).
@@ -404,7 +404,7 @@ The lifecycle of this function is stable
-This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
Click here for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with catalogue_of_life_version()
.
Reference data publicly available
diff --git a/docs/reference/catalogue_of_life.html b/docs/reference/catalogue_of_life.html
index 139f75764..e081c25be 100644
--- a/docs/reference/catalogue_of_life.html
+++ b/docs/reference/catalogue_of_life.html
@@ -249,7 +249,7 @@
-This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
Click here for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with catalogue_of_life_version()
.
Included taxa
diff --git a/docs/reference/catalogue_of_life_version.html b/docs/reference/catalogue_of_life_version.html
index 97c6fcfe1..7bd4026b4 100644
--- a/docs/reference/catalogue_of_life_version.html
+++ b/docs/reference/catalogue_of_life_version.html
@@ -256,7 +256,7 @@
-This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
Click here for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with catalogue_of_life_version()
.
Read more on our website!
diff --git a/docs/reference/eucast_rules.html b/docs/reference/eucast_rules.html
index dd498d359..aaffd41c2 100644
--- a/docs/reference/eucast_rules.html
+++ b/docs/reference/eucast_rules.html
@@ -302,7 +302,7 @@ To improve the interpretation of the antibiogram before EUCAST rules are applied
EUCAST Expert Rules. Version 2.0, 2012.
-Leclercq et al. EUCAST expert rules in antimicrobial susceptibility testing. Clin Microbiol Infect. 2013;19(2):141-60. (link)
+Leclercq et al. EUCAST expert rules in antimicrobial susceptibility testing. Clin Microbiol Infect. 2013;19(2):141-60; doi: 10.1111/j.1469-0691.2011.03703.x
EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes Tables. Version 3.1, 2016. (link)
EUCAST Intrinsic Resistance and Unusual Phenotypes. Version 3.2, 2020. (link)
EUCAST Breakpoint tables for interpretation of MICs and zone diameters. Version 9.0, 2019. (link)
@@ -325,7 +325,7 @@ Leclercq et al. EUCAST expert rules in antimicrobial susceptibility test
Important examples include amoxicillin and amoxicillin/clavulanic acid, and trimethoprim and trimethoprim/sulfamethoxazole. Needless to say, for these rules to work, both drugs must be available in the data set.
-Since these rules are not officially approved by EUCAST, they are not applied at default. To use these rules, include "other"
to the rules
argument, or use eucast_rules(..., rules = "all")
.
+Since these rules are not officially approved by EUCAST, they are not applied at default. To use these rules, include "other"
to the rules
argument, or use eucast_rules(..., rules = "all")
. You can also set the option AMR_eucastrules
, i.e. run options(AMR_eucastrules = "all")
.
Antibiotics
diff --git a/docs/reference/index.html b/docs/reference/index.html
index 64e7089bd..36aa3ff67 100644
--- a/docs/reference/index.html
+++ b/docs/reference/index.html
@@ -81,7 +81,7 @@
AMR (for R)
- 1.4.0.9062
+ 1.5.0
diff --git a/docs/reference/mdro.html b/docs/reference/mdro.html
index 8c40d3035..13ce229e0 100644
--- a/docs/reference/mdro.html
+++ b/docs/reference/mdro.html
@@ -331,7 +331,7 @@ Ordered factor with levels 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" (link)
guideline = "MRGN"
-The German national guideline - Mueller et al. (2015) Antimicrobial Resistance and Infection Control 4:7. DOI: 10.1186/s13756-015-0047-6
+The German national guideline - Mueller et al. (2015) Antimicrobial Resistance and Infection Control 4:7; doi: 10.1186/s13756-015-0047-6
guideline = "BRMO"
The Dutch national guideline - Rijksinstituut voor Volksgezondheid en Milieu "WIP-richtlijn BRMO (Bijzonder Resistente Micro-Organismen) (ZKH)" (link)
diff --git a/docs/reference/microorganisms.codes.html b/docs/reference/microorganisms.codes.html
index aa86be6ea..c65e00b4f 100644
--- a/docs/reference/microorganisms.codes.html
+++ b/docs/reference/microorganisms.codes.html
@@ -262,7 +262,7 @@
-This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
Click here for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with catalogue_of_life_version()
.
Read more on our website!
diff --git a/docs/reference/microorganisms.html b/docs/reference/microorganisms.html
index 00a182653..f93acaf3d 100644
--- a/docs/reference/microorganisms.html
+++ b/docs/reference/microorganisms.html
@@ -262,7 +262,7 @@
Source
Catalogue of Life: Annual Checklist (public online taxonomic database), http://www.catalogueoflife.org (check included annual version with catalogue_of_life_version()
).
-Parte, A.C. (2018). LPSN — List of Prokaryotic names with Standing in Nomenclature (bacterio.net), 20 years on. International Journal of Systematic and Evolutionary Microbiology, 68, 1825-1829; doi: 10.1099/ijsem.0.002786
+Parte, A.C. (2018). LPSN — List of Prokaryotic names with Standing in Nomenclature (bacterio.net), 20 years on. International Journal of Systematic and Evolutionary Microbiology, 68, 1825-1829; doi: 10.1099/ijsem.0.002786
Leibniz Institute DSMZ-German Collection of Microorganisms and Cell Cultures, Germany, Prokaryotic Nomenclature Up-to-Date, https://www.dsmz.de/services/online-tools/prokaryotic-nomenclature-up-to-date and https://lpsn.dsmz.de (check included version with catalogue_of_life_version()
).
Details
@@ -300,7 +300,7 @@
-This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
Click here for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with catalogue_of_life_version()
.
Reference data publicly available
diff --git a/docs/reference/microorganisms.old.html b/docs/reference/microorganisms.old.html
index 0ea63b273..c8a652122 100644
--- a/docs/reference/microorganisms.old.html
+++ b/docs/reference/microorganisms.old.html
@@ -257,13 +257,13 @@
Source
Catalogue of Life: Annual Checklist (public online taxonomic database), http://www.catalogueoflife.org (check included annual version with catalogue_of_life_version()
).
-Parte, A.C. (2018). LPSN — List of Prokaryotic names with Standing in Nomenclature (bacterio.net), 20 years on. International Journal of Systematic and Evolutionary Microbiology, 68, 1825-1829; doi: 10.1099/ijsem.0.002786
+Parte, A.C. (2018). LPSN — List of Prokaryotic names with Standing in Nomenclature (bacterio.net), 20 years on. International Journal of Systematic and Evolutionary Microbiology, 68, 1825-1829; doi: 10.1099/ijsem.0.002786
Catalogue of Life
-This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
Click here for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with catalogue_of_life_version()
.
Reference data publicly available
diff --git a/docs/reference/mo_property.html b/docs/reference/mo_property.html
index 253f3d4fa..37b8d5b6e 100644
--- a/docs/reference/mo_property.html
+++ b/docs/reference/mo_property.html
@@ -379,17 +379,17 @@ The lifecycle of this function is stable
-This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, http://www.catalogueoflife.org). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, lpsn.dsmz.de). This supplementation is needed until the CoL+ project is finished, which we await.
Click here for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with catalogue_of_life_version()
.
Source
-Becker K et al. Coagulase-Negative Staphylococci. 2014. Clin Microbiol Rev. 27(4): 870–926. https://dx.doi.org/10.1128/CMR.00109-13
-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
-Becker K et al. Emergence of coagulase-negative staphylococci 2020. Expert Rev Anti Infect Ther. 18(4):349-366. https://dx.doi.org/10.1080/14787210.2020.1730813
-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
+Becker K et al. Coagulase-Negative Staphylococci. 2014. Clin Microbiol Rev. 27(4): 870–926; doi: 10.1128/CMR.00109-13
+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; doi: 10.1016/j.cmi.2019.02.028
+Becker K et al. Emergence of coagulase-negative staphylococci 2020. Expert Rev Anti Infect Ther. 18(4):349-366; doi: 10.1080/14787210.2020.1730813
+Lancefield RC A serological differentiation of human and other groups of hemolytic streptococci. 1933. J Exp Med. 57(4): 571–95; doi: 10.1084/jem.57.4.571
Catalogue of Life: Annual Checklist (public online taxonomic database), http://www.catalogueoflife.org (check included annual version with catalogue_of_life_version()
).
diff --git a/docs/survey.html b/docs/survey.html
index 3d9988f51..fd727a877 100644
--- a/docs/survey.html
+++ b/docs/survey.html
@@ -81,7 +81,7 @@
AMR (for R)
- 1.4.0.9062
+ 1.5.0
diff --git a/index.md b/index.md
index f8a7871a9..b174b5cf9 100644
--- a/index.md
+++ b/index.md
@@ -1,5 +1,7 @@
# `AMR` (for R)
+*Note: the rules of 'EUCAST Clinical Breakpoints v11.0 (2021)' will be added in the next release, to be expected in February/March 2021.*
+
> **PLEASE TAKE PART IN OUR SURVEY!**
> Since you are one of our users, we would like to know how you use the package and what it brought you or your organisation. **If you have a minute, please [anonymously fill in this short questionnaire](./survey.html)**. Your valuable input will help to improve the package and its functionalities. You can answer the open questions in either English, Spanish, French, Dutch, or German. Thank you very much in advance!
>
diff --git a/man/antibiotic_class_selectors.Rd b/man/antibiotic_class_selectors.Rd
index 23b2b3546..f5fdd2b9a 100644
--- a/man/antibiotic_class_selectors.Rd
+++ b/man/antibiotic_class_selectors.Rd
@@ -53,7 +53,7 @@ tetracyclines()
These functions help to select the columns of antibiotics that are of a specific antibiotic class, without the need to define the columns or antibiotic abbreviations.
}
\details{
-These functions only work in R 3.2 (2015) and later.
+\strong{\Sexpr{ifelse(as.double(R.Version()$major) + (as.double(R.Version()$minor) / 10) < 3.2, paste0("NOTE: THESE FUNCTIONS DO NOT WORK ON YOUR CURRENT R VERSION. These functions require R version 3.2 or later - you have ", R.version.string, "."), "")}}
All columns will be searched for known antibiotic names, abbreviations, brand names and codes (ATC, EARS-Net, WHO, etc.) in the \link{antibiotics} data set. This means that a selector like e.g. \code{\link[=aminoglycosides]{aminoglycosides()}} will pick up column names like 'gen', 'genta', 'J01GB03', 'tobra', 'Tobracin', etc.
}
diff --git a/man/as.mo.Rd b/man/as.mo.Rd
index 7ad21b42e..50d26b3c5 100644
--- a/man/as.mo.Rd
+++ b/man/as.mo.Rd
@@ -123,10 +123,10 @@ The intelligent rules consider the prevalence of microorganisms in humans groupe
\section{Source}{
\enumerate{
-\item 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}
-\item 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}
-\item Becker K \emph{et al.} \strong{Emergence of coagulase-negative staphylococci} 2020. Expert Rev Anti Infect Ther. 18(4):349-366. \url{https://dx.doi.org/10.1080/14787210.2020.1730813}
-\item 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}
+\item Becker K \emph{et al.} \strong{Coagulase-Negative Staphylococci}. 2014. Clin Microbiol Rev. 27(4): 870–926; \doi{10.1128/CMR.00109-13}
+\item 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; \doi{10.1016/j.cmi.2019.02.028}
+\item Becker K \emph{et al.} \strong{Emergence of coagulase-negative staphylococci} 2020. Expert Rev Anti Infect Ther. 18(4):349-366; \doi{10.1080/14787210.2020.1730813}
+\item Lancefield RC \strong{A serological differentiation of human and other groups of hemolytic streptococci}. 1933. J Exp Med. 57(4): 571–95; \doi{10.1084/jem.57.4.571}
\item 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]{catalogue_of_life_version()}}).
}
}
@@ -163,7 +163,7 @@ All matches are sorted descending on their matching score and for all user input
\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 (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/Sp2000/colplus}{CoL+ project} is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/CatalogueOfLife/general}{CoL+ project} is finished, which we await.
\link[=catalogue_of_life]{Click here} for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with \code{\link[=catalogue_of_life_version]{catalogue_of_life_version()}}.
}
diff --git a/man/catalogue_of_life.Rd b/man/catalogue_of_life.Rd
index d9dd94cd0..cf5d6cd38 100644
--- a/man/catalogue_of_life.Rd
+++ b/man/catalogue_of_life.Rd
@@ -9,7 +9,7 @@ This package contains the complete taxonomic tree of almost all microorganisms f
\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 (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/Sp2000/colplus}{CoL+ project} is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/CatalogueOfLife/general}{CoL+ project} is finished, which we await.
\link[=catalogue_of_life]{Click here} for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with \code{\link[=catalogue_of_life_version]{catalogue_of_life_version()}}.
}
diff --git a/man/catalogue_of_life_version.Rd b/man/catalogue_of_life_version.Rd
index cd5e57bc2..896f6c2c1 100644
--- a/man/catalogue_of_life_version.Rd
+++ b/man/catalogue_of_life_version.Rd
@@ -18,7 +18,7 @@ For DSMZ, see \link{microorganisms}.
\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 (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/Sp2000/colplus}{CoL+ project} is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/CatalogueOfLife/general}{CoL+ project} is finished, which we await.
\link[=catalogue_of_life]{Click here} for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with \code{\link[=catalogue_of_life_version]{catalogue_of_life_version()}}.
}
diff --git a/man/eucast_rules.Rd b/man/eucast_rules.Rd
index 110f3f102..6c55fbdb0 100644
--- a/man/eucast_rules.Rd
+++ b/man/eucast_rules.Rd
@@ -7,7 +7,7 @@
\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. \href{https://doi.org/10.1111/j.1469-0691.2011.03703.x}{(link)}
+Leclercq et al. \strong{EUCAST expert rules in antimicrobial susceptibility testing.} \emph{Clin Microbiol Infect.} 2013;19(2):141-60; \doi{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. \href{https://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf}{(link)}
\item EUCAST Intrinsic Resistance and Unusual Phenotypes. Version 3.2, 2020. \href{https://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/2020/Intrinsic_Resistance_and_Unusual_Phenotypes_Tables_v3.2_20200225.pdf}{(link)}
\item EUCAST Breakpoint tables for interpretation of MICs and zone diameters. Version 9.0, 2019. \href{https://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Breakpoint_tables/v_9.0_Breakpoint_Tables.xlsx}{(link)}
@@ -69,7 +69,7 @@ Before further processing, two non-EUCAST rules about drug combinations can be a
Important examples include amoxicillin and amoxicillin/clavulanic acid, and trimethoprim and trimethoprim/sulfamethoxazole. Needless to say, for these rules to work, both drugs must be available in the data set.
-Since these rules are not officially approved by EUCAST, they are not applied at default. To use these rules, include \code{"other"} to the \code{rules} argument, or use \code{eucast_rules(..., rules = "all")}.
+Since these rules are not officially approved by EUCAST, they are not applied at default. To use these rules, include \code{"other"} to the \code{rules} argument, or use \code{eucast_rules(..., rules = "all")}. You can also set the option \code{AMR_eucastrules}, i.e. run \code{options(AMR_eucastrules = "all")}.
}
}
\section{Antibiotics}{
diff --git a/man/mdro.Rd b/man/mdro.Rd
index 01f056efe..6c8c98ea2 100644
--- a/man/mdro.Rd
+++ b/man/mdro.Rd
@@ -92,7 +92,7 @@ The European international guideline - EUCAST Expert Rules Version 3.1 "Intrinsi
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
+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/wip-richtlijn-brmo-bijzonder-resistente-micro-organismen-zkh}{link})
diff --git a/man/microorganisms.Rd b/man/microorganisms.Rd
index 1db872a2c..8c90412c1 100755
--- a/man/microorganisms.Rd
+++ b/man/microorganisms.Rd
@@ -21,7 +21,7 @@ A \link{data.frame} with 67,151 observations and 16 variables:
\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]{catalogue_of_life_version()}}).
-Parte, A.C. (2018). LPSN — List of Prokaryotic names with Standing in Nomenclature (bacterio.net), 20 years on. International Journal of Systematic and Evolutionary Microbiology, 68, 1825-1829; doi: 10.1099/ijsem.0.002786
+Parte, A.C. (2018). LPSN — List of Prokaryotic names with Standing in Nomenclature (bacterio.net), 20 years on. International Journal of Systematic and Evolutionary Microbiology, 68, 1825-1829; \doi{10.1099/ijsem.0.002786}
Leibniz Institute DSMZ-German Collection of Microorganisms and Cell Cultures, Germany, Prokaryotic Nomenclature Up-to-Date, \url{https://www.dsmz.de/services/online-tools/prokaryotic-nomenclature-up-to-date} and \url{https://lpsn.dsmz.de} (check included version with \code{\link[=catalogue_of_life_version]{catalogue_of_life_version()}}).
}
@@ -67,7 +67,7 @@ In February 2020, the DSMZ records were merged with the List of Prokaryotic name
\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 (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/Sp2000/colplus}{CoL+ project} is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/CatalogueOfLife/general}{CoL+ project} is finished, which we await.
\link[=catalogue_of_life]{Click here} for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with \code{\link[=catalogue_of_life_version]{catalogue_of_life_version()}}.
}
diff --git a/man/microorganisms.codes.Rd b/man/microorganisms.codes.Rd
index dd9af490b..236ffb2f9 100644
--- a/man/microorganisms.codes.Rd
+++ b/man/microorganisms.codes.Rd
@@ -25,7 +25,7 @@ All reference data sets (about microorganisms, antibiotics, R/SI interpretation,
\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 (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/Sp2000/colplus}{CoL+ project} is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/CatalogueOfLife/general}{CoL+ project} is finished, which we await.
\link[=catalogue_of_life]{Click here} for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with \code{\link[=catalogue_of_life_version]{catalogue_of_life_version()}}.
}
diff --git a/man/microorganisms.old.Rd b/man/microorganisms.old.Rd
index 435b77922..ab8370429 100644
--- a/man/microorganisms.old.Rd
+++ b/man/microorganisms.old.Rd
@@ -16,7 +16,7 @@ A \link{data.frame} with 12,708 observations and 4 variables:
\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]{catalogue_of_life_version()}}).
-Parte, A.C. (2018). LPSN — List of Prokaryotic names with Standing in Nomenclature (bacterio.net), 20 years on. International Journal of Systematic and Evolutionary Microbiology, 68, 1825-1829; doi: 10.1099/ijsem.0.002786
+Parte, A.C. (2018). LPSN — List of Prokaryotic names with Standing in Nomenclature (bacterio.net), 20 years on. International Journal of Systematic and Evolutionary Microbiology, 68, 1825-1829; \doi{10.1099/ijsem.0.002786}
}
\usage{
microorganisms.old
@@ -27,7 +27,7 @@ A data set containing old (previously valid or accepted) taxonomic names accordi
\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 (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/Sp2000/colplus}{CoL+ project} is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/CatalogueOfLife/general}{CoL+ project} is finished, which we await.
\link[=catalogue_of_life]{Click here} for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with \code{\link[=catalogue_of_life_version]{catalogue_of_life_version()}}.
}
diff --git a/man/mo_property.Rd b/man/mo_property.Rd
index 8dd1cb03d..67bca4b95 100644
--- a/man/mo_property.Rd
+++ b/man/mo_property.Rd
@@ -161,7 +161,7 @@ All matches are sorted descending on their matching score and for all user input
\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 (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/Sp2000/colplus}{CoL+ project} is finished, which we await.
+This package contains the complete taxonomic tree of almost all microorganisms (~70,000 species) from the authoritative and comprehensive Catalogue of Life (CoL, \url{http://www.catalogueoflife.org}). The CoL is the most comprehensive and authoritative global index of species currently available. Nonetheless, we supplemented the CoL data with data from the List of Prokaryotic names with Standing in Nomenclature (LPSN, \href{https://lpsn.dsmz.de}{lpsn.dsmz.de}). This supplementation is needed until the \href{https://github.com/CatalogueOfLife/general}{CoL+ project} is finished, which we await.
\link[=catalogue_of_life]{Click here} for more information about the included taxa. Check which versions of the CoL and LSPN were included in this package with \code{\link[=catalogue_of_life_version]{catalogue_of_life_version()}}.
}
@@ -169,10 +169,10 @@ This package contains the complete taxonomic tree of almost all microorganisms (
\section{Source}{
\enumerate{
-\item 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}
-\item 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}
-\item Becker K \emph{et al.} \strong{Emergence of coagulase-negative staphylococci} 2020. Expert Rev Anti Infect Ther. 18(4):349-366. \url{https://dx.doi.org/10.1080/14787210.2020.1730813}
-\item 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}
+\item Becker K \emph{et al.} \strong{Coagulase-Negative Staphylococci}. 2014. Clin Microbiol Rev. 27(4): 870–926; \doi{10.1128/CMR.00109-13}
+\item 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; \doi{10.1016/j.cmi.2019.02.028}
+\item Becker K \emph{et al.} \strong{Emergence of coagulase-negative staphylococci} 2020. Expert Rev Anti Infect Ther. 18(4):349-366; \doi{10.1080/14787210.2020.1730813}
+\item Lancefield RC \strong{A serological differentiation of human and other groups of hemolytic streptococci}. 1933. J Exp Med. 57(4): 571–95; \doi{10.1084/jem.57.4.571}
\item 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]{catalogue_of_life_version()}}).
}
}