(v1.1.0.9011) lose dependencies

This commit is contained in:
dr. M.S. (Matthijs) Berends 2020-05-18 13:59:34 +02:00
parent d659c9baef
commit 218fd08097
18 changed files with 110 additions and 65 deletions

View File

@ -151,7 +151,7 @@ lintr:
- master - master
script: script:
# check all syntax with lintr # check all syntax with lintr
- Rscript -e 'lintr::lint_package()' - Rscript -e 'lintr::lint_package(exclusions = list("R/aa_helper_functions_dplyr.R"))'
cache: cache:
key: release key: release
paths: paths:

View File

@ -1,5 +1,5 @@
Package: AMR Package: AMR
Version: 1.1.0.9010 Version: 1.1.0.9011
Date: 2020-05-18 Date: 2020-05-18
Title: Antimicrobial Resistance Analysis Title: Antimicrobial Resistance Analysis
Authors@R: c( Authors@R: c(
@ -37,10 +37,8 @@ Description: Functions to simplify the analysis and prediction of Antimicrobial
Depends: Depends:
R (>= 3.1.0) R (>= 3.1.0)
Imports: Imports:
backports,
cleaner, cleaner,
pillar, pillar,
tidyr (>= 1.0.0),
vctrs vctrs
Suggests: Suggests:
covr, covr,
@ -51,6 +49,7 @@ Suggests:
rmarkdown, rmarkdown,
rvest, rvest,
testthat, testthat,
tidyr,
utils utils
VignetteBuilder: knitr,rmarkdown VignetteBuilder: knitr,rmarkdown
URL: https://msberends.gitlab.io/AMR, https://gitlab.com/msberends/AMR URL: https://msberends.gitlab.io/AMR, https://gitlab.com/msberends/AMR

View File

@ -325,8 +325,6 @@ importFrom(stats,prcomp)
importFrom(stats,predict) importFrom(stats,predict)
importFrom(stats,qchisq) importFrom(stats,qchisq)
importFrom(stats,var) importFrom(stats,var)
importFrom(tidyr,pivot_longer)
importFrom(tidyr,pivot_wider)
importFrom(vctrs,vec_cast) importFrom(vctrs,vec_cast)
importFrom(vctrs,vec_cast.character) importFrom(vctrs,vec_cast.character)
importFrom(vctrs,vec_default_cast) importFrom(vctrs,vec_default_cast)

View File

@ -1,4 +1,4 @@
# AMR 1.1.0.9010 # AMR 1.1.0.9011
## <small>Last updated: 18-May-2020</small> ## <small>Last updated: 18-May-2020</small>
### Breaking ### Breaking
@ -11,7 +11,7 @@
* Added official drug names to verbose output of `eucast_rules()` * Added official drug names to verbose output of `eucast_rules()`
### Other ### Other
* Removed dependency on **all** packages that were needed for the `AMR` package to work properly: `crayon`, `data.table`, `dplyr`, `ggplot2`, `R6`, `rlang` and `tidyr`. This is a major code change, but will probably not be noticeable by users. Making this package independent on especially the tidyverse (packages `dplyr`, `ggplot2` and `tidyr`) tremendously increases sustainability on the long term, since tidyverse functions change quite often. Most of our functions are replaced with versions that only rely on base R, which keeps this package fully functional for many years to come, without requiring a lot of maintenance to keep up with other packages anymore. The only dependencies that remained are for extending methods of other packages, like `pillar` and `vctrs` for printing and working with tibbles using our classes `mo` and `ab`. * Removed dependency on **all** packages that were needed for the `AMR` package to work properly: `backports`, `crayon`, `data.table`, `dplyr`, `ggplot2`, `R6`, `rlang` and `tidyr`. This is a major code change, but will probably not be noticeable by users. Making this package independent on especially the tidyverse (packages `dplyr`, `ggplot2` and `tidyr`) tremendously increases sustainability on the long term, since tidyverse functions change quite often. Most of our functions are replaced with versions that only rely on base R, which keeps this package fully functional for many years to come, without requiring a lot of maintenance to keep up with other packages anymore. The only dependencies that remained are for extending methods of other packages, like `pillar` and `vctrs` for printing and working with tibbles using our classes `mo` and `ab`.
* Removed function `read.4d()`, that was only useful for reading from an old test database. * Removed function `read.4d()`, that was only useful for reading from an old test database.
# AMR 1.1.0 # AMR 1.1.0

View File

@ -338,12 +338,6 @@ font_stripstyle <- function(x) {
} }
progress_estimated <- function(n = 1, n_min = 0, ...) { progress_estimated <- function(n = 1, n_min = 0, ...) {
# initiate with:
# progress <- progressbar(n)
# on.exit(close(progress))
#
# update with:
# progress$tick()
if (n >= n_min) { if (n >= n_min) {
pb <- utils::txtProgressBar(max = n, style = 3) pb <- utils::txtProgressBar(max = n, style = 3)
pb$tick <- function() { pb$tick <- function() {
@ -431,3 +425,29 @@ percentage <- function(x, digits = NULL, ...) {
class = c("percentage", "numeric")), class = c("percentage", "numeric")),
digits = digits, ...) digits = digits, ...)
} }
# prevent dependency on package 'backports'
strrep = function(x, times) {
x = as.character(x)
if (length(x) == 0L)
return(x)
unlist(.mapply(function(x, times) {
if (is.na(x) || is.na(times))
return(NA_character_)
if (times <= 0L)
return("")
paste0(replicate(times, x), collapse = "")
}, list(x = x, times = times), MoreArgs = list()), use.names = FALSE)
}
trimws <- function (x, which = c("both", "left", "right")) {
which = match.arg(which)
mysub = function(re, x) sub(re, "", x, perl = TRUE)
if (which == "left")
return(mysub("^[ \t\r\n]+", x))
if (which == "right")
return(mysub("[ \t\r\n]+$", x))
mysub("[ \t\r\n]+$", mysub("^[ \t\r\n]+", x))
}
isFALSE <- function (x) {
is.logical(x) && length(x) == 1L && !is.na(x) && !x
}

View File

@ -129,7 +129,8 @@ atc_online_property <- function(atc_code,
} }
progress <- progress_estimated(n = length(atc_code)) progress <- progress_estimated(n = length(atc_code))
on.exit(close(progress))
for (i in seq_len(length(atc_code))) { for (i in seq_len(length(atc_code))) {
progress$tick() progress$tick()

View File

@ -32,7 +32,6 @@
#' @param ... arguments passed on to `FUN` #' @param ... arguments passed on to `FUN`
#' @inheritParams rsi_df #' @inheritParams rsi_df
#' @inheritParams base::formatC #' @inheritParams base::formatC
#' @importFrom tidyr pivot_longer
#' @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. #' @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 `options(AMR_locale)`, please see [translate]. #' The language of the output can be overwritten with `options(AMR_locale)`, please see [translate].
@ -73,28 +72,41 @@ bug_drug_combinations <- function(x,
stop("`col_mo` must be set.", call. = FALSE) stop("`col_mo` must be set.", call. = FALSE)
} }
select_rsi <- function(.data) { x <- as.data.frame(x, stringsAsFactors = FALSE)
.data[, c(col_mo, names(which(sapply(.data, is.rsi))))] x[, col_mo] <- FUN(x[, col_mo, drop = TRUE])
x <- x[, c(col_mo, names(which(sapply(x, is.rsi))))]
unique_mo <- sort(unique(x[, col_mo, drop = TRUE]))
out <- data.frame(
mo = character(0),
ab = character(0),
S = integer(0),
I = integer(0),
R = integer(0),
total = integer(0))
for (i in seq_len(length(unique_mo))) {
# filter on MO group and only select R/SI columns
x_mo_filter <- x[which(x[, col_mo, drop = TRUE] == unique_mo[i]), names(which(sapply(x, is.rsi)))]
# turn and merge everything
pivot <- lapply(x_mo_filter, function(x) {
m <- as.matrix(table(x))
data.frame(S = m["S", ], I = m["I", ], R = m["R", ], stringsAsFactors = FALSE)
})
merged <- do.call(rbind, pivot)
out_group <- data.frame(mo = unique_mo[i],
ab = rownames(merged),
S = merged$S,
I = merged$I,
R = merged$R,
total = merged$S + merged$I + merged$R)
out <- rbind(out, out_group)
} }
x <- x %>% as.data.frame(stringsAsFactors = FALSE) structure(.Data = out, class = c("bug_drug_combinations", class(x)))
x$mo <- FUN(x[, col_mo, drop = TRUE])
x <- x %>%
select_rsi() %>%
pivot_longer(-mo, names_to = "ab") %>%
group_by(mo, ab) %>%
summarise(S = sum(value == "S", na.rm = TRUE),
I = sum(value == "I", na.rm = TRUE),
R = sum(value == "R", na.rm = TRUE)) %>%
ungroup() %>%
mutate(total = S + I + R) %>%
as.data.frame(stringsAsFactors = FALSE)
structure(.Data = x, class = c("bug_drug_combinations", class(x)))
} }
#' @importFrom tidyr pivot_wider
#' @exportMethod format.bug_drug_combinations #' @exportMethod format.bug_drug_combinations
#' @export #' @export
#' @rdname bug_drug_combinations #' @rdname bug_drug_combinations
@ -109,10 +121,10 @@ format.bug_drug_combinations <- function(x,
decimal.mark = getOption("OutDec"), decimal.mark = getOption("OutDec"),
big.mark = ifelse(decimal.mark == ",", ".", ","), big.mark = ifelse(decimal.mark == ",", ".", ","),
...) { ...) {
x <- x %>% subset(total >= minimum) x <- subset(x, total >= minimum)
if (remove_intrinsic_resistant == TRUE) { if (remove_intrinsic_resistant == TRUE) {
x <- x %>% subset(R != total) x <- subset(x, R != total)
} }
if (combine_SI == TRUE | combine_IR == FALSE) { if (combine_SI == TRUE | combine_IR == FALSE) {
x$isolates <- x$R x$isolates <- x$R
@ -137,7 +149,10 @@ format.bug_drug_combinations <- function(x,
} }
remove_NAs <- function(.data) { remove_NAs <- function(.data) {
as.data.frame(sapply(.data, function(x) ifelse(is.na(x), "", x), simplify = FALSE)) cols <- colnames(.data)
.data <- as.data.frame(sapply(.data, function(x) ifelse(is.na(x), "", x), simplify = FALSE))
colnames(.data) <- cols
.data
} }
create_var <- function(.data, ...) { create_var <- function(.data, ...) {
@ -161,14 +176,26 @@ format.bug_drug_combinations <- function(x,
" (", trimws(format(y$isolates, big.mark = big.mark)), "/", " (", trimws(format(y$isolates, big.mark = big.mark)), "/",
trimws(format(y$total, big.mark = big.mark)), ")")) %>% trimws(format(y$total, big.mark = big.mark)), ")")) %>%
select(ab, ab_txt, mo, txt) %>% select(ab, ab_txt, mo, txt) %>%
arrange(mo) %>% arrange(mo)
pivot_wider(names_from = mo, values_from = txt) %>%
# replace tidyr::pivot_wider() from here
for (i in unique(y$mo)) {
mo_group <- y[which(y$mo == i), c("ab", "txt")]
colnames(mo_group) <- c("ab", i)
rownames(mo_group) <- NULL
y <- y %>%
left_join(mo_group, by = "ab")
}
y <- y %>%
distinct(ab, .keep_all = TRUE) %>%
select(-mo, -txt) %>%
# replace tidyr::pivot_wider() until here
remove_NAs() remove_NAs()
select_ab_vars <- function(.data) { select_ab_vars <- function(.data) {
.data[, c("ab_group", "ab_txt", colnames(.data)[!colnames(.data) %in% c("ab_group", "ab_txt", "ab")])] .data[, c("ab_group", "ab_txt", colnames(.data)[!colnames(.data) %in% c("ab_group", "ab_txt", "ab")])]
} }
y <- y %>% y <- y %>%
create_var(ab_group = ab_group(y$ab, language = language)) %>% create_var(ab_group = ab_group(y$ab, language = language)) %>%
select_ab_vars() %>% select_ab_vars() %>%
@ -177,13 +204,17 @@ format.bug_drug_combinations <- function(x,
create_var(ab_group = ifelse(y$ab_group != lag(y$ab_group) | is.na(lag(y$ab_group)), y$ab_group, "")) create_var(ab_group = ifelse(y$ab_group != lag(y$ab_group) | is.na(lag(y$ab_group)), y$ab_group, ""))
if (add_ab_group == FALSE) { if (add_ab_group == FALSE) {
y <- y %>% select(-ab_group) %>% rename("Drug" = ab_txt) y <- y %>%
select(-ab_group) %>%
rename("Drug" = ab_txt)
colnames(y)[1] <- translate_AMR(colnames(y)[1], language = get_locale(), only_unknown = FALSE) colnames(y)[1] <- translate_AMR(colnames(y)[1], language = get_locale(), only_unknown = FALSE)
} else { } else {
y <- y %>% rename("Group" = ab_group, y <- y %>% rename("Group" = ab_group,
"Drug" = ab_txt) "Drug" = ab_txt)
colnames(y)[1:2] <- translate_AMR(colnames(y)[1:2], language = get_locale(), only_unknown = FALSE) colnames(y)[1:2] <- translate_AMR(colnames(y)[1:2], language = get_locale(), only_unknown = FALSE)
} }
rownames(y) <- NULL
y y
} }

