diff --git a/DESCRIPTION b/DESCRIPTION index c438c08b..a56411ca 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR Version: 0.5.0.9016 -Date: 2019-02-01 +Date: 2019-02-04 Title: Antimicrobial Resistance Analysis Authors@R: c( person( diff --git a/NAMESPACE b/NAMESPACE index 50cf58d0..0965661a 100755 --- a/NAMESPACE +++ b/NAMESPACE @@ -66,6 +66,7 @@ export(atc_property) export(atc_tradenames) export(atc_trivial_nl) export(atc_umcg) +export(availability) export(brmo) export(count_I) export(count_IR) diff --git a/NEWS.md b/NEWS.md index c04ebab5..8f2e9770 100755 --- a/NEWS.md +++ b/NEWS.md @@ -77,7 +77,7 @@ * A note to the manual pages of the `portion` functions, that low counts can influence the outcome and that the `portion` functions may camouflage this, since they only return the portion (albeit being dependent on the `minimum` parameter) * Merged data sets `microorganisms.certe` and `microorganisms.umcg` into `microorganisms.codes` * Function `mo_taxonomy()` now contains the kingdom too -* Reduce false positives for `is.rsi.eligible()` +* Reduce false positives for `is.rsi.eligible()` using the new `threshold` parameter * New colours for `scale_rsi_colours()` * Summaries of class `mo` will now return the top 3 and the unique count, e.g. using `summary(mo)` * Small text updates to summaries of class `rsi` and `mic` diff --git a/R/availability.R b/R/availability.R new file mode 100644 index 00000000..a120430d --- /dev/null +++ b/R/availability.R @@ -0,0 +1,61 @@ +# ==================================================================== # +# TITLE # +# Antimicrobial Resistance (AMR) Analysis # +# # +# SOURCE # +# https://gitlab.com/msberends/AMR # +# # +# LICENCE # +# (c) 2019 Berends MS (m.s.berends@umcg.nl), Luz CF (c.f.luz@umcg.nl) # +# # +# This R package is free software; you can freely use and distribute # +# it for both personal and commercial purposes under the terms of the # +# GNU General Public License version 2.0 (GNU GPL-2), as published by # +# the Free Software Foundation. # +# # +# This R package was created for academic research and was publicly # +# released in the hope that it will be useful, but it comes WITHOUT # +# ANY WARRANTY OR LIABILITY. # +# Visit our website for more info: https://msberends.gitab.io/AMR. # +# ==================================================================== # + +#' Check availability of columns +#' +#' Easy check for availability of columns in a data set. This makes it easy to get an idea of which antibiotic combination can be used for calculation with e.g. \code{\link{portion_IR}}. +#' @param tbl a \code{data.frame} or \code{list} +#' @return \code{data.frame} with column names of \code{tbl} as row names and columns: \code{percent_IR}, \code{count}, \code{percent}, \code{visual_availability}. +#' @export +#' @examples +#' availability(septic_patients) +#' +#' library(dplyr) +#' septic_patients %>% availability() +#' +#' septic_patients %>% +#' select_if(is.rsi) %>% +#' availability() +#' +#' septic_patients %>% +#' filter(mo == as.mo("E. coli")) %>% +#' select_if(is.rsi) %>% +#' availability() +availability <- function(tbl) { + x <- base::sapply(tbl, function(x) { 1 - base::sum(base::is.na(x)) / base::length(x) }) + n <- base::sapply(tbl, function(x) base::length(x[!base::is.na(x)])) + IR <- base::sapply(tbl, function(x) base::ifelse(is.rsi(x), base::round(portion_IR(x, minimum = 0) * 100, 1), "NaN")) + IR <- paste0(IR, "%") + IR <- gsub("NaN%", "", IR) + max_chars <- 50 + x_chars <- strrep("#", round(x, digits = 2) / (1 / max_chars)) + x_chars_empty <- strrep("-", max_chars - nchar(x_chars)) + # x_abnames <- character(length(x)) + # for (i in 1:length(x)) { + # if (tbl %>% pull(i) %>% is.rsi()) { + # x_abnames[i] <- atc_name(colnames(tbl)[i]) + # } + # } + data.frame(percent_IR = IR, + count = n, + percent = paste0(round(x * 100, 1), "%"), + visual_availabilty = paste0("|", x_chars, x_chars_empty, "|")) +} diff --git a/R/data.R b/R/data.R index 673d381f..53150089 100755 --- a/R/data.R +++ b/R/data.R @@ -211,7 +211,7 @@ #' \describe{ #' \item{\code{Identification number}}{ID of the sample} #' \item{\code{Specimen number}}{ID of the specimen} -#' \item{\code{Organism}}{Microorganisms, can be coerced with \code{\link{as.mo}}} +#' \item{\code{Organism}}{Name of the microorganism. Before analysis, you should transform this to a valid microbial class, using \code{\link{as.mo}}.} #' \item{\code{Country}}{Country of origin} #' \item{\code{Laboratory}}{Name of laboratory} #' \item{\code{Last name}}{Last name of patient} @@ -234,7 +234,7 @@ #' \item{\code{Inducible clindamycin resistance}}{Clindamycin can be induced?} #' \item{\code{Comment}}{Other comments} #' \item{\code{Date of data entry}}{Date this data was entered in WHONET} -#' \item{\code{AMP_ND10:CIP_EE}}{27 different antibiotics. You can lookup the abbreviatons in the \code{\link{antibiotics}} data set, or use e.g. \code{\link{atc_name}("AMP")} to get the official name immediately.} +#' \item{\code{AMP_ND10:CIP_EE}}{27 different antibiotics. You can lookup the abbreviatons in the \code{\link{antibiotics}} data set, or use e.g. \code{\link{atc_name}("AMP")} to get the official name immediately. Before analysis, you should transform this to a valid antibiotic class, using \code{\link{as.rsi}}.} #' } #' @inheritSection AMR Read more on our website! "WHONET" diff --git a/R/first_isolate.R b/R/first_isolate.R index 46e16bd5..7e9faa5e 100755 --- a/R/first_isolate.R +++ b/R/first_isolate.R @@ -381,7 +381,7 @@ first_isolate <- function(tbl, if (abs(row.start) == Inf | abs(row.end) == Inf) { if (info == TRUE) { - message('No isolates found.') + message(paste("=> Found", bold("no isolates"))) } # NAs where genus is unavailable return(tbl %>% diff --git a/R/rsi.R b/R/rsi.R index 4d93bf02..e3e7b0f0 100755 --- a/R/rsi.R +++ b/R/rsi.R @@ -24,6 +24,7 @@ #' This transforms a vector to a new class \code{rsi}, which is an ordered factor with levels \code{S < I < R}. Invalid antimicrobial interpretations will be translated as \code{NA} with a warning. #' @rdname as.rsi #' @param x vector +#' @param threshold maximum fraction of \code{x} that is allowed to fail transformation, see Examples #' @details The function \code{is.rsi.eligible} returns \code{TRUE} when a columns contains only valid antimicrobial interpretations (S and/or I and/or R), and \code{FALSE} otherwise. #' @return Ordered factor with new class \code{rsi} #' @keywords rsi @@ -48,10 +49,15 @@ #' septic_patients %>% #' mutate_at(vars(peni:rifa), as.rsi) #' +#' #' # fastest way to transform all columns with already valid AB results to class `rsi`: #' septic_patients %>% #' mutate_if(is.rsi.eligible, #' as.rsi) +#' +#' # default threshold of `is.rsi.eligible` is 5%. +#' is.rsi.eligible(WHONET$`First name`) # fails, >80% is invalid +#' is.rsi.eligible(WHONET$`First name`, threhold = 0.9) # succeeds as.rsi <- function(x) { if (is.rsi(x)) { x @@ -99,28 +105,37 @@ as.rsi <- function(x) { #' @rdname as.rsi #' @export -#' @importFrom dplyr %>% is.rsi <- function(x) { - class(x) %>% identical(c('rsi', 'ordered', 'factor')) + identical(class(x), + c('rsi', 'ordered', 'factor')) } #' @rdname as.rsi #' @export -#' @importFrom dplyr %>% -is.rsi.eligible <- function(x) { - if (is.logical(x) - | is.numeric(x) - | is.mo(x) - | identical(class(x), "Date") - | is.rsi(x)) { +is.rsi.eligible <- function(x, threshold = 0.05) { + if (NCOL(x) > 1) { + stop('`x` must be a one-dimensional vector.') + } + if (any(c("logical", + "numeric", + "integer", + "mo", + "Date", + "POSIXct", + "rsi", + "raw", + "hms") + %in% class(x))) { # no transformation needed FALSE } else { - # check all but a-z - y <- unique(gsub("[^RSIrsi]+", "", unique(x))) - !all(y %in% c("", NA_character_)) & - all(y %in% c("R", "I", "S", "", NA_character_)) & - max(nchar(as.character(x)), na.rm = TRUE) < 8 + x <- x[!is.na(x) & !is.null(x) & !identical(x, "")] + if (length(x) == 0) { + return(FALSE) + } + checked <- suppressWarnings(as.rsi(x)) + outcome <- sum(is.na(checked)) / length(x) + outcome <= threshold } } diff --git a/data/WHONET.rda b/data/WHONET.rda index 4c642251..0a777481 100644 Binary files a/data/WHONET.rda and b/data/WHONET.rda differ diff --git a/docs/articles/AMR.html b/docs/articles/AMR.html index 9854b148..ee872f5a 100644 --- a/docs/articles/AMR.html +++ b/docs/articles/AMR.html @@ -185,7 +185,7 @@

How to conduct AMR analysis

Matthijs S. Berends

-

01 February 2019

+

04 February 2019

@@ -194,7 +194,7 @@ -

Note: values on this page will change with every website update since they are based on randomly created values and the page was written in RMarkdown. However, the methodology remains unchanged. This page was generated on 01 February 2019.

+

Note: values on this page will change with every website update since they are based on randomly created values and the page was written in RMarkdown. However, the methodology remains unchanged. This page was generated on 04 February 2019.

Introduction

@@ -210,21 +210,21 @@ -2019-02-01 +2019-02-04 abcd Escherichia coli S S -2019-02-01 +2019-02-04 abcd Escherichia coli S R -2019-02-01 +2019-02-04 efgh Escherichia coli R @@ -237,12 +237,12 @@ Needed R packages

As with many uses in R, we need some additional packages for AMR analysis. Our package works closely together with the tidyverse packages dplyr and ggplot2 by Dr Hadley Wickham. The tidyverse tremendously improves the way we conduct data science - it allows for a very natural way of writing syntaxes and creating beautiful plots in R.

Our AMR package depends on these packages and even extends their use and functions.

-
library(dplyr)
-library(ggplot2)
-library(AMR)
-
-# (if not yet installed, install with:)
-# install.packages(c("tidyverse", "AMR"))
+
library(dplyr)
+library(ggplot2)
+library(AMR)
+
+# (if not yet installed, install with:)
+# install.packages(c("tidyverse", "AMR"))
@@ -254,51 +254,51 @@

Patients

To start with patients, we need a unique list of patients.

-
patients <- unlist(lapply(LETTERS, paste0, 1:10))
+
patients <- unlist(lapply(LETTERS, paste0, 1:10))

The LETTERS object is available in R - it’s a vector with 26 characters: A to Z. The patients object we just created is now a vector of length 260, with values (patient IDs) varying from A1 to Z10. Now we we also set the gender of our patients, by putting the ID and the gender in a table:

-
patients_table <- data.frame(patient_id = patients,
-                             gender = c(rep("M", 135),
-                                        rep("F", 125)))
+
patients_table <- data.frame(patient_id = patients,
+                             gender = c(rep("M", 135),
+                                        rep("F", 125)))

The first 135 patient IDs are now male, the other 125 are female.

Dates

Let’s pretend that our data consists of blood cultures isolates from 1 January 2010 until 1 January 2018.

-
dates <- seq(as.Date("2010-01-01"), as.Date("2018-01-01"), by = "day")
+
dates <- seq(as.Date("2010-01-01"), as.Date("2018-01-01"), by = "day")

This dates object now contains all days in our date range.

Microorganisms

For this tutorial, we will uses four different microorganisms: Escherichia coli, Staphylococcus aureus, Streptococcus pneumoniae, and Klebsiella pneumoniae:

-
bacteria <- c("Escherichia coli", "Staphylococcus aureus",
-              "Streptococcus pneumoniae", "Klebsiella pneumoniae")
+
bacteria <- c("Escherichia coli", "Staphylococcus aureus",
+              "Streptococcus pneumoniae", "Klebsiella pneumoniae")

Other variables

For completeness, we can also add the hospital where the patients was admitted and we need to define valid antibmicrobial results for our randomisation:

-
hospitals <- c("Hospital A", "Hospital B", "Hospital C", "Hospital D")
-ab_interpretations <- c("S", "I", "R")
+
hospitals <- c("Hospital A", "Hospital B", "Hospital C", "Hospital D")
+ab_interpretations <- c("S", "I", "R")

Put everything together

Using the sample() function, we can randomly select items from all objects we defined earlier. To let our fake data reflect reality a bit, we will also approximately define the probabilities of bacteria and the antibiotic results with the prob parameter.

-
data <- data.frame(date = sample(dates, 5000, replace = TRUE),
-                   patient_id = sample(patients, 5000, replace = TRUE),
-                   hospital = sample(hospitals, 5000, replace = TRUE, prob = c(0.30, 0.35, 0.15, 0.20)),
-                   bacteria = sample(bacteria, 5000, replace = TRUE, prob = c(0.50, 0.25, 0.15, 0.10)),
-                   amox = sample(ab_interpretations, 5000, replace = TRUE, prob = c(0.60, 0.05, 0.35)),
-                   amcl = sample(ab_interpretations, 5000, replace = TRUE, prob = c(0.75, 0.10, 0.15)),
-                   cipr = sample(ab_interpretations, 5000, replace = TRUE, prob = c(0.80, 0.00, 0.20)),
-                   gent = sample(ab_interpretations, 5000, replace = TRUE, prob = c(0.92, 0.00, 0.08))
-                   )
+
data <- data.frame(date = sample(dates, 5000, replace = TRUE),
+                   patient_id = sample(patients, 5000, replace = TRUE),
+                   hospital = sample(hospitals, 5000, replace = TRUE, prob = c(0.30, 0.35, 0.15, 0.20)),
+                   bacteria = sample(bacteria, 5000, replace = TRUE, prob = c(0.50, 0.25, 0.15, 0.10)),
+                   amox = sample(ab_interpretations, 5000, replace = TRUE, prob = c(0.60, 0.05, 0.35)),
+                   amcl = sample(ab_interpretations, 5000, replace = TRUE, prob = c(0.75, 0.10, 0.15)),
+                   cipr = sample(ab_interpretations, 5000, replace = TRUE, prob = c(0.80, 0.00, 0.20)),
+                   gent = sample(ab_interpretations, 5000, replace = TRUE, prob = c(0.92, 0.00, 0.08))
+                   )

Using the left_join() function from the dplyr package, we can ‘map’ the gender to the patient ID using the patients_table object we created earlier:

-
data <- data %>% left_join(patients_table)
+
data <- data %>% left_join(patients_table)

The resulting data set contains 5,000 blood culture isolates. With the head() function we can preview the first 6 values of this data set:

-
head(data)
+
head(data)
@@ -313,70 +313,70 @@ ab_interpretations <- - - - - - - - - - - - - - - - - - - - - - - - - + + - + + + + + + + + + + + + + + + + + + + + + + + - - + + - - - + - + + + - - + + - + - - - - + + + + - +
date2014-06-07Y9Hospital AKlebsiella pneumoniaeSSSSF
2010-06-10Z1Hospital BEscherichia coliRSSSF
2012-03-20J62010-05-26E8 Hospital CStreptococcus pneumoniaeEscherichia coliR SRSM
2016-11-27D6Hospital BStreptococcus pneumoniaeRSSSM
2015-03-24J2Hospital AEscherichia coliR S S S M
2016-10-31M52014-09-12Y4 Hospital AEscherichia coliSRStaphylococcus aureus S SMSSF
2016-05-05W82015-05-27M8 Hospital B Escherichia coli R S S SFM
2016-03-10G8Hospital AStreptococcus pneumoniae2017-10-14R8Hospital CStaphylococcus aureus S S S SMF
@@ -387,7 +387,7 @@ ab_interpretations <- Cleaning the data

Use the frequency table function freq() to look specifically for unique values in any variable. For example, for the gender variable:

-
data %>% freq(gender) # this would be the same: freq(data$gender)
+
data %>% freq(gender) # this would be the same: freq(data$gender)
# Frequency table of `gender` from a `data.frame` (5,000 x 9) 
 # Class:   factor (numeric)
 # Levels:  F, M
@@ -396,67 +396,67 @@ ab_interpretations <- mutate() function of the dplyr package makes this really easy:

-
data <- data %>%
-  mutate(bacteria = as.mo(bacteria))
+
data <- data %>%
+  mutate(bacteria = as.mo(bacteria))

We also want to transform the antibiotics, because in real life data we don’t know if they are really clean. The as.rsi() function ensures reliability and reproducibility in these kind of variables. The mutate_at() will run the as.rsi() function on defined variables:

-
data <- data %>%
-  mutate_at(vars(amox:gent), as.rsi)
+
data <- data %>%
+  mutate_at(vars(amox:gent), as.rsi)

Finally, we will apply EUCAST rules on our antimicrobial results. In Europe, most medical microbiological laboratories already apply these rules. Our package features their latest insights on intrinsic resistance and exceptional phenotypes. Moreover, the eucast_rules() function can also apply additional rules, like forcing ampicillin = R when amoxicillin/clavulanic acid = R.

Because the amoxicillin (column amox) and amoxicillin/clavulanic acid (column amcl) in our data were generated randomly, some rows will undoubtedly contain amox = S and amcl = R, which is technically impossible. The eucast_rules() fixes this:

-
data <- eucast_rules(data, col_mo = "bacteria")
-# 
-# Rules by the European Committee on Antimicrobial Susceptibility Testing (EUCAST)
-# 
-# EUCAST Clinical Breakpoints (v9.0, 2019)
-# Enterobacteriales (Order) (no changes)
-# Staphylococcus (no changes)
-# Enterococcus (no changes)
-# Streptococcus groups A, B, C, G (no changes)
-# Streptococcus pneumoniae (no changes)
-# Viridans group streptococci (no changes)
-# Haemophilus influenzae (no changes)
-# Moraxella catarrhalis (no changes)
-# Anaerobic Gram positives (no changes)
-# Anaerobic Gram negatives (no changes)
-# Pasteurella multocida (no changes)
-# Campylobacter jejuni and C. coli (no changes)
-# Aerococcus sanguinicola and A. urinae (no changes)
-# Kingella kingae (no changes)
-# 
-# EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)
-# Table 1:  Intrinsic resistance in Enterobacteriaceae (340 changes)
-# Table 2:  Intrinsic resistance in non-fermentative Gram-negative bacteria (no changes)
-# Table 3:  Intrinsic resistance in other Gram-negative bacteria (no changes)
-# Table 4:  Intrinsic resistance in Gram-positive bacteria (681 changes)
-# Table 8:  Interpretive rules for B-lactam agents and Gram-positive cocci (no changes)
-# Table 9:  Interpretive rules for B-lactam agents and Gram-negative rods (no changes)
-# Table 10: Interpretive rules for B-lactam agents and other Gram-negative bacteria (no changes)
-# Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins (no changes)
-# Table 12: Interpretive rules for aminoglycosides (no changes)
-# Table 13: Interpretive rules for quinolones (no changes)
-# 
-# Other rules
-# Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (no changes)
-# Non-EUCAST: piperacillin = R where piperacillin/tazobactam = R (no changes)
-# Non-EUCAST: trimethoprim = R where trimethoprim/sulfa = R (no changes)
-# Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (no changes)
-# Non-EUCAST: piperacillin/tazobactam = S where piperacillin = S (no changes)
-# Non-EUCAST: trimethoprim/sulfa = S where trimethoprim = S (no changes)
-# 
-# => EUCAST rules affected 1,858 out of 5,000 rows -> changed 1,021 test results.
+
data <- eucast_rules(data, col_mo = "bacteria")
+# 
+# Rules by the European Committee on Antimicrobial Susceptibility Testing (EUCAST)
+# 
+# EUCAST Clinical Breakpoints (v9.0, 2019)
+# Enterobacteriales (Order) (no changes)
+# Staphylococcus (no changes)
+# Enterococcus (no changes)
+# Streptococcus groups A, B, C, G (no changes)
+# Streptococcus pneumoniae (no changes)
+# Viridans group streptococci (no changes)
+# Haemophilus influenzae (no changes)
+# Moraxella catarrhalis (no changes)
+# Anaerobic Gram positives (no changes)
+# Anaerobic Gram negatives (no changes)
+# Pasteurella multocida (no changes)
+# Campylobacter jejuni and C. coli (no changes)
+# Aerococcus sanguinicola and A. urinae (no changes)
+# Kingella kingae (no changes)
+# 
+# EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)
+# Table 1:  Intrinsic resistance in Enterobacteriaceae (348 changes)
+# Table 2:  Intrinsic resistance in non-fermentative Gram-negative bacteria (no changes)
+# Table 3:  Intrinsic resistance in other Gram-negative bacteria (no changes)
+# Table 4:  Intrinsic resistance in Gram-positive bacteria (702 changes)
+# Table 8:  Interpretive rules for B-lactam agents and Gram-positive cocci (no changes)
+# Table 9:  Interpretive rules for B-lactam agents and Gram-negative rods (no changes)
+# Table 10: Interpretive rules for B-lactam agents and other Gram-negative bacteria (no changes)
+# Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins (no changes)
+# Table 12: Interpretive rules for aminoglycosides (no changes)
+# Table 13: Interpretive rules for quinolones (no changes)
+# 
+# Other rules
+# Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (no changes)
+# Non-EUCAST: piperacillin = R where piperacillin/tazobactam = R (no changes)
+# Non-EUCAST: trimethoprim = R where trimethoprim/sulfa = R (no changes)
+# Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (no changes)
+# Non-EUCAST: piperacillin/tazobactam = S where piperacillin = S (no changes)
+# Non-EUCAST: trimethoprim/sulfa = S where trimethoprim = S (no changes)
+# 
+# => EUCAST rules affected 1,820 out of 5,000 rows -> changed 1,050 test results.

Adding new variables

Now that we have the microbial ID, we can add some taxonomic properties:

-
data <- data %>% 
-  mutate(gramstain = mo_gramstain(bacteria),
-         genus = mo_genus(bacteria),
-         species = mo_species(bacteria))
+
data <- data %>% 
+  mutate(gramstain = mo_gramstain(bacteria),
+         genus = mo_genus(bacteria),
+         species = mo_species(bacteria))

First isolates

@@ -467,18 +467,18 @@ ab_interpretations <- M39-A4 Analysis and Presentation of Cumulative Antimicrobial Susceptibility Test Data, 4th Edition. CLSI, 2014. Chapter 6.4

This AMR package includes this methodology with the first_isolate() function. It adopts the episode of a year (can be changed by user) and it starts counting days after every selected isolate. This new variable can easily be added to our data:

-
data <- data %>% 
-  mutate(first = first_isolate(.))
-# NOTE: Using column `bacteria` as input for `col_mo`.
-# NOTE: Using column `date` as input for `col_date`.
-# NOTE: Using column `patient_id` as input for `col_patient_id`.
-# => Found 2,956 first isolates (59.1% of total)
-

So only 59.1% is suitable for resistance analysis! We can now filter on it with the filter() function, also from the dplyr package:

-
data_1st <- data %>% 
-  filter(first == TRUE)
+ +

So only 59% is suitable for resistance analysis! We can now filter on it with the filter() function, also from the dplyr package:

+

For future use, the above two syntaxes can be shortened with the filter_first_isolate() function:

-
data_1st <- data %>% 
-  filter_first_isolate()
+

@@ -499,30 +499,30 @@ ab_interpretations <- 1 -2010-10-23 -K10 +2010-03-08 +G3 B_ESCHR_COL -R S +I S S TRUE 2 -2011-03-17 -K10 +2010-05-08 +G3 B_ESCHR_COL -R -R S S +R +S FALSE 3 -2011-08-12 -K10 +2010-06-21 +G3 B_ESCHR_COL S S @@ -532,21 +532,21 @@ ab_interpretations <- 4 -2012-02-24 -K10 +2010-12-01 +G3 B_ESCHR_COL -S R S S -TRUE +R +FALSE 5 -2012-04-19 -K10 +2011-01-05 +G3 B_ESCHR_COL -S +R S S S @@ -554,32 +554,32 @@ ab_interpretations <- 6 -2013-08-25 -K10 +2012-01-16 +G3 B_ESCHR_COL -R -R S -R +S +S +S TRUE 7 -2014-01-04 -K10 +2012-04-11 +G3 B_ESCHR_COL -R -R S S +R +S FALSE 8 -2014-03-05 -K10 +2012-10-23 +G3 B_ESCHR_COL -R +S S S S @@ -587,8 +587,8 @@ ab_interpretations <- 9 -2014-03-11 -K10 +2012-11-24 +G3 B_ESCHR_COL S S @@ -598,29 +598,29 @@ ab_interpretations <- 10 -2014-06-20 -K10 +2014-01-26 +G3 B_ESCHR_COL S S S S -FALSE +TRUE

Only 3 isolates are marked as ‘first’ according to CLSI guideline. But when reviewing the antibiogram, it is obvious that some isolates are absolutely different strains and should be included too. This is why we weigh isolates, based on their antibiogram. The key_antibiotics() function adds a vector with 18 key antibiotics: 6 broad spectrum ones, 6 small spectrum for Gram negatives and 6 small spectrum for Gram positives. These can be defined by the user.

If a column exists with a name like ‘key(…)ab’ the first_isolate() function will automatically use it and determine the first weighted isolates. Mind the NOTEs in below output:

-
data <- data %>% 
-  mutate(keyab = key_antibiotics(.)) %>% 
-  mutate(first_weighted = first_isolate(.))
-# NOTE: Using column `bacteria` as input for `col_mo`.
-# NOTE: Using column `bacteria` as input for `col_mo`.
-# NOTE: Using column `date` as input for `col_date`.
-# NOTE: Using column `patient_id` as input for `col_patient_id`.
-# NOTE: Using column `keyab` as input for `col_keyantibiotics`. Use col_keyantibiotics  = FALSE to prevent this.
-# [Criterion] Inclusion based on key antibiotics, ignoring I.
-# => Found 4,383 first weighted isolates (87.7% of total)
+ @@ -637,11 +637,11 @@ ab_interpretations <- - - + + - + @@ -649,20 +649,20 @@ ab_interpretations <- - - + + - - + + - - + + @@ -673,22 +673,22 @@ ab_interpretations <- - - + + - - + + - - + + - + @@ -697,34 +697,34 @@ ab_interpretations <- - - + + - - - + + + - - + + - - + + - - + + - + @@ -733,40 +733,40 @@ ab_interpretations <- - - + + - + - - + + - - + +
isolate12010-10-23K102010-03-08G3 B_ESCHR_COLR SI S S TRUE22011-03-17K102010-05-08G3 B_ESCHR_COLRR S SRS FALSE TRUE
32011-08-12K102010-06-21G3 B_ESCHR_COL S S42012-02-24K102010-12-01G3 B_ESCHR_COLS R S STRUERFALSE TRUE
52012-04-19K102011-01-05G3 B_ESCHR_COLSR S S S62013-08-25K102012-01-16G3 B_ESCHR_COLRR SRSSS TRUE TRUE
72014-01-04K102012-04-11G3 B_ESCHR_COLRR S SRS FALSE TRUE
82014-03-05K102012-10-23G3 B_ESCHR_COLRS S S S92014-03-11K102012-11-24G3 B_ESCHR_COL S S S S FALSETRUEFALSE
102014-06-20K102014-01-26G3 B_ESCHR_COL S S S SFALSEFALSETRUETRUE
-

Instead of 3, now 9 isolates are flagged. In total, 87.7% of all isolates are marked ‘first weighted’ - 28.5% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.

+

Instead of 3, now 9 isolates are flagged. In total, 88.5% of all isolates are marked ‘first weighted’ - 29.5% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.

As with filter_first_isolate(), there’s a shortcut for this new algorithm too:

-
data_1st <- data %>% 
-  filter_first_weighted_isolate()
-

So we end up with 4,383 isolates for analysis.

+ +

So we end up with 4,424 isolates for analysis.

We can remove unneeded columns:

-
data_1st <- data_1st %>% 
-  select(-c(first, keyab))
+

Now our data looks like:

-
head(data_1st)
+
head(data_1st)
@@ -785,41 +785,26 @@ ab_interpretations <- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - + + - + + + + + + + + + + + + + + + + @@ -829,49 +814,64 @@ ab_interpretations <- pneumoniae - - - + + + - + + + + + + + + + + + + + + + + - - + + - + - - - - + + + + - - + + - - + + @@ -888,12 +888,12 @@ ab_interpretations <- Dispersion of species

To just get an idea how the species are distributed, create a frequency table with our freq() function. We created the genus and species column earlier based on the microbial ID. With paste(), we can concatenate them together.

The freq() function can be used like the base R language was intended:

-
freq(paste(data_1st$genus, data_1st$species))
+
freq(paste(data_1st$genus, data_1st$species))

Or can be used like the dplyr way, which is easier readable:

-
data_1st %>% freq(genus, species)
-

Frequency table of genus and species from a data.frame (4,383 x 13)
+

data_1st %>% freq(genus, species)
+

Frequency table of genus and species from a data.frame (4,424 x 13)
Columns: 2
-Length: 4,383 (of which NA: 0 = 0.00%)
+Length: 4,424 (of which NA: 0 = 0.00%)
Unique: 4

Shortest: 16
Longest: 24

@@ -910,33 +910,33 @@ Longest: 24

- - - - + + + + - - - - + + + + - - - - + + + + - - - + + + @@ -946,12 +946,12 @@ Longest: 24

Resistance percentages

The functions portion_R, portion_RI, portion_I, portion_IS and portion_S can be used to determine the portion of a specific antimicrobial outcome. They can be used on their own:

-
data_1st %>% portion_IR(amox)
-# [1] 0.4832307
+

Or can be used in conjuction with group_by() and summarise(), both from the dplyr package:

-
data_1st %>% 
-  group_by(hospital) %>% 
-  summarise(amoxicillin = portion_IR(amox))
+
data_1st %>% 
+  group_by(hospital) %>% 
+  summarise(amoxicillin = portion_IR(amox))
date2014-06-07Y9Hospital AB_KLBSL_PNERSSSFGram negativeKlebsiellapneumoniaeTRUE
2010-06-10Z1Hospital BB_ESCHR_COLRSSSFGram negativeEscherichiacoliTRUE
2012-03-20J62010-05-26E8 Hospital CB_STRPTC_PNEB_ESCHR_COLR SRSMGram negativeEscherichiacoliTRUE
2016-11-27D6Hospital BB_STRPTC_PNER S S RTRUE
2016-10-31M5
2015-03-24J2 Hospital A B_ESCHR_COLS R S SS M Gram negative Escherichia coli TRUE
2014-09-12Y4Hospital AB_STPHY_AURSSSSFGram positiveStaphylococcusaureusTRUE
2016-05-05W82015-05-27M8 Hospital B B_ESCHR_COL R S S SFM Gram negative Escherichia coli TRUE
2016-03-10G8Hospital AB_STRPTC_PNE2017-10-14R8Hospital CB_STPHY_AUR S S SRMSF Gram positiveStreptococcuspneumoniaeStaphylococcusaureus TRUE
1 Escherichia coli2,12848.6%2,12848.6%2,14148.4%2,14148.4%
2 Staphylococcus aureus1,11025.3%3,23873.9%1,12625.5%3,26773.8%
3 Streptococcus pneumoniae68415.6%3,92289.5%69915.8%3,96689.6%
4 Klebsiella pneumoniae46110.5%4,38345810.4%4,424 100.0%
@@ -960,27 +960,27 @@ Longest: 24

- + - + - + - +
hospital
Hospital A0.49591690.4566642
Hospital B0.46909560.4615894
Hospital C0.50755290.4807122
Hospital D0.46953410.4579008

Of course it would be very convenient to know the number of isolates responsible for the percentages. For that purpose the n_rsi() can be used, which works exactly like n_distinct() from the dplyr package. It counts all isolates available for every group (i.e. values S, I or R):

-
data_1st %>% 
-  group_by(hospital) %>% 
-  summarise(amoxicillin = portion_IR(amox),
-            available = n_rsi(amox))
+
data_1st %>% 
+  group_by(hospital) %>% 
+  summarise(amoxicillin = portion_IR(amox),
+            available = n_rsi(amox))
@@ -990,32 +990,32 @@ Longest: 24

- - + + - - + + - - + + - - + +
hospital
Hospital A0.495916913470.45666421373
Hospital B0.469095615370.46158941510
Hospital C0.50755296620.4807122674
Hospital D0.46953418370.4579008867

These functions can also be used to get the portion of multiple antibiotics, to calculate co-resistance very easily:

-
data_1st %>% 
-  group_by(genus) %>% 
-  summarise(amoxicillin = portion_S(amcl),
-            gentamicin = portion_S(gent),
-            "amox + gent" = portion_S(amcl, gent))
+
data_1st %>% 
+  group_by(genus) %>% 
+  summarise(amoxicillin = portion_S(amcl),
+            gentamicin = portion_S(gent),
+            "amox + gent" = portion_S(amcl, gent))
@@ -1026,94 +1026,94 @@ Longest: 24

- - - + + + - - - + + + - - - + + + - + - +
genus
Escherichia0.74812030.91635340.97650380.73563760.90331620.9729099
Klebsiella0.77223430.92407810.99132320.74454150.89301310.9694323
Staphylococcus0.75675680.92342340.98648650.75666070.91740670.9760213
Streptococcus0.73830410.7668097 0.00000000.73830410.7668097

To make a transition to the next part, let’s see how this difference could be plotted:

-
data_1st %>% 
-  group_by(genus) %>% 
-  summarise("1. Amoxicillin" = portion_S(amcl),
-            "2. Gentamicin" = portion_S(gent),
-            "3. Amox + gent" = portion_S(amcl, gent)) %>% 
-  tidyr::gather("Antibiotic", "S", -genus) %>%
-  ggplot(aes(x = genus,
-             y = S,
-             fill = Antibiotic)) +
-  geom_col(position = "dodge2")
+
data_1st %>% 
+  group_by(genus) %>% 
+  summarise("1. Amoxicillin" = portion_S(amcl),
+            "2. Gentamicin" = portion_S(gent),
+            "3. Amox + gent" = portion_S(amcl, gent)) %>% 
+  tidyr::gather("Antibiotic", "S", -genus) %>%
+  ggplot(aes(x = genus,
+             y = S,
+             fill = Antibiotic)) +
+  geom_col(position = "dodge2")

Plots

To show results in plots, most R users would nowadays use the ggplot2 package. This package lets you create plots in layers. You can read more about it on their website. A quick example would look like these syntaxes:

-
ggplot(data = a_data_set,
-       mapping = aes(x = year,
-                     y = value)) +
-  geom_col() +
-  labs(title = "A title",
-       subtitle = "A subtitle",
-       x = "My X axis",
-       y = "My Y axis")
-
-ggplot(a_data_set,
-       aes(year, value) +
-  geom_bar()
+
ggplot(data = a_data_set,
+       mapping = aes(x = year,
+                     y = value)) +
+  geom_col() +
+  labs(title = "A title",
+       subtitle = "A subtitle",
+       x = "My X axis",
+       y = "My Y axis")
+
+ggplot(a_data_set,
+       aes(year, value) +
+  geom_bar()

The AMR package contains functions to extend this ggplot2 package, for example geom_rsi(). It automatically transforms data with count_df() or portion_df() and show results in stacked bars. Its simplest and shortest example:

-
ggplot(data_1st) +
-  geom_rsi(translate_ab = FALSE)
+
ggplot(data_1st) +
+  geom_rsi(translate_ab = FALSE)

Omit the translate_ab = FALSE to have the antibiotic codes (amox, amcl, cipr, gent) translated to official WHO names (amoxicillin, amoxicillin and betalactamase inhibitor, ciprofloxacin, gentamicin).

If we group on e.g. the genus column and add some additional functions from our package, we can create this:

-
# group the data on `genus`
-ggplot(data_1st %>% group_by(genus)) + 
-  # create bars with genus on x axis
-  # it looks for variables with class `rsi`,
-  # of which we have 4 (earlier created with `as.rsi`)
-  geom_rsi(x = "genus") + 
-  # split plots on antibiotic
-  facet_rsi(facet = "Antibiotic") +
-  # make R red, I yellow and S green
-  scale_rsi_colours() +
-  # show percentages on y axis
-  scale_y_percent(breaks = 0:4 * 25) +
-  # turn 90 degrees, make it bars instead of columns
-  coord_flip() +
-  # add labels
-  labs(title = "Resistance per genus and antibiotic", 
-       subtitle = "(this is fake data)") +
-  # and print genus in italic to follow our convention
-  # (is now y axis because we turned the plot)
-  theme(axis.text.y = element_text(face = "italic"))
+

To simplify this, we also created the ggplot_rsi() function, which combines almost all above functions:

-
data_1st %>% 
-  group_by(genus) %>%
-  ggplot_rsi(x = "genus",
-             facet = "Antibiotic",
-             breaks = 0:4 * 25,
-             datalabels = FALSE) +
-  coord_flip()
+

@@ -1141,26 +1141,26 @@ Longest: 24

We can transform the data and apply the test in only a couple of lines:

-
septic_patients %>%
-  filter(hospital_id %in% c("A", "D")) %>% # filter on only hospitals A and D
-  select(hospital_id, fosf) %>%            # select the hospitals and fosfomycin
-  group_by(hospital_id) %>%                # group on the hospitals
-  count_df(combine_IR = TRUE) %>%          # count all isolates per group (hospital_id)
-  tidyr::spread(hospital_id, Value) %>%    # transform output so A and D are columns
-  select(A, D) %>%                         # and select these only
-  as.matrix() %>%                          # transform to good old matrix for fisher.test()
-  fisher.test()                            # do Fisher's Exact Test
-# 
-#   Fisher's Exact Test for Count Data
-# 
-# data:  .
-# p-value = 0.03104
-# alternative hypothesis: true odds ratio is not equal to 1
-# 95 percent confidence interval:
-#  1.054283 4.735995
-# sample estimates:
-# odds ratio 
-#   2.228006
+
septic_patients %>%
+  filter(hospital_id %in% c("A", "D")) %>% # filter on only hospitals A and D
+  select(hospital_id, fosf) %>%            # select the hospitals and fosfomycin
+  group_by(hospital_id) %>%                # group on the hospitals
+  count_df(combine_IR = TRUE) %>%          # count all isolates per group (hospital_id)
+  tidyr::spread(hospital_id, Value) %>%    # transform output so A and D are columns
+  select(A, D) %>%                         # and select these only
+  as.matrix() %>%                          # transform to good old matrix for fisher.test()
+  fisher.test()                            # do Fisher's Exact Test
+# 
+#   Fisher's Exact Test for Count Data
+# 
+# data:  .
+# p-value = 0.03104
+# alternative hypothesis: true odds ratio is not equal to 1
+# 95 percent confidence interval:
+#  1.054283 4.735995
+# sample estimates:
+# odds ratio 
+#   2.228006

As can be seen, the p value is 0.03, which means that the fosfomycin resistances found in hospital A and D are really different.

diff --git a/docs/articles/AMR_files/figure-html/plot 1-1.png b/docs/articles/AMR_files/figure-html/plot 1-1.png index 353cc3c4..77cb0e5f 100644 Binary files a/docs/articles/AMR_files/figure-html/plot 1-1.png and b/docs/articles/AMR_files/figure-html/plot 1-1.png differ diff --git a/docs/articles/AMR_files/figure-html/plot 3-1.png b/docs/articles/AMR_files/figure-html/plot 3-1.png index 433da064..ec93c11c 100644 Binary files a/docs/articles/AMR_files/figure-html/plot 3-1.png and b/docs/articles/AMR_files/figure-html/plot 3-1.png differ diff --git a/docs/articles/AMR_files/figure-html/plot 4-1.png b/docs/articles/AMR_files/figure-html/plot 4-1.png index 80fdb87d..9011c3e9 100644 Binary files a/docs/articles/AMR_files/figure-html/plot 4-1.png and b/docs/articles/AMR_files/figure-html/plot 4-1.png differ diff --git a/docs/articles/AMR_files/figure-html/plot 5-1.png b/docs/articles/AMR_files/figure-html/plot 5-1.png index 66135f32..6c99bc50 100644 Binary files a/docs/articles/AMR_files/figure-html/plot 5-1.png and b/docs/articles/AMR_files/figure-html/plot 5-1.png differ diff --git a/docs/index.html b/docs/index.html index 73a9c432..5f829e0d 100644 --- a/docs/index.html +++ b/docs/index.html @@ -190,11 +190,13 @@

(TLDR - to find out how to conduct AMR analysis, please continue reading here to get started.


AMR is a free and open-source R package to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial properties by using evidence-based methods. It supports any table format, including WHONET/EARS-Net data.

+

After installing this package, R knows almost all ~20.000 microorganisms and ~500 antibiotics by name and code, and knows all about valid RSI and MIC values.

We created this package for both academic research and routine analysis at the Faculty of Medical Sciences of the University of Groningen and the Medical Microbiology & Infection Prevention (MMBI) department of the University Medical Center Groningen (UMCG). This R package is actively maintained and free software; you can freely use and distribute it for both personal and commercial (but not patent) purposes under the terms of the GNU General Public License version 2.0 (GPL-2), as published by the Free Software Foundation. Read the full license here.

This package can be used for:

+ +

diff --git a/docs/news/index.html b/docs/news/index.html index 905a6bcd..978dc238 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -236,13 +236,28 @@

@@ -266,12 +294,16 @@
  • Functions atc_ddd() and atc_groups() have been renamed atc_online_ddd() and atc_online_groups(). The old functions are deprecated and will be removed in a future version.
  • Function guess_mo() is now deprecated in favour of as.mo() and will be removed in future versions
  • Function guess_atc() is now deprecated in favour of as.atc() and will be removed in future versions
  • -
  • Function eucast_rules():
  • +
  • Function eucast_rules(): + +
  • +
  • Improvements for as.mo(): + +
  • +
  • Function first_isolate(): + +
  • A note to the manual pages of the portion functions, that low counts can influence the outcome and that the portion functions may camouflage this, since they only return the portion (albeit being dependent on the minimum parameter)
  • Merged data sets microorganisms.certe and microorganisms.umcg into microorganisms.codes
  • Function mo_taxonomy() now contains the kingdom too
  • -
  • Reduce false positives for is.rsi.eligible() -
  • +
  • Reduce false positives for is.rsi.eligible() using the new threshold parameter
  • New colours for scale_rsi_colours()
  • Summaries of class mo will now return the top 3 and the unique count, e.g. using summary(mo)
  • Small text updates to summaries of class rsi and mic
  • -
  • Frequency tables (freq() function):
  • +
  • Frequency tables (freq() function): + +
  • Function scale_y_percent() now contains the limits parameter
  • Automatic parameter filling for mdro(), key_antibiotics() and eucast_rules()
  • Updated examples for resistance prediction (resistance_predict() function)
  • -
  • Fix for as.mic() to support more values ending in (several) zeroes

  • +
  • Fix for as.mic() to support more values ending in (several) zeroes
  • @@ -369,7 +408,8 @@ septic_patients %>%
  • EUCAST_rules was renamed to eucast_rules, the old function still exists as a deprecated function
  • -
  • Big changes to the eucast_rules function:
  • +
  • Big changes to the eucast_rules function: + +
  • Added column kingdom to the microorganisms data set, and function mo_kingdom to look up values
  • Tremendous speed improvement for as.mo (and subsequently all mo_* functions), as empty values wil be ignored a priori
  • Fewer than 3 characters as input for as.mo will return NA
  • -
  • Function as.mo (and all mo_* wrappers) now supports genus abbreviations with “species” attached r as.mo("E. species") # B_ESCHR mo_fullname("E. spp.") # "Escherichia species" as.mo("S. spp") # B_STPHY mo_fullname("S. species") # "Staphylococcus species" +
  • +

    Function as.mo (and all mo_* wrappers) now supports genus abbreviations with “species” attached

    +
    as.mo("E. species")        # B_ESCHR
    +mo_fullname("E. spp.")     # "Escherichia species"
    +as.mo("S. spp")            # B_STPHY
    +mo_fullname("S. species")  # "Staphylococcus species"
  • Added parameter combine_IR (TRUE/FALSE) to functions portion_df and count_df, to indicate that all values of I and R must be merged into one, so the output only consists of S vs. IR (susceptible vs. non-susceptible)
  • Fix for portion_*(..., as_percent = TRUE) when minimal number of isolates would not be met
  • @@ -391,18 +438,19 @@ septic_patients %>%
  • 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(): + +
  • first_isolate now tries to find columns to use as input when parameters are left blank
  • Improvements for MDRO algorithm (function mdro)
  • @@ -424,7 +474,8 @@ septic_patients %>%
  • ggplot_rsi and scale_y_percent have breaks parameter
  • -
  • AI improvements for as.mo:
  • +
  • AI improvements for as.mo: + +
  • Fix for join functions
  • Speed improvement for is.rsi.eligible, now 15-20 times faster
  • In g.test, when sum(x) is below 1000 or any of the expected values is below 5, Fisher’s Exact Test will be suggested
  • @@ -465,7 +518,8 @@ septic_patients %>% New

    @@ -535,15 +653,21 @@ septic_patients %>% New

    + +
  • Determining bacterial ID: + +
  • For convience, new descriptive statistical functions kurtosis and skewness that are lacking in base R - they are generic functions and have support for vectors, data.frames and matrices
  • Function g.test to perform the Χ2 distributed G-test, which use is the same as chisq.test
  • -
  • Function ratio to transform a vector of values to a preset ratio
  • +
  • +Function ratio to transform a vector of values to a preset ratio + +
  • Support for Addins menu in RStudio to quickly insert %in% or %like% (and give them keyboard shortcuts), or to view the datasets that come with this package
  • Function p.symbol to transform p values to their related symbols: 0 '***' 0.001 '**' 0.01 '*' 0.05 '.' 0.1 ' ' 1
  • Functions clipboard_import and clipboard_export as helper functions to quickly copy and paste from/to software like Excel and SPSS. These functions use the clipr package, but are a little altered to also support headless Linux servers (so you can use it in RStudio Server)
  • -
  • New for frequency tables (function freq):
  • +
  • New for frequency tables (function freq): + +
  • +

    @@ -605,21 +741,27 @@ septic_patients %>%
  • Small improvements to the microorganisms dataset (especially for Salmonella) and the column bactid now has the new class "bactid"
  • -
  • Combined MIC/RSI values will now be coerced by the rsi and mic functions:
  • +
  • Combined MIC/RSI values will now be coerced by the rsi and mic functions: + +
  • Now possible to coerce MIC values with a space between operator and value, i.e. as.mic("<= 0.002") now works
  • Classes rsi and mic do not add the attribute package.version anymore
  • Added "groups" option for atc_property(..., property). It will return a vector of the ATC hierarchy as defined by the WHO. The new function atc_groups is a convenient wrapper around this.
  • Build-in host check for atc_property as it requires the host set by url to be responsive
  • Improved first_isolate algorithm to exclude isolates where bacteria ID or genus is unavailable
  • Fix for warning hybrid evaluation forced for row_number (924b62) from the dplyr package v0.7.5 and above
  • -
  • Support for empty values and for 1 or 2 columns as input for guess_bactid (now called as.bactid)
  • +
  • Support for empty values and for 1 or 2 columns as input for guess_bactid (now called as.bactid) +
    • So yourdata %>% select(genus, species) %>% as.bactid() now also works
    • +
    +
  • Other small fixes
  • @@ -627,11 +769,14 @@ septic_patients %>%

    Other

    @@ -650,10 +795,13 @@ septic_patients %>%
  • 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
  • -
  • Function MDRO to determine Multi Drug Resistant Organisms (MDRO) with support for country-specific guidelines.
  • +
  • Function MDRO to determine Multi Drug Resistant Organisms (MDRO) with support for country-specific guidelines. + +
  • New algorithm to determine weighted isolates, can now be "points" or "keyantibiotics", see ?first_isolate
  • New print format for tibbles and data.tables
  • diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index 6102d6c7..ac0898dd 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -1,4 +1,4 @@ -pandoc: 1.17.2 +pandoc: 2.3.1 pkgdown: 1.3.0 pkgdown_sha: ~ articles: diff --git a/docs/reference/WHONET.html b/docs/reference/WHONET.html index 7121db55..b7e6268a 100644 --- a/docs/reference/WHONET.html +++ b/docs/reference/WHONET.html @@ -241,7 +241,7 @@

    A data.frame with 500 observations and 53 variables:

    Identification number

    ID of the sample

    Specimen number

    ID of the specimen

    -
    Organism

    Microorganisms, can be coerced with as.mo

    +
    Organism

    Name of the microorganism. Before analysis, you should transform this to a valid microbial class, using as.mo.

    Country

    Country of origin

    Laboratory

    Name of laboratory

    Last name

    Last name of patient

    @@ -264,7 +264,7 @@
    Inducible clindamycin resistance

    Clindamycin can be induced?

    Comment

    Other comments

    Date of data entry

    Date this data was entered in WHONET

    -
    AMP_ND10:CIP_EE

    27 different antibiotics. You can lookup the abbreviatons in the antibiotics data set, or use e.g. atc_name("AMP") to get the official name immediately.

    +
    AMP_ND10:CIP_EE

    27 different antibiotics. You can lookup the abbreviatons in the antibiotics data set, or use e.g. atc_name("AMP") to get the official name immediately. Before analysis, you should transform this to a valid antibiotic class, using as.rsi.

    Read more on our website!

    diff --git a/docs/reference/as.rsi.html b/docs/reference/as.rsi.html index 37c5a6fa..2289ba8a 100644 --- a/docs/reference/as.rsi.html +++ b/docs/reference/as.rsi.html @@ -238,7 +238,7 @@ is.rsi(x) -is.rsi.eligible(x) +is.rsi.eligible(x, threshold = 0.05)

    Arguments

    @@ -247,6 +247,10 @@ + + + +
    x

    vector

    threshold

    maximum fraction of x that is allowed to fail transformation, see Examples

    Value

    @@ -286,10 +290,15 @@ On our website https://msberends.gitla septic_patients %>% mutate_at(vars(peni:rifa), as.rsi) + # fastest way to transform all columns with already valid AB results to class `rsi`: septic_patients %>% mutate_if(is.rsi.eligible, as.rsi) + +# default threshold of `is.rsi.eligible` is 5%. +is.rsi.eligible(WHONET$`First name`) # fails, >80% is invalid +is.rsi.eligible(WHONET$`First name`, threhold = 0.9) # succeeds # }