From 1d982a82b449aa3359822b64001a5dd76743f797 Mon Sep 17 00:00:00 2001 From: "Matthijs S. Berends" Date: Thu, 24 Sep 2020 12:38:13 +0200 Subject: [PATCH] (v1.3.0.9028) eucast fix --- DESCRIPTION | 2 +- NEWS.md | 3 +- R/eucast_rules.R | 33 +++++++++---- R/rsi.R | 60 ++++++++++++++--------- docs/404.html | 2 +- docs/LICENSE-text.html | 2 +- docs/articles/datasets.html | 6 +-- docs/articles/index.html | 2 +- docs/authors.html | 2 +- docs/index.html | 2 +- docs/news/index.html | 47 +++++++++--------- docs/pkgdown.yml | 2 +- docs/reference/antibiotics.html | 2 +- docs/reference/as.mo.html | 2 +- docs/reference/as.rsi.html | 14 +++--- docs/reference/bug_drug_combinations.html | 2 +- docs/reference/eucast_rules.html | 2 +- docs/reference/index.html | 2 +- docs/reference/intrinsic_resistant.html | 2 +- docs/reference/mdro.html | 2 +- docs/reference/mo_matching_score.html | 2 +- docs/reference/mo_source.html | 2 +- docs/survey.html | 2 +- man/as.rsi.Rd | 12 +++-- 24 files changed, 121 insertions(+), 88 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 994846b9..2bcfe90b 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: AMR -Version: 1.3.0.9027 +Version: 1.3.0.9028 Date: 2020-09-24 Title: Antimicrobial Resistance Analysis Authors@R: c( diff --git a/NEWS.md b/NEWS.md index 1867b550..929b7b65 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# AMR 1.3.0.9027 +# AMR 1.3.0.9028 ## Last updated: 24 September 2020 Note: some changes in this version were suggested by anonymous reviewers from the journal we submitted our manuscipt to. We are those reviewers very grateful for going through our code so thoroughly! @@ -32,6 +32,7 @@ Note: some changes in this version were suggested by anonymous reviewers from th 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. * Added parameter 'add_intrinsic_resistance' (defaults to `FALSE`), that considers intrinsic resistance according to EUCAST * Fixed a bug where in EUCAST rules the breakpoint for R would be interpreted as ">=" while this should have been "<" diff --git a/R/eucast_rules.R b/R/eucast_rules.R index 0ee47488..9266cb7f 100755 --- a/R/eucast_rules.R +++ b/R/eucast_rules.R @@ -136,6 +136,11 @@ eucast_rules <- function(x, version_expertrules = 3.2, ...) { + x_deparsed <- deparse(substitute(x)) + if (!x_deparsed %like% "[a-z]") { + x_deparsed <- "your_data" + } + check_dataset_integrity() version_breakpoints <- as.double(version_breakpoints) @@ -152,12 +157,12 @@ eucast_rules <- function(x, rules <- getOption("AMR.eucast_rules") } - if (verbose == TRUE & info == TRUE) { + if (interactive() & verbose == TRUE & info == TRUE) { txt <- paste0("WARNING: In Verbose mode, the eucast_rules() function does not apply rules to the data, but instead returns a data set in logbook form with extensive info about which rows and columns would be effected and in which way.", "\n\nThis may overwrite your existing data if you use e.g.:", "\ndata <- eucast_rules(data, verbose = TRUE)\n\nDo you want to continue?") showQuestion <- import_fn("showQuestion", "rstudioapi", error_on_fail = FALSE) - if (!is.null(showQuestion) & interactive()) { + if (!is.null(showQuestion)) { q_continue <- showQuestion("Using verbose = TRUE with eucast_rules()", txt) } else { q_continue <- utils::menu(choices = c("OK", "Cancel"), graphics = FALSE, title = txt) @@ -504,6 +509,7 @@ eucast_rules <- function(x, paste(collapse = ", ") x <- gsub("_", " ", x, fixed = TRUE) x <- gsub("except CAZ", paste("except", ab_name("CAZ", language = NULL, tolower = TRUE)), x, fixed = TRUE) + x <- gsub("cephalosporins (1st|2nd|3rd|4th|5th)", "cephalosporins (\\1 gen.)", x) x } format_antibiotic_names <- function(ab_names, ab_results) { @@ -881,9 +887,13 @@ eucast_rules <- function(x, rownames(verbose_info) <- NULL affected <- x.bak[which(x.bak$`.rowid` %in% x$`.rowid`), , drop = FALSE] rows_affected <- as.integer(rownames(affected)) - verbose_info <- data.frame(row = rows_affected, rowid = affected[, ".rowid", drop = TRUE]) %pm>% - pm_left_join(verbose_info, by = "rowid") %pm>% + verbose_info <- verbose_info %pm>% + pm_left_join(data.frame(row = rows_affected, + rowid = affected[, ".rowid", drop = TRUE], + stringsAsFactors = FALSE), + by = "rowid") %pm>% pm_select(-rowid) %pm>% + pm_select(row, pm_everything()) %pm>% pm_filter(!is.na(new)) %pm>% pm_arrange(row, rule_group, rule_name, col) @@ -919,7 +929,7 @@ eucast_rules <- function(x, pm_count(new, name = "n") cat(paste(" -", paste0(formatnr(added_summary$n), " test result", ifelse(added_summary$n > 1, "s", ""), - " added as ", added_summary$new), collapse = "\n")) + " added as ", paste0('"', added_summary$new, '"')), collapse = "\n")) } # print changed values @@ -942,7 +952,7 @@ eucast_rules <- function(x, pm_count(old, new, name = "n") cat(paste(" -", paste0(formatnr(changed_summary$n), " test result", ifelse(changed_summary$n > 1, "s", ""), " changed from ", - changed_summary$old, " to ", changed_summary$new), collapse = "\n")) + paste0('"', changed_summary$old, '"'), " to ", paste0('"', changed_summary$new, '"')), collapse = "\n")) cat("\n") } @@ -955,9 +965,12 @@ eucast_rules <- function(x, } } + if (isTRUE(warn_lacking_rsi_class)) { - warning("Not all columns with antimicrobial results are of class .\n", - "Transform eligible columns to class on beforehand: your_data %pm>% mutate_if(is.rsi.eligible, as.rsi)", + unique_cols <- colnames(x.bak)[colnames(x.bak) %in% verbose_info$col] + warning("Not all columns with antimicrobial results are of class . Transform them on beforehand, with e.g.:\n", + " ", x_deparsed, " %>% mutate_if(is.rsi.eligible, as.rsi)\n", + " ", x_deparsed, " %>% as.rsi(", unique_cols[1], ":", unique_cols[length(unique_cols)], ")", call. = FALSE) } @@ -1010,7 +1023,7 @@ edit_rsi <- function(x, if (length(rows) > 0 & length(cols) > 0) { new_edits <- x if (any(!sapply(x[, cols, drop = FALSE], is.rsi), na.rm = TRUE)) { - track_changes$warn <- TRUE + track_changes$rsi_warn <- TRUE } tryCatch( # insert into original table @@ -1044,7 +1057,7 @@ edit_rsi <- function(x, ) track_changes$output <- new_edits - if (isTRUE(info) && isFALSE(all.equal(x, track_changes$output))) { + if (isTRUE(info) && !isTRUE(all.equal(x, track_changes$output))) { get_original_rows <- function(rowids) { as.integer(rownames(original_data[which(original_data$.rowid %in% rowids), , drop = FALSE])) } diff --git a/R/rsi.R b/R/rsi.R index 97954325..67dc2ad8 100755 --- a/R/rsi.R +++ b/R/rsi.R @@ -33,7 +33,7 @@ #' @param conserve_capped_values a logical to indicate that MIC values starting with `">"` (but not `">="`) must always return "R" , and that MIC values starting with `"<"` (but not `"<="`) must always return "S" #' @param add_intrinsic_resistance *(only useful when using a EUCAST guideline)* a logical to indicate whether intrinsic antibiotic resistance must also be considered for applicable bug-drug combinations, meaning that e.g. ampicillin will always return "R" in *Klebsiella* species. Determination is based on the [intrinsic_resistant] data set, that itself is based on 'EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes', version `r EUCAST_VERSION_EXPERT_RULES`. #' @param threshold maximum fraction of invalid antimicrobial interpretations of `x`, please see *Examples* -#' @param ... parameters passed on to methods +#' @param ... for using on a [data.frame]: names of columns to apply [as.rsi()] on (supports tidy selection like `AMX:VAN`). Otherwise: parameters passed on to methods. #' @details #' ## How it works #' @@ -86,7 +86,7 @@ #' A microorganism is categorised as *Susceptible, Increased exposure* when there is a high likelihood of therapeutic success because exposure to the agent is increased by adjusting the dosing regimen or by its concentration at the site of infection. #' #' This AMR package honours this new insight. Use [susceptibility()] (equal to [proportion_SI()]) to determine antimicrobial susceptibility and [count_susceptible()] (equal to [count_SI()]) to count susceptible isolates. -#' @return Ordered factor with new class [`rsi`] +#' @return Ordered [factor] with new class [`rsi`] #' @aliases rsi #' @export #' @seealso [as.mic()], [as.disk()], [as.mo()] @@ -150,7 +150,7 @@ #' #' as.rsi(c("S", "I", "R", "A", "B", "C")) #' as.rsi("<= 0.002; S") # will return "S" -#' + #' rsi_data <- as.rsi(c(rep("S", 474), rep("I", 36), rep("R", 370))) #' is.rsi(rsi_data) #' plot(rsi_data) # for percentages @@ -160,6 +160,9 @@ #' library(dplyr) #' example_isolates %>% #' mutate_at(vars(PEN:RIF), as.rsi) +#' # same: +#' example_isolates %>% +#' as.rsi(PEN:RIF) #' #' # fastest way to transform all columns with already valid AMR results to class `rsi`: #' example_isolates %>% @@ -418,13 +421,14 @@ as.rsi.disk <- function(x, #' @rdname as.rsi #' @export -as.rsi.data.frame <- function(x, +as.rsi.data.frame <- function(x, + ..., col_mo = NULL, guideline = "EUCAST", uti = NULL, conserve_capped_values = FALSE, - add_intrinsic_resistance = FALSE, - ...) { + add_intrinsic_resistance = FALSE) { + # try to find columns based on type # -- mo if (is.null(col_mo)) { @@ -471,38 +475,46 @@ as.rsi.data.frame <- function(x, } i <- 0 + sel <- colnames(pm_select(x, ...)) ab_cols <- colnames(x)[sapply(x, function(y) { i <<- i + 1 check <- is.mic(y) | is.disk(y) ab <- colnames(x)[i] - ab_coerced <- suppressWarnings(as.ab(ab)) - if (is.na(ab_coerced)) { - # not even a valid AB code - return(FALSE) - } else if (!check & all_valid_mics(y)) { - message(font_blue(paste0("NOTE: Assuming column `", ab, "` (", - ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""), - ab_name(ab_coerced, tolower = TRUE), ") contains MIC values."))) - return(TRUE) - } else if (!check & all_valid_disks(y)) { - message(font_blue(paste0("NOTE: Assuming column `", ab, "` (", - ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""), - ab_name(ab_coerced, tolower = TRUE), ") contains disk zones."))) - return(TRUE) + if (length(sel) == 0 || (length(sel) > 0 && ab %in% sel)) { + ab_coerced <- suppressWarnings(as.ab(ab)) + if (is.na(ab_coerced) | !ab %in% sel) { + # not even a valid AB code + return(FALSE) + } else { + if (!check & all_valid_mics(y)) { + message(font_blue(paste0("NOTE: Assuming column `", ab, "` (", + ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""), + ab_name(ab_coerced, tolower = TRUE), ") contains MIC values."))) + } else if (!check & all_valid_disks(y)) { + message(font_blue(paste0("NOTE: Assuming column `", ab, "` (", + ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""), + ab_name(ab_coerced, tolower = TRUE), ") contains disk zones."))) + } else if (!is.rsi(y)) { + message(font_blue(paste0("NOTE: Assuming column `", ab, "` (", + ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""), + ab_name(ab_coerced, tolower = TRUE), ") must be cleaned to valid R/SI values."))) + } + return(TRUE) + } } else { - return(check) + return(FALSE) } })] stop_if(length(ab_cols) == 0, - "no columns with MIC values or disk zones found in this data set. Use as.mic() or as.disk() to transform antimicrobial columns.") - + "no columns with MIC values, disk zones or antibiotic column names found in this data set. Use as.mic() or as.disk() to transform antimicrobial columns.") # set type per column types <- character(length(ab_cols)) types[sapply(x[, ab_cols], is.mic)] <- "mic" types[types == "" & sapply(x[, ab_cols], all_valid_mics)] <- "mic" types[sapply(x[, ab_cols], is.disk)] <- "disk" types[types == "" & sapply(x[, ab_cols], all_valid_disks)] <- "disk" + types[types == "" & !sapply(x[, ab_cols], is.rsi)] <- "rsi" for (i in seq_len(length(ab_cols))) { if (types[i] == "mic") { @@ -518,6 +530,8 @@ as.rsi.data.frame <- function(x, ab = ab_cols[i], guideline = guideline, uti = uti) + } else if (types[i] == "rsi") { + x[, ab_cols[i]] <- as.rsi.default(x = x %pm>% pm_pull(ab_cols[i])) } } diff --git a/docs/404.html b/docs/404.html index d4d5565a..29394d05 100644 --- a/docs/404.html +++ b/docs/404.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9027 + 1.3.0.9028 diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index 82c39a18..c79279f3 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9027 + 1.3.0.9028 diff --git a/docs/articles/datasets.html b/docs/articles/datasets.html index f39f1e09..fd15fbf8 100644 --- a/docs/articles/datasets.html +++ b/docs/articles/datasets.html @@ -39,7 +39,7 @@ AMR (for R) - 1.3.0.9026 + 1.3.0.9028 @@ -494,7 +494,7 @@ If you are reading this page from within R, please Antibiotic agents

A data set with 455 rows and 14 columns, containing the following column names:
‘ab’, ‘atc’, ‘cid’, ‘name’, ‘group’, ‘atc_group1’, ‘atc_group2’, ‘abbreviations’, ‘synonyms’, ‘oral_ddd’, ‘oral_units’, ‘iv_ddd’, ‘iv_units’, ‘loinc’.

This data set is in R available as antibiotics, after you load the AMR package.

-

It was last updated on 20 September 2020 11:45:13 CEST. Find more info about the structure of this data set here.

+

It was last updated on 24 September 2020 00:50:35 CEST. Find more info about the structure of this data set here.

Direct download links:

  • Download as R file (31 kB)
    @@ -789,7 +789,7 @@ If you are reading this page from within R, please Intrinsic bacterial resistance

    A data set with 93,892 rows and 2 columns, containing the following column names:
    ‘microorganism’, ‘antibiotic’.

    This data set is in R available as intrinsic_resistant, after you load the AMR package.

    -

    It was last updated on 23 September 2020 23:42:04 CEST. Find more info about the structure of this data set here.

    +

    It was last updated on 24 September 2020 00:50:35 CEST. Find more info about the structure of this data set here.

    Direct download links:

    • Download as R file (67 kB)
      diff --git a/docs/articles/index.html b/docs/articles/index.html index 4dd9b0d2..3b74aec8 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9027 + 1.3.0.9028 diff --git a/docs/authors.html b/docs/authors.html index 8b9286c7..11bf5502 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9027 + 1.3.0.9028 diff --git a/docs/index.html b/docs/index.html index fa1d2f18..606b6bd3 100644 --- a/docs/index.html +++ b/docs/index.html @@ -43,7 +43,7 @@ AMR (for R) - 1.3.0.9027 + 1.3.0.9028 diff --git a/docs/news/index.html b/docs/news/index.html index 56732ef9..25cbdcc2 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9027 + 1.3.0.9028 @@ -236,9 +236,9 @@ Source: NEWS.md -
      -

      -AMR 1.3.0.9027 Unreleased +
      +

      +AMR 1.3.0.9028 Unreleased

      @@ -286,6 +286,7 @@ 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.

    • Added parameter ‘add_intrinsic_resistance’ (defaults to FALSE), that considers intrinsic resistance according to EUCAST

    • Fixed a bug where in EUCAST rules the breakpoint for R would be interpreted as “>=” while this should have been “<”

    • @@ -436,7 +437,7 @@

      Making this package independent of especially the tidyverse (e.g. packages dplyr and tidyr) tremendously increases sustainability on the long term, since tidyverse functions change quite often. Good for users, but hard for package maintainers. 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. Another upside it that this package can now be used with all versions of R since R-3.0.0 (April 2013). Our package is being used in settings where the resources are very limited. Fewer dependencies on newer software is helpful for such settings.

      Negative effects of this change are:

        -
      • Function freq() that was borrowed from the cleaner package was removed. Use cleaner::freq(), or run library("cleaner") before you use freq().
      • +
      • Function freq() that was borrowed from the cleaner package was removed. Use cleaner::freq(), or run library("cleaner") before you use freq().
      • Printing values of class mo or rsi in a tibble will no longer be in colour and printing rsi in a tibble will show the class <ord>, not <rsi> anymore. This is purely a visual effect.
      • All functions from the mo_* family (like mo_name() and mo_gramstain()) are noticeably slower when running on hundreds of thousands of rows.
      • For developers: classes mo and ab now both also inherit class character, to support any data transformation. This change invalidates code that checks for class length == 1.
      • @@ -773,7 +774,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/

        This is important, because a value like "testvalue" could never be understood by e.g. mo_name(), although the class would suggest a valid microbial code.

        -
      • Function freq() has moved to a new package, clean (CRAN link), since creating frequency tables actually does not fit the scope of this package. The freq() function still works, since it is re-exported from the clean package (which will be installed automatically upon updating this AMR package).

      • +
      • Function freq() has moved to a new package, clean (CRAN link), since creating frequency tables actually does not fit the scope of this package. The freq() function still works, since it is re-exported from the clean package (which will be installed automatically upon updating this AMR package).

      • Renamed data set septic_patients to example_isolates

      @@ -1042,7 +1043,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
    • The age() function gained a new parameter exact to determine ages with decimals
    • Removed deprecated functions guess_mo(), guess_atc(), EUCAST_rules(), interpretive_reading(), rsi()
    • -
    • Frequency tables (freq()): +
    • Frequency tables (freq()):
      • speed improvement for microbial IDs

      • fixed factor level names for R Markdown

      • @@ -1051,12 +1052,12 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/

        support for boxplots:

         septic_patients %>% 
        -  freq(age) %>% 
        +  freq(age) %>% 
           boxplot()
         # grouped boxplots:
         septic_patients %>% 
           group_by(hospital_id) %>% 
        -  freq(age) %>%
        +  freq(age) %>%
           boxplot()
         
        @@ -1067,7 +1068,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
      • Added ceftazidim intrinsic resistance to Streptococci
      • Changed default settings for age_groups(), to let groups of fives and tens end with 100+ instead of 120+
      • -
      • Fix for freq() for when all values are NA +
      • Fix for freq() for when all values are NA
      • Fix for first_isolate() for when dates are missing
      • Improved speed of guess_ab_col() @@ -1308,7 +1309,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
    • -
    • Frequency tables (freq() function): +
    • Frequency tables (freq() function):
      • Support for tidyverse quasiquotation! Now you can create frequency tables of function outcomes:

        @@ -1317,15 +1318,15 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ # OLD WAY septic_patients %>% mutate(genus = mo_genus(mo)) %>% - freq(genus) + freq(genus) # NEW WAY septic_patients %>% - freq(mo_genus(mo)) + freq(mo_genus(mo)) # Even supports grouping variables: septic_patients %>% group_by(gender) %>% - freq(mo_genus(mo)) + freq(mo_genus(mo))
      • Header info is now available as a list, with the header function

      • @@ -1409,21 +1410,21 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
      • Using portion_* functions now throws a warning when total available isolate is below parameter minimum

      • Functions as.mo, as.rsi, as.mic, as.atc and freq will not set package name as attribute anymore

      • -

        Frequency tables - freq():

        +

        Frequency tables - freq():

        • Support for grouping variables, test with:

           septic_patients %>% 
             group_by(hospital_id) %>% 
          -  freq(gender)
          +  freq(gender)
           
        • Support for (un)selecting columns:

           septic_patients %>% 
          -  freq(hospital_id) %>% 
          +  freq(hospital_id) %>% 
             select(-count, -cum_count) # only get item, percent, cum_percent
           
        • @@ -1442,7 +1443,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
        • Removed diacritics from all authors (columns microorganisms$ref and microorganisms.old$ref) to comply with CRAN policy to only allow ASCII characters

        • Fix for mo_property not working properly

        • Fix for eucast_rules where some Streptococci would become ceftazidime R in EUCAST rule 4.5

        • -
        • Support for named vectors of class mo, useful for top_freq()

        • +
        • Support for named vectors of class mo, useful for top_freq()

        • ggplot_rsi and scale_y_percent have breaks parameter

        • AI improvements for as.mo:

          @@ -1609,13 +1610,13 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/

          Support for types (classes) list and matrix for freq

           my_matrix = with(septic_patients, matrix(c(age, gender), ncol = 2))
          -freq(my_matrix)
          +freq(my_matrix)
           

          For lists, subsetting is possible:

           my_list = list(age = septic_patients$age, gender = septic_patients$gender)
          -my_list %>% freq(age)
          -my_list %>% freq(gender)
          +my_list %>% freq(age)
          +my_list %>% freq(gender)
           
        @@ -1690,13 +1691,13 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
        • A vignette to explain its usage
        • Support for rsi (antimicrobial resistance) to use as input
        • -
        • Support for table to use as input: freq(table(x, y)) +
        • Support for table to use as input: freq(table(x, y))
        • Support for existing functions hist and plot to use a frequency table as input: hist(freq(df$age))
        • Support for as.vector, as.data.frame, as_tibble and format
        • -
        • Support for quasiquotation: freq(mydata, mycolumn) is the same as mydata %>% freq(mycolumn) +
        • Support for quasiquotation: freq(mydata, mycolumn) is the same as mydata %>% freq(mycolumn)
        • Function top_freq function to return the top/below n items as vector
        • Header of frequency tables now also show Mean Absolute Deviaton (MAD) and Interquartile Range (IQR)
        • diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index 2ef83a0a..c5df8645 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -2,7 +2,7 @@ pandoc: 2.7.3 pkgdown: 1.5.1.9000 pkgdown_sha: eae56f08694abebf93cdfc0dd8e9ede06d8c815f articles: [] -last_built: 2020-09-23T22:50Z +last_built: 2020-09-24T10:36Z urls: reference: https://msberends.github.io/AMR/reference article: https://msberends.github.io/AMR/articles diff --git a/docs/reference/antibiotics.html b/docs/reference/antibiotics.html index 196ad184..6b9be2d7 100644 --- a/docs/reference/antibiotics.html +++ b/docs/reference/antibiotics.html @@ -82,7 +82,7 @@ AMR (for R) - 1.3.0.9026 + 1.3.0.9028 diff --git a/docs/reference/as.mo.html b/docs/reference/as.mo.html index d18c255c..f59567c2 100644 --- a/docs/reference/as.mo.html +++ b/docs/reference/as.mo.html @@ -82,7 +82,7 @@ AMR (for R) - 1.3.0.9026 + 1.3.0.9028 diff --git a/docs/reference/as.rsi.html b/docs/reference/as.rsi.html index 65bc8137..0453a8a5 100644 --- a/docs/reference/as.rsi.html +++ b/docs/reference/as.rsi.html @@ -82,7 +82,7 @@ AMR (for R) - 1.3.0.9026 + 1.3.0.9028 @@ -274,12 +274,12 @@ # S3 method for data.frame as.rsi( x, + ..., col_mo = NULL, guideline = "EUCAST", uti = NULL, conserve_capped_values = FALSE, - add_intrinsic_resistance = FALSE, - ... + add_intrinsic_resistance = FALSE )

          Arguments

          @@ -291,7 +291,7 @@ ... -

          parameters passed on to methods

          +

          for using on a data.frame: names of columns to apply as.rsi() on (supports tidy selection like AMX:VAN). Otherwise: parameters passed on to methods.

          threshold @@ -330,7 +330,7 @@ list(version_txt = "v3.2", year = 2020, title = "EUCAST Expert Rules / EUCAST In

          Value

          -

          Ordered factor with new class rsi

          +

          Ordered factor with new class rsi

          Details

          @@ -468,7 +468,6 @@ The lifecycle of this function is stableas.rsi(c("S", "I", "R", "A", "B", "C")) as.rsi("<= 0.002; S") # will return "S" - rsi_data <- as.rsi(c(rep("S", 474), rep("I", 36), rep("R", 370))) is.rsi(rsi_data) plot(rsi_data) # for percentages @@ -478,6 +477,9 @@ The lifecycle of this function is stablelibrary(dplyr) example_isolates %>% mutate_at(vars(PEN:RIF), as.rsi) +# same: +example_isolates %>% + as.rsi(PEN:RIF) # fastest way to transform all columns with already valid AMR results to class `rsi`: example_isolates %>% diff --git a/docs/reference/bug_drug_combinations.html b/docs/reference/bug_drug_combinations.html index e8914d48..15258182 100644 --- a/docs/reference/bug_drug_combinations.html +++ b/docs/reference/bug_drug_combinations.html @@ -82,7 +82,7 @@ AMR (for R) - 1.3.0.9026 + 1.3.0.9028 diff --git a/docs/reference/eucast_rules.html b/docs/reference/eucast_rules.html index 7bbb7c93..d1981557 100644 --- a/docs/reference/eucast_rules.html +++ b/docs/reference/eucast_rules.html @@ -83,7 +83,7 @@ To improve the interpretation of the antibiogram before EUCAST rules are applied AMR (for R) - 1.3.0.9026 + 1.3.0.9028 diff --git a/docs/reference/index.html b/docs/reference/index.html index 9a06d9f2..39a88a1b 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9027 + 1.3.0.9028 diff --git a/docs/reference/intrinsic_resistant.html b/docs/reference/intrinsic_resistant.html index 19089453..38dbe7a9 100644 --- a/docs/reference/intrinsic_resistant.html +++ b/docs/reference/intrinsic_resistant.html @@ -82,7 +82,7 @@ AMR (for R) - 1.3.0.9026 + 1.3.0.9028 diff --git a/docs/reference/mdro.html b/docs/reference/mdro.html index f5b3a179..fd86b883 100644 --- a/docs/reference/mdro.html +++ b/docs/reference/mdro.html @@ -82,7 +82,7 @@ AMR (for R) - 1.3.0.9026 + 1.3.0.9028 diff --git a/docs/reference/mo_matching_score.html b/docs/reference/mo_matching_score.html index 919832e8..5e6654eb 100644 --- a/docs/reference/mo_matching_score.html +++ b/docs/reference/mo_matching_score.html @@ -82,7 +82,7 @@ AMR (for R) - 1.3.0.9026 + 1.3.0.9028 diff --git a/docs/reference/mo_source.html b/docs/reference/mo_source.html index 215fc5de..cd840252 100644 --- a/docs/reference/mo_source.html +++ b/docs/reference/mo_source.html @@ -83,7 +83,7 @@ This is the fastest way to have your organisation (or analysis) specific codes p AMR (for R) - 1.3.0.9026 + 1.3.0.9028 diff --git a/docs/survey.html b/docs/survey.html index e36851d1..75c96f3a 100644 --- a/docs/survey.html +++ b/docs/survey.html @@ -81,7 +81,7 @@ AMR (for R) - 1.3.0.9027 + 1.3.0.9028 diff --git a/man/as.rsi.Rd b/man/as.rsi.Rd index f468f098..bf8cc511 100755 --- a/man/as.rsi.Rd +++ b/man/as.rsi.Rd @@ -39,18 +39,18 @@ is.rsi.eligible(x, threshold = 0.05) \method{as.rsi}{data.frame}( x, + ..., col_mo = NULL, guideline = "EUCAST", uti = NULL, conserve_capped_values = FALSE, - add_intrinsic_resistance = FALSE, - ... + add_intrinsic_resistance = FALSE ) } \arguments{ \item{x}{vector of values (for class \code{\link{mic}}: an MIC value in mg/L, for class \code{\link{disk}}: a disk diffusion radius in millimetres)} -\item{...}{parameters passed on to methods} +\item{...}{for using on a \link{data.frame}: names of columns to apply \code{\link[=as.rsi]{as.rsi()}} on (supports tidy selection like \code{AMX:VAN}). Otherwise: parameters passed on to methods.} \item{threshold}{maximum fraction of invalid antimicrobial interpretations of \code{x}, please see \emph{Examples}} @@ -70,7 +70,7 @@ list(version_txt = "v3.2", year = 2020, title = "EUCAST Expert Rules / EUCAST In \item{col_mo}{column name of the IDs of the microorganisms (see \code{\link[=as.mo]{as.mo()}}), defaults to the first column of class \code{\link{mo}}. Values will be coerced using \code{\link[=as.mo]{as.mo()}}.} } \value{ -Ordered factor with new class \code{\link{rsi}} +Ordered \link{factor} with new class \code{\link{rsi}} } \description{ Interpret minimum inhibitory concentration (MIC) values and disk diffusion diameters according to EUCAST or CLSI, or clean up existing R/SI values. This transforms the input to a new class \code{\link{rsi}}, which is an ordered factor with levels \verb{S < I < R}. Values that cannot be interpreted will be returned as \code{NA} with a warning. @@ -211,7 +211,6 @@ as.rsi(x = as.disk(18), as.rsi(c("S", "I", "R", "A", "B", "C")) as.rsi("<= 0.002; S") # will return "S" - rsi_data <- as.rsi(c(rep("S", 474), rep("I", 36), rep("R", 370))) is.rsi(rsi_data) plot(rsi_data) # for percentages @@ -221,6 +220,9 @@ barplot(rsi_data) # for frequencies library(dplyr) example_isolates \%>\% mutate_at(vars(PEN:RIF), as.rsi) +# same: +example_isolates \%>\% + as.rsi(PEN:RIF) # fastest way to transform all columns with already valid AMR results to class `rsi`: example_isolates \%>\%