View File

@ -45,7 +45,7 @@ rsi_calc <- function(...,
stop("`only_all_tested` must be logical", call. = FALSE) stop("`only_all_tested` must be logical", call. = FALSE)
} }
dots_df <- ...elt(1) # it needs this evaluation dots_df <- switch(1, ...) # it needs this evaluation
dots <- base::eval(base::substitute(base::alist(...))) dots <- base::eval(base::substitute(base::alist(...)))
if ("also_single_tested" %in% names(dots)) { if ("also_single_tested" %in% names(dots)) {
stop("`also_single_tested` was replaced by `only_all_tested`. Please read Details in the help page (`?proportion`) as this may have a considerable impact on your analysis.", call. = FALSE) stop("`also_single_tested` was replaced by `only_all_tested`. Please read Details in the help page (`?proportion`) as this may have a considerable impact on your analysis.", call. = FALSE)

10
R/zzz.R
View File

@ -20,9 +20,6 @@
# ==================================================================== # # ==================================================================== #
.onLoad <- function(libname, pkgname) { .onLoad <- function(libname, pkgname) {
# get new functions not available in older versions of R
backports::import(pkgname)
assign(x = "MO_lookup", assign(x = "MO_lookup",
value = create_MO_lookup(), value = create_MO_lookup(),
envir = asNamespace("AMR")) envir = asNamespace("AMR"))
@ -34,7 +31,6 @@
assign(x = "mo_codes_v0.5.0", assign(x = "mo_codes_v0.5.0",
value = make_trans_tbl(), value = make_trans_tbl(),
envir = asNamespace("AMR")) envir = asNamespace("AMR"))
} }
# maybe add survey later: "https://www.surveymonkey.com/r/AMR_for_R" # maybe add survey later: "https://www.surveymonkey.com/r/AMR_for_R"
@ -55,13 +51,13 @@ create_MO_lookup <- function() {
MO_lookup$subspecies))) MO_lookup$subspecies)))
MO_lookup[MO_lookup$genus == "" | grepl("^[(]unknown ", MO_lookup$fullname), "fullname_lower"] <- tolower(trimws(MO_lookup[MO_lookup$genus == "" | grepl("^[(]unknown ", MO_lookup$fullname), MO_lookup[MO_lookup$genus == "" | grepl("^[(]unknown ", MO_lookup$fullname), "fullname_lower"] <- tolower(trimws(MO_lookup[MO_lookup$genus == "" | grepl("^[(]unknown ", MO_lookup$fullname),
"fullname"])) "fullname"]))
MO_lookup$fullname_lower <- gsub("[^.a-z0-9/ \\-]+", "",MO_lookup$fullname_lower) MO_lookup$fullname_lower <- gsub("[^.a-z0-9/ \\-]+", "", MO_lookup$fullname_lower)
# add a column with only "e coli" like combinations # add a column with only "e coli" like combinations
MO_lookup$g_species <- gsub("^([a-z])[a-z]+ ([a-z]+) ?.*", "\\1 \\2", MO_lookup$fullname_lower) MO_lookup$g_species <- gsub("^([a-z])[a-z]+ ([a-z]+) ?.*", "\\1 \\2", MO_lookup$fullname_lower)
# so arrange data on prevalence first, then kingdom, then full name # so arrange data on prevalence first, then kingdom, then full name
MO_lookup[order(MO_lookup$prevalence, MO_lookup$kingdom_index, MO_lookup$fullname_lower),] MO_lookup[order(MO_lookup$prevalence, MO_lookup$kingdom_index, MO_lookup$fullname_lower), ]
} }
create_MO.old_lookup <- function() { create_MO.old_lookup <- function() {
@ -75,7 +71,7 @@ create_MO.old_lookup <- function() {
MO.old_lookup$g_species <- gsub("^([a-z])[a-z]+ ([a-z]+) ?.*", "\\1 \\2", MO.old_lookup$fullname_lower) MO.old_lookup$g_species <- gsub("^([a-z])[a-z]+ ([a-z]+) ?.*", "\\1 \\2", MO.old_lookup$fullname_lower)
# so arrange data on prevalence first, then full name # so arrange data on prevalence first, then full name
MO.old_lookup[order(MO.old_lookup$prevalence, MO.old_lookup$fullname_lower),] MO.old_lookup[order(MO.old_lookup$prevalence, MO.old_lookup$fullname_lower), ]
} }
make_trans_tbl <- function() { make_trans_tbl <- function() {

View File

@ -81,7 +81,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="https://msberends.gitlab.io/AMR/index.html">AMR (for R)</a> <a class="navbar-link" href="https://msberends.gitlab.io/AMR/index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9011</span>
</span> </span>
</div> </div>

View File

@ -81,7 +81,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a> <a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9011</span>
</span> </span>
</div> </div>

View File

@ -81,7 +81,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9011</span>
</span> </span>
</div> </div>

View File

@ -81,7 +81,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a> <a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9011</span>
</span> </span>
</div> </div>

View File

@ -43,7 +43,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a> <a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9011</span>
</span> </span>
</div> </div>
@ -198,12 +198,12 @@ A methods paper about this package has been preprinted at bioRxiv (DOI: 10.1101/
<h3 class="hasAnchor"> <h3 class="hasAnchor">
<a href="#what-is-amr-for-r" class="anchor"></a>What is <code>AMR</code> (for R)?</h3> <a href="#what-is-amr-for-r" class="anchor"></a>What is <code>AMR</code> (for R)?</h3>
<p><em>(<help title="Too Long, Didn't Read">TLDR</help> - to find out how to conduct AMR analysis, please <a href="./articles/AMR.html">continue reading here to get started</a>.</em></p> <p><em>(<help title="Too Long, Didn't Read">TLDR</help> - to find out how to conduct AMR analysis, please <a href="./articles/AMR.html">continue reading here to get started</a>.</em></p>
<p><code>AMR</code> is a free and open-source <a href="https://www.r-project.org">R package</a> to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial data and properties, by using evidence-based methods. <strong>Our aim is to provide a standard</strong> for clean and reproducible antimicrobial resistance data analysis, that can therefore empower epidemiological analyses to continuously enable surveillance and treatment evaluation in any setting.</p> <p><code>AMR</code> is a free, open-source and independent <a href="https://www.r-project.org">R package</a> to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial data and properties, by using evidence-based methods. <strong>Our aim is to provide a standard</strong> for clean and reproducible antimicrobial resistance data analysis, that can therefore empower epidemiological analyses to continuously enable surveillance and treatment evaluation in any setting.</p>
<p>After installing this package, R knows <a href="./reference/microorganisms.html"><strong>~70,000 distinct microbial species</strong></a> and all <a href="./reference/antibiotics.html"><strong>~550 antibiotic, antimycotic and antiviral drugs</strong></a> by name and code (including ATC, LOINC and SNOMED CT), and knows all about valid R/SI and MIC values. It supports any data format, including WHONET/EARS-Net data.</p> <p>After installing this package, R knows <a href="./reference/microorganisms.html"><strong>~70,000 distinct microbial species</strong></a> and all <a href="./reference/antibiotics.html"><strong>~550 antibiotic, antimycotic and antiviral drugs</strong></a> by name and code (including ATC, LOINC and SNOMED CT), and knows all about valid R/SI and MIC values. It supports any data format, including WHONET/EARS-Net data.</p>
<p>We created this package for both routine data analysis and academic research (as part of our PhD theses) at the Faculty of Medical Sciences of the University of Groningen, the Netherlands, and the Medical Microbiology &amp; Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG). This R package is <a href="./news">actively maintained</a> and is free software (see <a href="#copyright">Copyright</a>).</p> <p>We created this package for both routine data analysis and academic research (as part of our PhD theses) at the Faculty of Medical Sciences of the University of Groningen, the Netherlands, and the Medical Microbiology &amp; Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG). This R package is <a href="./news">actively maintained</a> and is free software (see <a href="#copyright">Copyright</a>).</p>
<div class="main-content"> <div class="main-content">
<p> <p>
<a href="./countries_large.png" target="_blank"><img src="./countries.png" class="countries_map"></a> <strong>Used in more than 100 countries</strong><br> Since its first public release in early 2018, this package has been downloaded from more than 100 countries <small>(as of March 2020, <a href="https://cran-logs.rstudio.com" target="_blank">CRAN logs</a>)</small>. Click the map to enlarge, to see the names of the countries. <a href="./countries_large.png" target="_blank"><img src="./countries.png" class="countries_map"></a> <strong>Used in more than 100 countries</strong><br> Since its first public release in early 2018, this package has been downloaded from more than 100 countries <small>(source: <a href="https://cran-logs.rstudio.com" target="_blank">CRAN logs</a>)</small>. Click the map to enlarge, to see the names of the countries.
</p> </p>
<br><br> <br><br>
</div> </div>

View File

@ -81,7 +81,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9011</span>
</span> </span>
</div> </div>
@ -229,9 +229,9 @@
<small>Source: <a href='https://gitlab.com/msberends/AMR/blob/master/NEWS.md'><code>NEWS.md</code></a></small> <small>Source: <a href='https://gitlab.com/msberends/AMR/blob/master/NEWS.md'><code>NEWS.md</code></a></small>
</div> </div>
<div id="amr-1-1-0-9010" class="section level1"> <div id="amr-1-1-0-9011" class="section level1">
<h1 class="page-header" data-toc-text="1.1.0.9010"> <h1 class="page-header" data-toc-text="1.1.0.9011">
<a href="#amr-1-1-0-9010" class="anchor"></a>AMR 1.1.0.9010<small> Unreleased </small> <a href="#amr-1-1-0-9011" class="anchor"></a>AMR 1.1.0.9011<small> Unreleased </small>
</h1> </h1>
<div id="last-updated-18-may-2020" class="section level2"> <div id="last-updated-18-may-2020" class="section level2">
<h2 class="hasAnchor"> <h2 class="hasAnchor">
@ -260,7 +260,7 @@
<h3 class="hasAnchor"> <h3 class="hasAnchor">
<a href="#other" class="anchor"></a>Other</h3> <a href="#other" class="anchor"></a>Other</h3>
<ul> <ul>
<li>Removed dependency on <strong>all</strong> packages that were needed for the <code>AMR</code> package to work properly: <code>crayon</code>, <code>data.table</code>, <code>dplyr</code>, <code>ggplot2</code>, <code>R6</code>, <code>rlang</code> and <code>tidyr</code>. This is a major code change, but will probably not be noticeable by users. Making this package independent on especially the tidyverse (packages <code>dplyr</code>, <code>ggplot2</code> and <code>tidyr</code>) tremendously increases sustainability on the long term, since tidyverse functions change quite often. Most of our functions are replaced with versions that only rely on base R, which keeps this package fully functional for many years to come, without requiring a lot of maintenance to keep up with other packages anymore. The only dependencies that remained are for extending methods of other packages, like <code>pillar</code> and <code>vctrs</code> for printing and working with tibbles using our classes <code>mo</code> and <code>ab</code>.</li> <li>Removed dependency on <strong>all</strong> packages that were needed for the <code>AMR</code> package to work properly: <code>backports</code>, <code>crayon</code>, <code>data.table</code>, <code>dplyr</code>, <code>ggplot2</code>, <code>R6</code>, <code>rlang</code> and <code>tidyr</code>. This is a major code change, but will probably not be noticeable by users. Making this package independent on especially the tidyverse (packages <code>dplyr</code>, <code>ggplot2</code> and <code>tidyr</code>) tremendously increases sustainability on the long term, since tidyverse functions change quite often. Most of our functions are replaced with versions that only rely on base R, which keeps this package fully functional for many years to come, without requiring a lot of maintenance to keep up with other packages anymore. The only dependencies that remained are for extending methods of other packages, like <code>pillar</code> and <code>vctrs</code> for printing and working with tibbles using our classes <code>mo</code> and <code>ab</code>.</li>
<li>Removed function <code>read.4d()</code>, that was only useful for reading from an old test database.</li> <li>Removed function <code>read.4d()</code>, that was only useful for reading from an old test database.</li>
</ul> </ul>
</div> </div>

View File

@ -10,7 +10,7 @@ articles:
WHONET: WHONET.html WHONET: WHONET.html
benchmarks: benchmarks.html benchmarks: benchmarks.html
resistance_predict: resistance_predict.html resistance_predict: resistance_predict.html
last_built: 2020-05-18T09:07Z last_built: 2020-05-18T11:59Z
urls: urls:
reference: https://msberends.gitlab.io/AMR/reference reference: https://msberends.gitlab.io/AMR/reference
article: https://msberends.gitlab.io/AMR/articles article: https://msberends.gitlab.io/AMR/articles

View File

@ -81,7 +81,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9010</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.1.0.9011</span>
</span> </span>
</div> </div>

View File

@ -8,7 +8,7 @@
*(<help title="Too Long, Didn't Read">TLDR</help> - to find out how to conduct AMR analysis, please [continue reading here to get started](./articles/AMR.html).* *(<help title="Too Long, Didn't Read">TLDR</help> - to find out how to conduct AMR analysis, please [continue reading here to get started](./articles/AMR.html).*
`AMR` is a free and open-source [R package](https://www.r-project.org) to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial data and properties, by using evidence-based methods. **Our aim is to provide a standard** for clean and reproducible antimicrobial resistance data analysis, that can therefore empower epidemiological analyses to continuously enable surveillance and treatment evaluation in any setting. `AMR` is a free, open-source and independent [R package](https://www.r-project.org) to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial data and properties, by using evidence-based methods. **Our aim is to provide a standard** for clean and reproducible antimicrobial resistance data analysis, that can therefore empower epidemiological analyses to continuously enable surveillance and treatment evaluation in any setting.
After installing this package, R knows [**~70,000 distinct microbial species**](./reference/microorganisms.html) and all [**~550 antibiotic, antimycotic and antiviral drugs**](./reference/antibiotics.html) by name and code (including ATC, LOINC and SNOMED CT), and knows all about valid R/SI and MIC values. It supports any data format, including WHONET/EARS-Net data. After installing this package, R knows [**~70,000 distinct microbial species**](./reference/microorganisms.html) and all [**~550 antibiotic, antimycotic and antiviral drugs**](./reference/antibiotics.html) by name and code (including ATC, LOINC and SNOMED CT), and knows all about valid R/SI and MIC values. It supports any data format, including WHONET/EARS-Net data.
@ -18,7 +18,7 @@ We created this package for both routine data analysis and academic research (as
<p> <p>
<a href="./countries_large.png" target="_blank"><img src="./countries.png" class="countries_map"></a> <a href="./countries_large.png" target="_blank"><img src="./countries.png" class="countries_map"></a>
<strong>Used in more than 100 countries</strong><br> <strong>Used in more than 100 countries</strong><br>
Since its first public release in early 2018, this package has been downloaded from more than 100 countries <small>(as of March 2020, <a href="https://cran-logs.rstudio.com" target="_blank">CRAN logs</a>)</small>. Click the map to enlarge, to see the names of the countries.</p><br><br> Since its first public release in early 2018, this package has been downloaded from more than 100 countries <small>(source: <a href="https://cran-logs.rstudio.com" target="_blank">CRAN logs</a>)</small>. Click the map to enlarge, to see the names of the countries.</p><br><br>
</div> </div>
#### Partners #### Partners