diff --git a/DESCRIPTION b/DESCRIPTION index 9e8cfbb5..f2e0ac7b 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 0.7.1.9005 -Date: 2019-07-01 +Version: 0.7.1.9006 +Date: 2019-07-02 Title: Antimicrobial Resistance Analysis Authors@R: c( person( diff --git a/NEWS.md b/NEWS.md index ce8e8189..f1bff2a6 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,7 +1,7 @@ -# AMR 0.7.1.9005 +# AMR 0.7.1.9006 ### New -* Additional way to calculate co-resistance, i.e. when using multiple antibiotics as input for `portion_*` functions or `count_*` functions. This can be used to determine the empiric susceptibily of a combination therapy. A new parameter `only_all_tested` replaces the old `also_single_tested` and can be used to select one of the two methods to count isolates and calculate portions. The difference can be seen in this example table (which is also on the `portion` and `count` help pages), where the %SI is being determined: +* Additional way to calculate co-resistance, i.e. when using multiple antibiotics as input for `portion_*` functions or `count_*` functions. This can be used to determine the empiric susceptibily of a combination therapy. A new parameter `only_all_tested` (**which defaults to `FALSE`**) replaces the old `also_single_tested` and can be used to select one of the two methods to count isolates and calculate portions. The difference can be seen in this example table (which is also on the `portion` and `count` help pages), where the %SI is being determined: ```r # ------------------------------------------------------------------------- diff --git a/R/freq.R b/R/freq.R index a234593a..91d636fe 100755 --- a/R/freq.R +++ b/R/freq.R @@ -318,7 +318,7 @@ freq <- function(x, df <- df %>% ungroup() %>% # do not repeat group labels - mutate_at(vars(x.group), funs(ifelse(lag(.) == ., "", .))) + mutate_at(vars(x.group), ~(ifelse(lag(.) == ., "", .))) df[1, 1] <- df.topleft colnames(df)[1:2] <- c("group", "item") diff --git a/R/globals.R b/R/globals.R index baf90fdd..f9ed702e 100755 --- a/R/globals.R +++ b/R/globals.R @@ -30,7 +30,7 @@ globalVariables(c(".", "count.x", "date_lab", "diff.percent", - "First", + "First name", "first_isolate_row_index", "fullname", "fullname_lower", @@ -46,7 +46,7 @@ globalVariables(c(".", "key_ab_other", "kingdom", "lang", - "Last", + "Last name", "lookup", "mdr", "median", @@ -56,8 +56,6 @@ globalVariables(c(".", "mono_count", "more_than_episode_ago", "name", - "name", - "name", "new", "observations", "observed", diff --git a/R/mo.R b/R/mo.R index 605a6cc0..dab25c05 100755 --- a/R/mo.R +++ b/R/mo.R @@ -135,6 +135,7 @@ #' @inheritSection AMR Read more on our website! #' @importFrom dplyr %>% pull left_join #' @examples +#' \donttest{ #' # These examples all return "B_STPHY_AUR", the ID of S. aureus: #' as.mo("sau") # WHONET code #' as.mo("stau") @@ -169,7 +170,7 @@ #' # All mo_* functions use as.mo() internally too (see ?mo_property): #' mo_genus("E. coli") # returns "Escherichia" #' mo_gramstain("E. coli") # returns "Gram negative"#' -#' +#' } #' \dontrun{ #' df$mo <- as.mo(df$microorganism_name) #' diff --git a/R/portion.R b/R/portion.R index 6599fec0..798c3afa 100755 --- a/R/portion.R +++ b/R/portion.R @@ -36,7 +36,7 @@ #' @inheritSection as.rsi Interpretation of S, I and R #' @details \strong{Remember that you should filter your table to let it contain only first isolates!} This is needed to exclude duplicates and to reduce selection bias. Use \code{\link{first_isolate}} to determine them in your data set. #' -#' These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. \emph{Low counts can infuence the outcome - these \code{portion} functions may camouflage this, since they only return the portion albeit being dependent on the \code{minimum} parameter.} +#' These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. The function \code{portion_SI()} is essentially equal to \code{count_SI() / count_all()}. \emph{Low counts can infuence the outcome - the \code{portion} functions may camouflage this, since they only return the portion (albeit being dependent on the \code{minimum} parameter).} #' #' The function \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each group and each variable with class \code{"rsi"}. #' @@ -70,12 +70,12 @@ #' ------------------------------------------------------------------------- #' } #' -#' Please note that for \code{only_all_tested = TRUE} applies that: +#' Please note that, in combination therapies, for \code{only_all_tested = TRUE} applies that: #' \preformatted{ #' count_S() + count_I() + count_R() == count_all() #' portion_S() + portion_I() + portion_R() == 1 #' } -#' and that for \code{only_all_tested = FALSE} applies that: +#' and that, in combination therapies, for \code{only_all_tested = FALSE} applies that: #' \preformatted{ #' count_S() + count_I() + count_R() >= count_all() #' portion_S() + portion_I() + portion_R() >= 1 diff --git a/R/resistance_predict.R b/R/resistance_predict.R index 7b344346..b4a97706 100755 --- a/R/resistance_predict.R +++ b/R/resistance_predict.R @@ -166,7 +166,7 @@ resistance_predict <- function(x, df <- x %>% mutate_at(col_ab, as.rsi) %>% mutate_at(col_ab, droplevels) %>% - mutate_at(col_ab, funs( + mutate_at(col_ab, ~( if (I_as_S == TRUE) { gsub("I", "S", .) } else { diff --git a/R/rsi_calc.R b/R/rsi_calc.R index 74e2151f..431adff3 100755 --- a/R/rsi_calc.R +++ b/R/rsi_calc.R @@ -120,9 +120,15 @@ rsi_calc <- function(..., #numerator <- x %>% filter_all(any_vars(. %in% ab_result)) %>% nrow() if (only_all_tested == TRUE) { # THE NUMBER OF ISOLATES WHERE *ALL* ABx ARE S/I/R - x_filtered <- x %>% filter_all(all_vars(!is.na(.))) - numerator <- x_filtered %>% filter_all(any_vars(. %in% ab_result)) %>% nrow() - denominator <- x_filtered %>% nrow() + # x_filtered <- x %>% filter_all(all_vars(!is.na(.))) + # numerator <- x_filtered %>% filter_all(any_vars(. %in% ab_result)) %>% nrow() + # denominator <- x_filtered %>% nrow() + x <- apply(X = x %>% mutate_all(as.integer), + MARGIN = 1, + FUN = base::min) + numerator <- sum(as.integer(x) %in% as.integer(ab_result), na.rm = TRUE) + denominator <- length(x) - sum(is.na(x)) + } else { # THE NUMBER OF ISOLATES WHERE *ANY* ABx IS S/I/R other_values <- base::setdiff(c(NA, levels(ab_result)), ab_result) diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index 8a234d0d..8a29f7dc 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.1.9005 + 0.7.1.9006 diff --git a/docs/articles/index.html b/docs/articles/index.html index 5e1c1d91..9a136fef 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.1.9005 + 0.7.1.9006 diff --git a/docs/authors.html b/docs/authors.html index bbdaf4b9..a55b79fb 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.1.9005 + 0.7.1.9006 diff --git a/docs/index.html b/docs/index.html index 88449734..32901c15 100644 --- a/docs/index.html +++ b/docs/index.html @@ -42,7 +42,7 @@ AMR (for R) - 0.7.1.9005 + 0.7.1.9006 diff --git a/docs/news/index.html b/docs/news/index.html index 132adec3..dda17fd2 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.1.9005 + 0.7.1.9006 @@ -232,16 +232,16 @@ -
+

-AMR 0.7.1.9005 Unreleased +AMR 0.7.1.9006 Unreleased

New

  • -

    Additional way to calculate co-resistance, i.e. when using multiple antibiotics as input for portion_* functions or count_* functions. This can be used to determine the empiric susceptibily of a combination therapy. A new parameter only_all_tested replaces the old also_single_tested and can be used to select one of the two methods to count isolates and calculate portions. The difference can be seen in this example table (which is also on the portion and count help pages), where the %SI is being determined:

    +

    Additional way to calculate co-resistance, i.e. when using multiple antibiotics as input for portion_* functions or count_* functions. This can be used to determine the empiric susceptibily of a combination therapy. A new parameter only_all_tested (which defaults to FALSE) replaces the old also_single_tested and can be used to select one of the two methods to count isolates and calculate portions. The difference can be seen in this example table (which is also on the portion and count help pages), where the %SI is being determined:

    # -------------------------------------------------------------------------
     #                         only_all_tested = FALSE   only_all_tested = TRUE
     # Antibiotic  Antibiotic  -----------------------   -----------------------
    @@ -1192,7 +1192,7 @@ Using as.mo(..., allow_uncertain = 3)
           

    Contents

    @@ -406,7 +406,6 @@ The mo_property functions (like # All mo_* functions use as.mo() internally too (see ?mo_property): mo_genus("E. coli") # returns "Escherichia" mo_gramstain("E. coli") # returns "Gram negative"#' - # }# NOT RUN { df$mo <- as.mo(df$microorganism_name) diff --git a/docs/reference/count.html b/docs/reference/count.html index 732c6e31..b8d648b2 100644 --- a/docs/reference/count.html +++ b/docs/reference/count.html @@ -81,7 +81,7 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_ AMR (for R) - 0.7.1.9005 + 0.7.1.9006
@@ -349,10 +349,10 @@ not tested R - - - - not tested not tested - - - - ------------------------------------------------------------------------- -

Please note that for only_all_tested = TRUE applies that:

+    

Please note that, in combination therapies, for only_all_tested = TRUE applies that:

    count_S()  +  count_I()  +  count_R()  == count_all()
   portion_S() + portion_I() + portion_R() == 1
-

and that for only_all_tested = FALSE applies that:

+

and that, in combination therapies, for only_all_tested = FALSE applies that:

    count_S()  +  count_I()  +  count_R()  >= count_all()
   portion_S() + portion_I() + portion_R() >= 1
 
diff --git a/docs/reference/index.html b/docs/reference/index.html index c46837c3..d2e60c69 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.1.9005 + 0.7.1.9006
diff --git a/docs/reference/portion.html b/docs/reference/portion.html index 3b723cbb..c293d830 100644 --- a/docs/reference/portion.html +++ b/docs/reference/portion.html @@ -81,7 +81,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port AMR (for R) - 0.7.1.9005 + 0.7.1.9006
@@ -319,7 +319,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port

Details

Remember that you should filter your table to let it contain only first isolates! This is needed to exclude duplicates and to reduce selection bias. Use first_isolate to determine them in your data set.

-

These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the count functions to count isolates. Low counts can infuence the outcome - these portion functions may camouflage this, since they only return the portion albeit being dependent on the minimum parameter.

+

These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the count functions to count isolates. The function portion_SI() is essentially equal to count_SI() / count_all(). Low counts can infuence the outcome - the portion functions may camouflage this, since they only return the portion (albeit being dependent on the minimum parameter).

The function portion_df takes any variable from data that has an "rsi" class (created with as.rsi) and calculates the portions R, I and S. The resulting tidy data (see Source) data.frame will have three rows (S/I/R) and a column for each group and each variable with class "rsi".

The function rsi_df works exactly like portion_df, but adds the number of isolates.

@@ -352,10 +352,10 @@ not tested R - - - - not tested not tested - - - - ------------------------------------------------------------------------- -

Please note that for only_all_tested = TRUE applies that:

+    

Please note that, in combination therapies, for only_all_tested = TRUE applies that:

    count_S()  +  count_I()  +  count_R()  == count_all()
   portion_S() + portion_I() + portion_R() == 1
-

and that for only_all_tested = FALSE applies that:

+

and that, in combination therapies, for only_all_tested = FALSE applies that:

    count_S()  +  count_I()  +  count_R()  >= count_all()
   portion_S() + portion_I() + portion_R() >= 1
 
diff --git a/man/as.mo.Rd b/man/as.mo.Rd index e515628b..eb502754 100644 --- a/man/as.mo.Rd +++ b/man/as.mo.Rd @@ -145,6 +145,7 @@ On our website \url{https://msberends.gitlab.io/AMR} you can find \href{https:// } \examples{ +\donttest{ # These examples all return "B_STPHY_AUR", the ID of S. aureus: as.mo("sau") # WHONET code as.mo("stau") @@ -179,7 +180,7 @@ as.mo("S. pyogenes", Lancefield = TRUE) # will not remain species: B_STRPT_GRA # All mo_* functions use as.mo() internally too (see ?mo_property): mo_genus("E. coli") # returns "Escherichia" mo_gramstain("E. coli") # returns "Gram negative"#' - +} \dontrun{ df$mo <- as.mo(df$microorganism_name) diff --git a/man/count.Rd b/man/count.Rd index f70562e1..791d7532 100644 --- a/man/count.Rd +++ b/man/count.Rd @@ -109,12 +109,12 @@ not tested not tested - - - - ------------------------------------------------------------------------- } -Please note that for \code{only_all_tested = TRUE} applies that: +Please note that, in combination therapies, for \code{only_all_tested = TRUE} applies that: \preformatted{ count_S() + count_I() + count_R() == count_all() portion_S() + portion_I() + portion_R() == 1 } -and that for \code{only_all_tested = FALSE} applies that: +and that, in combination therapies, for \code{only_all_tested = FALSE} applies that: \preformatted{ count_S() + count_I() + count_R() >= count_all() portion_S() + portion_I() + portion_R() >= 1 diff --git a/man/portion.Rd b/man/portion.Rd index 2a6f8304..c6f0f614 100644 --- a/man/portion.Rd +++ b/man/portion.Rd @@ -69,7 +69,7 @@ These functions can be used to calculate the (co-)resistance of microbial isolat \details{ \strong{Remember that you should filter your table to let it contain only first isolates!} This is needed to exclude duplicates and to reduce selection bias. Use \code{\link{first_isolate}} to determine them in your data set. -These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. \emph{Low counts can infuence the outcome - these \code{portion} functions may camouflage this, since they only return the portion albeit being dependent on the \code{minimum} parameter.} +These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. The function \code{portion_SI()} is essentially equal to \code{count_SI() / count_all()}. \emph{Low counts can infuence the outcome - the \code{portion} functions may camouflage this, since they only return the portion (albeit being dependent on the \code{minimum} parameter).} The function \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each group and each variable with class \code{"rsi"}. @@ -105,12 +105,12 @@ not tested not tested - - - - ------------------------------------------------------------------------- } -Please note that for \code{only_all_tested = TRUE} applies that: +Please note that, in combination therapies, for \code{only_all_tested = TRUE} applies that: \preformatted{ count_S() + count_I() + count_R() == count_all() portion_S() + portion_I() + portion_R() == 1 } -and that for \code{only_all_tested = FALSE} applies that: +and that, in combination therapies, for \code{only_all_tested = FALSE} applies that: \preformatted{ count_S() + count_I() + count_R() >= count_all() portion_S() + portion_I() + portion_R() >= 1 diff --git a/tests/testthat/test-mo.R b/tests/testthat/test-mo.R index c8dee3b2..b8c76a56 100644 --- a/tests/testthat/test-mo.R +++ b/tests/testthat/test-mo.R @@ -238,7 +238,7 @@ test_that("as.mo works", { print(mo_uncertainties()) # Salmonella (City) are all actually Salmonella enterica spp (City) - expect_equal(as.character(suppressMessages(as.mo("Salmonella Goettingen"))), + expect_equal(as.character(suppressWarnings(as.mo("Salmonella Goettingen"))), "B_SLMNL_ENT") expect_equal(as.character(as.mo("Salmonella Group A")), "B_SLMNL")