diff --git a/DESCRIPTION b/DESCRIPTION index 034fab43..bb38c078 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 1.2.0.9015 -Date: 2020-06-25 +Version: 1.2.0.9016 +Date: 2020-06-26 Title: Antimicrobial Resistance Analysis Authors@R: c( person(role = c("aut", "cre"), diff --git a/NEWS.md b/NEWS.md index 778e1a17..3094fc49 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,5 @@ -# AMR 1.2.0.9015 -## Last updated: 25-Jun-2020 +# AMR 1.2.0.9016 +## Last updated: 26-Jun-2020 ### New * Function `ab_from_text()` to retrieve antimicrobial drugs from clinical texts in e.g. health care records, which also corrects for misspelling since it uses `as.ab()` internally: @@ -31,7 +31,7 @@ * Added antibiotics code "FOX1" for cefoxitin screening (abbreviation "cfsc") to the `antibiotics` data set ### Changed -* Fixed a bug for using `susceptibility` or `resistance()` outside `summarise()` +* Using unexisting columns in all `count_*()`, `proportion_*()`, `susceptibility()` and `resistance()` functions wil now return an error instead of dropping them silently * Fixed a bug where `eucast_rules()` would not work on a tibble when the `tibble` or `dplyr` package was loaded * All `*_join_microorganisms()` functions and `bug_drug_combinations()` now return the original data class (e.g. `tibble`s and `data.table`s) * Fixed a bug where `as.ab()` would return an error on invalid input values diff --git a/R/aa_helper_functions.R b/R/aa_helper_functions.R index 94d81b5a..6516566e 100755 --- a/R/aa_helper_functions.R +++ b/R/aa_helper_functions.R @@ -202,33 +202,33 @@ import_fn <- function(name, pkg) { } stop_if <- function(expr, ..., call = TRUE) { - msg <- paste0(c(...), collapse = "") - if (!isFALSE(call)) { - if (isTRUE(call)) { - call <- as.character(sys.call(-1)[1]) - } else { - # so you can go back more than 1 call, as used in rsi_calc(), that now throws a reference to e.g. n_rsi() - call <- as.character(sys.call(call)[1]) - } - msg <- paste0("in ", call, "(): ", msg) - } if (isTRUE(expr)) { + msg <- paste0(c(...), collapse = "") + if (!isFALSE(call)) { + if (isTRUE(call)) { + call <- as.character(sys.call(-1)[1]) + } else { + # so you can go back more than 1 call, as used in rsi_calc(), that now throws a reference to e.g. n_rsi() + call <- as.character(sys.call(call)[1]) + } + msg <- paste0("in ", call, "(): ", msg) + } stop(msg, call. = FALSE) } } stop_ifnot <- function(expr, ..., call = TRUE) { - msg <- paste0(c(...), collapse = "") - if (!isFALSE(call)) { - if (isTRUE(call)) { - call <- as.character(sys.call(-1)[1]) - } else { - # so you can go back more than 1 call, as used in rsi_calc(), that now throws a reference to e.g. n_rsi() - call <- as.character(sys.call(call)[1]) - } - msg <- paste0("in ", call, "(): ", msg) - } if (!isTRUE(expr)) { + msg <- paste0(c(...), collapse = "") + if (!isFALSE(call)) { + if (isTRUE(call)) { + call <- as.character(sys.call(-1)[1]) + } else { + # so you can go back more than 1 call, as used in rsi_calc(), that now throws a reference to e.g. n_rsi() + call <- as.character(sys.call(call)[1]) + } + msg <- paste0("in ", call, "(): ", msg) + } stop(msg, call. = FALSE) } } diff --git a/R/ab.R b/R/ab.R index 31da9d82..c1efbcc0 100755 --- a/R/ab.R +++ b/R/ab.R @@ -209,7 +209,7 @@ as.ab <- function(x, ...) { # correct for digital reading text (OCR) x_spelling <- gsub("[NRD]", "[NRD]", x_spelling) } - + # try if name starts with it found <- antibiotics[which(antibiotics$name %like% paste0("^", x_spelling)), ]$ab if (length(found) > 0) { diff --git a/R/ab_from_text.R b/R/ab_from_text.R index c5e39598..5d6d7275 100644 --- a/R/ab_from_text.R +++ b/R/ab_from_text.R @@ -58,12 +58,17 @@ ab_from_text <- function(text, collapse = NULL, translate_ab = "name", ...) { } text_split <- unlist(strsplit(text, "[ ;.,:/\\|-]")) - result <- as.ab(unique(c(text_split[grep(to_regex(abbr), text_split)], - text_split[grep(to_regex(names), text_split)], - # regular expression must not be too long, so split synonyms in two: - text_split[grep(to_regex(synonyms[c(1:0.5 * length(synonyms))]), text_split)], - text_split[grep(to_regex(synonyms[c(0.5 * length(synonyms):length(synonyms))]), text_split)])), - ...) + result <- suppressWarnings( + as.ab(unique(c(text_split[grep(to_regex(abbr), text_split)], + text_split[grep(to_regex(names), text_split)], + # regular expression must not be too long, so split synonyms in two: + text_split[grep(to_regex(synonyms[c(1:0.5 * length(synonyms))]), text_split)], + text_split[grep(to_regex(synonyms[c(0.5 * length(synonyms):length(synonyms))]), text_split)])), + ...)) + result <- result[!is.na(result)] + if (length(result) == 0) { + result <- as.ab(NA) + } translate_ab <- get_translate_ab(translate_ab) if (!isFALSE(translate_ab)) { result <- ab_property(result, property = translate_ab) diff --git a/R/mic.R b/R/mic.R index 1715b87d..14d95c63 100755 --- a/R/mic.R +++ b/R/mic.R @@ -130,7 +130,8 @@ as.mic <- function(x, na.rm = FALSE) { } all_valid_mics <- function(x) { - x_mic <- suppressWarnings(as.mic(x[!is.na(x)])) + x_mic <- tryCatch(suppressWarnings(as.mic(x[!is.na(x)])), + error = function(e) NA) !any(is.na(x_mic)) & !all(is.na(x)) } diff --git a/R/rsi.R b/R/rsi.R index 16050fc5..6ff21c6c 100755 --- a/R/rsi.R +++ b/R/rsi.R @@ -166,10 +166,10 @@ as.rsi.default <- function(x, ...) { } } - x <- x %>% unlist() + x <- as.character(unlist(x)) x.bak <- x - na_before <- x[is.na(x) | x == ""] %>% length() + na_before <- length(x[is.na(x) | x == ""]) # remove all spaces x <- gsub(" +", "", x) # remove all MIC-like values: numbers, operators and periods @@ -188,7 +188,7 @@ as.rsi.default <- function(x, ...) { x <- gsub("^I+$", "I", x) x <- gsub("^R+$", "R", x) x[!x %in% c("S", "I", "R")] <- NA - na_after <- x[is.na(x) | x == ""] %>% length() + na_after <- length(x[is.na(x) | x == ""]) if (!isFALSE(list(...)$warn)) { # so as.rsi(..., warn = FALSE) will never throw a warning if (na_before != na_after) { diff --git a/R/rsi_calc.R b/R/rsi_calc.R index ee1ada71..9de3fdcc 100755 --- a/R/rsi_calc.R +++ b/R/rsi_calc.R @@ -48,18 +48,23 @@ rsi_calc <- function(..., "Please read Details in the help page (`?proportion`) as this may have a considerable impact on your analysis.", call = -2) ndots <- length(dots) - if ("data.frame" %in% class(dots_df)) { + if (is.data.frame(dots_df)) { # data.frame passed with other columns, like: example_isolates %>% proportion_S(AMC, GEN) dots <- as.character(dots) - dots <- dots[dots != "."] + # remove first element, it's the data.frame + if (length(dots) == 1) { + dots <- character(0) + } else { + dots <- dots[2:length(dots)] + } if (length(dots) == 0 | all(dots == "df")) { # for complete data.frames, like example_isolates %>% select(AMC, GEN) %>% proportion_S() # and the old rsi function, which has "df" as name of the first parameter x <- dots_df - } else if (length(dots) == 1 | all(!dots %in% colnames(dots_df))) { - x <- dots_df } else { - x <- dots_df[, dots[dots %in% colnames(dots_df)], drop = FALSE] + dots_not_exist <- dots[!dots %in% colnames(dots_df)] + stop_if(length(dots_not_exist) > 0, "column(s) not found: ", paste0("'", dots_not_exist, "'", collapse = ", "), call = -2) + x <- dots_df[, dots, drop = FALSE] } } else if (ndots == 1) { # only 1 variable passed (can also be data.frame), like: proportion_S(example_isolates$AMC) and example_isolates$AMC %>% proportion_S() diff --git a/docs/404.html b/docs/404.html index 20e4bb6f..eca69945 100644 --- a/docs/404.html +++ b/docs/404.html @@ -81,7 +81,7 @@ AMR (for R) - 1.2.0.9015 + 1.2.0.9016 diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index 7f22924c..ad80d18f 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -81,7 +81,7 @@ AMR (for R) - 1.2.0.9015 + 1.2.0.9016 diff --git a/docs/articles/index.html b/docs/articles/index.html index 9872d93b..346ec7c4 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.2.0.9015 + 1.2.0.9016 diff --git a/docs/authors.html b/docs/authors.html index d050bcd0..b59291f2 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -81,7 +81,7 @@ AMR (for R) - 1.2.0.9015 + 1.2.0.9016 diff --git a/docs/index.html b/docs/index.html index 81b9a28b..87b69ddb 100644 --- a/docs/index.html +++ b/docs/index.html @@ -43,7 +43,7 @@ AMR (for R) - 1.2.0.9015 + 1.2.0.9016 diff --git a/docs/news/index.html b/docs/news/index.html index b214d5a4..452737c1 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.2.0.9015 + 1.2.0.9016 @@ -229,13 +229,13 @@ Source: NEWS.md -
-

-AMR 1.2.0.9015 Unreleased +
+

+AMR 1.2.0.9016 Unreleased

-
+

-Last updated: 25-Jun-2020 +Last updated: 26-Jun-2020

@@ -274,8 +274,7 @@

Changed

    -
  • Fixed a bug for using susceptibility or resistance() outside summarise() -
  • +
  • Using unexisting columns in all count_*(), proportion_*(), susceptibility() and resistance() functions wil now return an error instead of dropping them silently
  • Fixed a bug where eucast_rules() would not work on a tibble when the tibble or dplyr package was loaded
  • All *_join_microorganisms() functions and bug_drug_combinations() now return the original data class (e.g. tibbles and data.tables)
  • Fixed a bug where as.ab() would return an error on invalid input values
  • diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index 83bd9533..05ec846d 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -10,7 +10,7 @@ articles: WHONET: WHONET.html benchmarks: benchmarks.html resistance_predict: resistance_predict.html -last_built: 2020-06-25T17:20Z +last_built: 2020-06-26T08:20Z urls: reference: https://msberends.gitlab.io/AMR/reference article: https://msberends.gitlab.io/AMR/articles diff --git a/docs/reference/ab_from_text.html b/docs/reference/ab_from_text.html index 6cac6cf6..32d59125 100644 --- a/docs/reference/ab_from_text.html +++ b/docs/reference/ab_from_text.html @@ -82,7 +82,7 @@ AMR (for R) - 1.2.0.9014 + 1.2.0.9016
diff --git a/docs/reference/as.ab.html b/docs/reference/as.ab.html index 31309376..37bf95d6 100644 --- a/docs/reference/as.ab.html +++ b/docs/reference/as.ab.html @@ -82,7 +82,7 @@ AMR (for R) - 1.2.0.9014 + 1.2.0.9016
diff --git a/docs/reference/count.html b/docs/reference/count.html index b077baca..f70225a2 100644 --- a/docs/reference/count.html +++ b/docs/reference/count.html @@ -83,7 +83,7 @@ count_resistant() should be used to count resistant isolates, count_susceptible( AMR (for R) - 1.2.0.9014 + 1.2.0.9016
diff --git a/docs/reference/ggplot_rsi.html b/docs/reference/ggplot_rsi.html index 20599a41..4b4849ba 100644 --- a/docs/reference/ggplot_rsi.html +++ b/docs/reference/ggplot_rsi.html @@ -82,7 +82,7 @@ AMR (for R) - 1.2.0.9014 + 1.2.0.9016
diff --git a/docs/reference/index.html b/docs/reference/index.html index 3337d7f8..e1d2603d 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.2.0.9015 + 1.2.0.9016

diff --git a/docs/reference/proportion.html b/docs/reference/proportion.html index 79f5d734..06312d91 100644 --- a/docs/reference/proportion.html +++ b/docs/reference/proportion.html @@ -83,7 +83,7 @@ resistance() should be used to calculate resistance, susceptibility() should be AMR (for R) - 1.2.0.9014 + 1.2.0.9016