diff --git a/DESCRIPTION b/DESCRIPTION index b547216b..83c33c5e 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 0.7.0.9012 -Date: 2019-06-18 +Version: 0.7.0.9013 +Date: 2019-06-22 Title: Antimicrobial Resistance Analysis Authors@R: c( person( diff --git a/NEWS.md b/NEWS.md index 7143a761..fbc28680 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# AMR 0.7.0.9012 +# AMR 0.7.0.9013 #### New * Function `rsi_df()` to transform a `data.frame` to a data set containing only the microbial interpretation (S, I, R), the antibiotic, the percentage of S/I/R and the number of available isolates. This is a convenient combination of the existing functions `count_df()` and `portion_df()` to immediately show resistance percentages and number of available isolates: @@ -12,7 +12,7 @@ # 3 Ciprofloxacin SI 0.8381831 1181 # 4 Ciprofloxacin R 0.1618169 228 ``` -* Support for all scientifically published pathotypes of *E. coli* to date. Supported are: +* Support for all scientifically published pathotypes of *E. coli* to date (that we could find). Supported are: * AIEC (Adherent-Invasive *E. coli*) * ATEC (Atypical Entero-pathogenic *E. coli*) @@ -51,9 +51,10 @@ * Fixed a EUCAST rule for Staphylococci, where amikacin resistance would not be inferred from tobramycin * Removed `latest_annual_release` from the `catalogue_of_life_version()` function * Removed antibiotic code `PVM1` from the `antibiotics` data set as this was a duplicate of `PME` -* Fixed bug where not all old taxonomic named would not be printed when using a vector as input for `as.mo()` +* Fixed bug where not all old taxonomic names would be printed, when using a vector as input for `as.mo()` * Manually added *Trichomonas vaginalis* from the kingdom of Protozoa, which is missing from the Catalogue of Life * Small improvements to `plot()` and `barplot()` for MIC and RSI classes +* Allow Catalogue of Life IDs to be coerced by `as.mo()` #### Other * Fixed a note thrown by CRAN tests diff --git a/R/mo.R b/R/mo.R index 2aaaf9ca..d521638b 100755 --- a/R/mo.R +++ b/R/mo.R @@ -148,9 +148,10 @@ #' as.mo("Staphylococcus aureus") #' as.mo("Staphylococcus aureus (MRSA)") #' as.mo("Sthafilokkockus aaureuz") # handles incorrect spelling -#' as.mo("MRSA") # Methicillin Resistant S. aureus -#' as.mo("VISA") # Vancomycin Intermediate S. aureus -#' as.mo("VRSA") # Vancomycin Resistant S. aureus +#' as.mo("MRSA") # Methicillin Resistant S. aureus +#' as.mo("VISA") # Vancomycin Intermediate S. aureus +#' as.mo("VRSA") # Vancomycin Resistant S. aureus +#' as.mo(22242419) # Catalogue of Life ID #' #' # Dyslexia is no problem - these all work: #' as.mo("Ureaplasma urealyticum") @@ -232,11 +233,11 @@ as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, allow_uncertain = TRUE, & isFALSE(Lancefield)) { y <- x - # } else if (!any(is.na(mo_hist)) - # & isFALSE(Becker) - # & isFALSE(Lancefield)) { - # # check previously found results - # y <- mo_hist + # } else if (!any(is.na(mo_hist)) + # & isFALSE(Becker) + # & isFALSE(Lancefield)) { + # # check previously found results + # y <- mo_hist } else if (all(tolower(x) %in% microorganismsDT$fullname_lower) & isFALSE(Becker) @@ -564,6 +565,17 @@ exec_as.mo <- function(x, next } + found <- microorganismsDT[col_id == x_backup[i], ..property][[1]] + # is a valid Catalogue of Life ID + if (NROW(found) > 0) { + x[i] <- found[1L] + if (initial_search == TRUE) { + set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history) + } + next + } + + # WHONET: xxx = no growth if (tolower(as.character(paste0(x_backup_without_spp[i], ""))) %in% c("", "xxx", "na", "nan")) { x[i] <- NA_character_ @@ -642,6 +654,18 @@ exec_as.mo <- function(x, } next } + # support for: + # - AIEC (Adherent-Invasive E. coli) + # - ATEC (Atypical Entero-pathogenic E. coli) + # - DAEC (Diffusely Adhering E. coli) + # - EAEC (Entero-Aggresive E. coli) + # - EHEC (Entero-Haemorrhagic E. coli) + # - EIEC (Entero-Invasive E. coli) + # - EPEC (Entero-Pathogenic E. coli) + # - ETEC (Entero-Toxigenic E. coli) + # - NMEC (Neonatal Meningitis‐causing E. coli) + # - STEC (Shiga-toxin producing E. coli) + # - UPEC (Uropathogenic E. coli) if (toupper(x_backup_without_spp[i]) %in% c("AIEC", "ATEC", "DAEC", "EAEC", "EHEC", "EIEC", "EPEC", "ETEC", "NMEC", "STEC", "UPEC") | x_backup_without_spp[i] %like% "O?(26|103|104|104|111|121|145|157)") { x[i] <- microorganismsDT[mo == 'B_ESCHR_COL', ..property][[1]][1L] @@ -770,7 +794,7 @@ exec_as.mo <- function(x, } } - # FIRST TRY FULLNAMES AND CODES + # FIRST TRY FULLNAMES AND CODES ---- # if only genus is available, return only genus if (all(!c(x[i], x_trimmed[i]) %like% " ")) { found <- microorganismsDT[fullname_lower %in% tolower(c(x_species[i], x_trimmed_species[i])), ..property][[1]] @@ -1465,6 +1489,9 @@ unregex <- function(x) { } get_mo_code <- function(x, property) { + # don't use right now + return(NULL) + if (property == "mo") { unique(x) } else { diff --git a/R/mo_property.R b/R/mo_property.R index e02bdae8..f9a06003 100755 --- a/R/mo_property.R +++ b/R/mo_property.R @@ -279,7 +279,7 @@ mo_ref <- function(x, ...) { #' @export mo_authors <- function(x, ...) { x <- mo_validate(x = x, property = "ref", ...) - # remove last 4 digits and presumably the comma and space that preceeds them + # remove last 4 digits and presumably the comma and space that preceed them x[!is.na(x)] <- gsub(",? ?[0-9]{4}", "", x[!is.na(x)]) suppressWarnings(x) } @@ -303,35 +303,52 @@ mo_rank <- function(x, ...) { #' @export mo_taxonomy <- function(x, language = get_locale(), ...) { x <- AMR::as.mo(x, ...) - base::list(kingdom = mo_kingdom(x, language = language), - phylum = mo_phylum(x, language = language), - class = mo_class(x, language = language), - order = mo_order(x, language = language), - family = mo_family(x, language = language), - genus = mo_genus(x, language = language), - species = mo_species(x, language = language), - subspecies = mo_subspecies(x, language = language)) + base::list(kingdom = AMR::mo_kingdom(x, language = language), + phylum = AMR::mo_phylum(x, language = language), + class = AMR::mo_class(x, language = language), + order = AMR::mo_order(x, language = language), + family = AMR::mo_family(x, language = language), + genus = AMR::mo_genus(x, language = language), + species = AMR::mo_species(x, language = language), + subspecies = AMR::mo_subspecies(x, language = language)) } #' @rdname mo_property #' @export mo_synonyms <- function(x, ...) { - x <- AMR::as.mo(x, ...) - col_id <- AMR::microorganisms[which(AMR::microorganisms$mo == x), "col_id"] - if (is.na(col_id) | !col_id %in% AMR::microorganisms.old$col_id_new) { - return(NULL) + x <- as.mo(x, ...) + IDs <- AMR::mo_property(x = x, property = "col_id", language = NULL) + syns <- lapply(IDs, function(col_id) { + res <- sort(AMR::microorganisms.old[which(AMR::microorganisms.old$col_id_new == col_id), "fullname"]) + if (length(res) == 0) { + NULL + } else { + res + } + }) + if (length(syns) > 1) { + names(syns) <- mo_fullname(x) + syns + } else { + unlist(syns) } - sort(AMR::microorganisms.old[which(AMR::microorganisms.old$col_id_new == col_id), "fullname"]) } #' @rdname mo_property #' @export mo_info <- function(x, language = get_locale(), ...) { x <- AMR::as.mo(x, ...) - c(mo_taxonomy(x, language = language), - list(synonyms = mo_synonyms(x), - url = unname(mo_url(x, open = FALSE)), - ref = mo_ref(x))) + info <- lapply(x, function(y) + c(mo_taxonomy(y, language = language), + list(synonyms = mo_synonyms(y), + url = unname(mo_url(y, open = FALSE)), + ref = mo_ref(y)))) + if (length(info) > 1) { + names(info) <- mo_fullname(x) + info + } else { + info[[1L]] + } } #' @rdname mo_property @@ -350,7 +367,7 @@ mo_url <- function(x, open = FALSE, ...) { NA_character_)) u <- df$url - names(u) <- mo_fullname(mo) + names(u) <- AMR::mo_fullname(mo) if (open == TRUE) { if (length(u) > 1) { warning("only the first URL will be opened, as `browseURL()` only suports one string.") @@ -400,12 +417,15 @@ mo_validate <- function(x, property, ...) { if (!all(x %in% pull(AMR::microorganisms, property)) | Becker %in% c(TRUE, "all") | Lancefield %in% c(TRUE, "all")) { - exec_as.mo(x, property = property, ...) - } else { - if (property == "mo") { - return(structure(x, class = "mo")) - } else { - return(x) - } + x <- exec_as.mo(x, property = property, ...) } + + if (property == "mo") { + return(structure(x, class = "mo")) + } else if (property == "col_id") { + return(as.integer(x)) + } else { + return(x) + } + } diff --git a/data-raw/reproduction_of_microorganisms.R b/data-raw/reproduction_of_microorganisms.R index 4e187753..db8b7217 100644 --- a/data-raw/reproduction_of_microorganisms.R +++ b/data-raw/reproduction_of_microorganisms.R @@ -525,15 +525,19 @@ MOs <- MOs %>% MOs <- MOs %>% arrange(fullname) MOs.old <- MOs.old %>% arrange(fullname) -# save it +# transform MOs <- as.data.frame(MOs, stringsAsFactors = FALSE) MOs.old <- as.data.frame(MOs.old, stringsAsFactors = FALSE) class(MOs$mo) <- "mo" +MOs$col_id <- as.integer(MOs$col_id) +MOs.old$col_id <- as.integer(MOs.old$col_id) +MOs.old$col_id_new <- as.integer(MOs.old$col_id_new) +# save saveRDS(MOs, "microorganisms.rds") saveRDS(MOs.old, "microorganisms.old.rds") -# on the server: +# on the server, do: usethis::use_data(microorganisms, overwrite = TRUE, version = 2) usethis::use_data(microorganisms.old, overwrite = TRUE, version = 2) rm(microorganisms) diff --git a/data/microorganisms.old.rda b/data/microorganisms.old.rda index a62408fd..5d42f9d3 100644 Binary files a/data/microorganisms.old.rda and b/data/microorganisms.old.rda differ diff --git a/data/microorganisms.rda b/data/microorganisms.rda index c27938fa..830db938 100755 Binary files a/data/microorganisms.rda and b/data/microorganisms.rda differ diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index 0f0f5d87..dc6eb7cc 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.0.9012 + 0.7.0.9013 diff --git a/docs/articles/AMR.html b/docs/articles/AMR.html index 9543f9ee..9ec1ab02 100644 --- a/docs/articles/AMR.html +++ b/docs/articles/AMR.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0.9012 + 0.7.0.9013 @@ -192,7 +192,7 @@

How to conduct AMR analysis

Matthijs S. Berends

-

18 June 2019

+

22 June 2019

@@ -201,7 +201,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 R Markdown. However, the methodology remains unchanged. This page was generated on 18 June 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 R Markdown. However, the methodology remains unchanged. This page was generated on 22 June 2019.

Introduction

@@ -217,21 +217,21 @@ -2019-06-18 +2019-06-22 abcd Escherichia coli S S -2019-06-18 +2019-06-22 abcd Escherichia coli S R -2019-06-18 +2019-06-22 efgh Escherichia coli R @@ -327,71 +327,71 @@ -2012-05-24 -H8 -Hospital B -Escherichia coli +2014-05-06 +Y6 +Hospital D +Streptococcus pneumoniae R S S S -M - - -2013-01-14 -S5 -Hospital B -Escherichia coli -S -I -S -S F - -2011-04-02 -G2 -Hospital B + +2010-10-04 +M1 +Hospital D Escherichia coli S S +S +R +M + + +2015-04-19 +L8 +Hospital D +Escherichia coli +R +R R S M -2011-09-22 -B3 +2013-08-28 +O2 +Hospital C +Streptococcus pneumoniae +R +S +S +R +F + + +2010-04-25 +T1 Hospital C Escherichia coli -R S S S -M - - -2015-07-30 -G10 -Hospital A -Klebsiella pneumoniae -R -S -S -S -M - - -2017-10-07 -X3 -Hospital A -Escherichia coli -R -S -S S F + +2010-05-31 +B3 +Hospital A +Escherichia coli +S +S +S +S +M +

Now, let’s start the cleaning and the analysis!

@@ -411,8 +411,8 @@ # # Item Count Percent Cum. Count Cum. Percent # --- ----- ------- -------- ----------- ------------- -# 1 M 10,332 51.7% 10,332 51.7% -# 2 F 9,668 48.3% 20,000 100.0% +# 1 M 10,382 51.9% 10,382 51.9% +# 2 F 9,618 48.1% 20,000 100.0%

So, we can draw at least two conclusions immediately. From a data scientists perspective, the data looks clean: only values M and F. From a researchers perspective: there are slightly more men. Nothing we didn’t already know.

The data is already quite clean, but we still need to transform some variables. The bacteria column now consists of text, and we want to add more variables based on microbial IDs later on. So, we will transform this column to valid IDs. The mutate() function of the dplyr package makes this really easy:

data <- data %>%
@@ -442,14 +442,14 @@
 # Pasteurella multocida (no new changes)
 # Staphylococcus (no new changes)
 # Streptococcus groups A, B, C, G (no new changes)
-# Streptococcus pneumoniae (1,428 new changes)
+# Streptococcus pneumoniae (1,472 new changes)
 # Viridans group streptococci (no new changes)
 # 
 # EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)
-# Table 01: Intrinsic resistance in Enterobacteriaceae (1,339 new changes)
+# Table 01: Intrinsic resistance in Enterobacteriaceae (1,278 new changes)
 # Table 02: Intrinsic resistance in non-fermentative Gram-negative bacteria (no new changes)
 # Table 03: Intrinsic resistance in other Gram-negative bacteria (no new changes)
-# Table 04: Intrinsic resistance in Gram-positive bacteria (2,671 new changes)
+# Table 04: Intrinsic resistance in Gram-positive bacteria (2,802 new changes)
 # Table 08: Interpretive rules for B-lactam agents and Gram-positive cocci (no new changes)
 # Table 09: Interpretive rules for B-lactam agents and Gram-negative rods (no new changes)
 # Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins (no new changes)
@@ -457,24 +457,24 @@
 # Table 13: Interpretive rules for quinolones (no new changes)
 # 
 # Other rules
-# Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (2,233 new changes)
-# Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (92 new changes)
+# Non-EUCAST: amoxicillin/clav acid = S where ampicillin = S (2,239 new changes)
+# Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R (112 new changes)
 # Non-EUCAST: piperacillin = R where piperacillin/tazobactam = R (no new changes)
 # Non-EUCAST: piperacillin/tazobactam = S where piperacillin = S (no new changes)
 # Non-EUCAST: trimethoprim = R where trimethoprim/sulfa = R (no new changes)
 # Non-EUCAST: trimethoprim/sulfa = S where trimethoprim = S (no new changes)
 # 
 # --------------------------------------------------------------------------
-# EUCAST rules affected 6,456 out of 20,000 rows, making a total of 7,763 edits
+# EUCAST rules affected 6,529 out of 20,000 rows, making a total of 7,903 edits
 # => added 0 test results
 # 
-# => changed 7,763 test results
-#    - 95 test results changed from S to I
-#    - 4,674 test results changed from S to R
-#    - 1,070 test results changed from I to S
-#    - 305 test results changed from I to R
-#    - 1,596 test results changed from R to S
-#    - 23 test results changed from R to I
+# => changed 7,903 test results
+#    - 117 test results changed from S to I
+#    - 4,760 test results changed from S to R
+#    - 1,044 test results changed from I to S
+#    - 324 test results changed from I to R
+#    - 1,642 test results changed from R to S
+#    - 16 test results changed from R to I
 # --------------------------------------------------------------------------
 # 
 # Use verbose = TRUE to get a data.frame with all specified edits instead.
@@ -502,7 +502,7 @@ # 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 5,673 first isolates (28.4% of total)
+# => Found 5,683 first isolates (28.4% of total)

So only 28.4% 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)
@@ -513,7 +513,7 @@

First weighted isolates

-

We made a slight twist to the CLSI algorithm, to take into account the antimicrobial susceptibility profile. Have a look at all isolates of patient W10, sorted on date:

+

We made a slight twist to the CLSI algorithm, to take into account the antimicrobial susceptibility profile. Have a look at all isolates of patient L1, sorted on date:

@@ -529,8 +529,8 @@ - - + + @@ -540,8 +540,8 @@ - - + + @@ -551,30 +551,30 @@ - - + + - - + + - - + + + + - - - + - - + + @@ -584,30 +584,30 @@ - - + + - + - - + + - - + + - - + + @@ -617,8 +617,8 @@ - - + + @@ -628,10 +628,10 @@ - - + + - + @@ -650,7 +650,7 @@ # 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 15,099 first weighted isolates (75.5% of total) +# => Found 15,191 first weighted isolates (76.0% of total)
isolate
12010-01-10W102010-06-13L1 B_ESCHR_COL S S
22010-04-21W102010-08-25L1 B_ESCHR_COL S S
32010-05-14W102010-09-09L1 B_ESCHR_COLSSR S RS FALSE
42010-05-21W102010-09-14L1 B_ESCHR_COLRI SSSSR FALSE
52010-06-09W102010-10-01L1 B_ESCHR_COL R S
62010-06-19W102010-11-15L1 B_ESCHR_COL S SRS S FALSE
72010-07-07W102010-12-31L1 B_ESCHR_COLSS RIS S FALSE
82010-07-10W102011-01-14L1 B_ESCHR_COL R S
92010-08-12W102011-01-31L1 B_ESCHR_COL S S
102010-10-15W102011-03-23L1 B_ESCHR_COLSR S S S
@@ -667,8 +667,8 @@ - - + + @@ -679,8 +679,8 @@ - - + + @@ -691,32 +691,32 @@ - - + + - - + + - - + + + + - - - + - - + + @@ -727,44 +727,44 @@ - - + + - + - - + + - - + + - + - - + + - + - - + + @@ -775,23 +775,23 @@ - - + + - + - +
isolate
12010-01-10W102010-06-13L1 B_ESCHR_COL S S
22010-04-21W102010-08-25L1 B_ESCHR_COL S S
32010-05-14W102010-09-09L1 B_ESCHR_COLSSR S RS FALSE TRUE
42010-05-21W102010-09-14L1 B_ESCHR_COLRI SSSSR FALSE TRUE
52010-06-09W102010-10-01L1 B_ESCHR_COL R S
62010-06-19W102010-11-15L1 B_ESCHR_COL S SRS S FALSE TRUE
72010-07-07W102010-12-31L1 B_ESCHR_COLSS RIS S FALSEFALSETRUE
82010-07-10W102011-01-14L1 B_ESCHR_COL R S S S FALSETRUEFALSE
92010-08-12W102011-01-31L1 B_ESCHR_COL S S
102010-10-15W102011-03-23L1 B_ESCHR_COLSR S S S FALSEFALSETRUE
-

Instead of 1, now 7 isolates are flagged. In total, 75.5% of all isolates are marked ‘first weighted’ - 47.1% 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 1, now 8 isolates are flagged. In total, 76% of all isolates are marked ‘first weighted’ - 47.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 15,099 isolates for analysis.

+

So we end up with 15,191 isolates for analysis.

We can remove unneeded columns:

data_1st <- data_1st %>% 
   select(-c(first, keyab))
@@ -816,31 +816,31 @@ -2 -2013-01-14 -S5 -Hospital B -B_ESCHR_COL -S -S -S +1 +2014-05-06 +Y6 +Hospital D +B_STRPT_PNE +R +R S +R F -Gram-negative -Escherichia -coli +Gram-positive +Streptococcus +pneumoniae TRUE -3 -2011-04-02 -G2 -Hospital B +2 +2010-10-04 +M1 +Hospital D B_ESCHR_COL S S -R S +R M Gram-negative Escherichia @@ -848,14 +848,14 @@ TRUE -4 -2011-09-22 -B3 -Hospital C +3 +2015-04-19 +L8 +Hospital D B_ESCHR_COL R -S -S +R +R S M Gram-negative @@ -864,51 +864,51 @@ TRUE -5 -2015-07-30 -G10 -Hospital A -B_KLBSL_PNE +4 +2013-08-28 +O2 +Hospital C +B_STRPT_PNE +R R S -S -S -M -Gram-negative -Klebsiella +R +F +Gram-positive +Streptococcus pneumoniae TRUE -6 -2017-10-07 -X3 +7 +2012-05-09 +B2 Hospital A B_ESCHR_COL -R S S S -F +S +M Gram-negative Escherichia coli TRUE -7 -2015-11-01 -O1 -Hospital B -B_ESCHR_COL +8 +2016-11-07 +J4 +Hospital D +B_STPHY_AUR R S S S -F -Gram-negative -Escherichia -coli +M +Gram-positive +Staphylococcus +aureus TRUE @@ -928,9 +928,9 @@
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 data_1st (15,099 x 13)

+

Frequency table of genus and species from data_1st (15,191 x 13)

Columns: 2
-Length: 15,099 (of which NA: 0 = 0.00%)
+Length: 15,191 (of which NA: 0 = 0.00%)
Unique: 4

Shortest: 16
Longest: 24

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

1 Escherichia coli -7,513 -49.8% -7,513 -49.8% +7,443 +49.0% +7,443 +49.0% 2 Staphylococcus aureus -3,708 -24.6% -11,221 -74.3% +3,827 +25.2% +11,270 +74.2% 3 Streptococcus pneumoniae -2,266 -15.0% -13,487 -89.3% +2,353 +15.5% +13,623 +89.7% 4 Klebsiella pneumoniae -1,612 -10.7% -15,099 +1,568 +10.3% +15,191 100.0% @@ -984,7 +984,7 @@ Longest: 24

Resistance percentages

The functions portion_S(), portion_SI(), portion_I(), portion_IR() and portion_R() can be used to determine the portion of a specific antimicrobial outcome. As per the EUCAST guideline of 2019, we calculate resistance as the portion of R (portion_R()) and susceptibility as the portion of S and I (portion_SI()). These functions can be used on their own:

data_1st %>% portion_R(AMX)
-# [1] 0.4679118
+# [1] 0.4710684

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

data_1st %>% 
   group_by(hospital) %>% 
@@ -997,19 +997,19 @@ Longest: 24

Hospital A -0.4754386 +0.4769129 Hospital B -0.4673058 +0.4643125 Hospital C -0.4625054 +0.4723793 Hospital D -0.4617169 +0.4731788 @@ -1027,23 +1027,23 @@ Longest: 24

Hospital A -0.4754386 -4560 +0.4769129 +4548 Hospital B -0.4673058 -5215 +0.4643125 +5324 Hospital C -0.4625054 -2307 +0.4723793 +2299 Hospital D -0.4617169 -3017 +0.4731788 +3020 @@ -1063,27 +1063,27 @@ Longest: 24

Escherichia -0.9237322 -0.8957806 -0.9952083 +0.9226119 +0.8988311 +0.9943571 Klebsiella -0.8207196 -0.8957816 -0.9844913 +0.8010204 +0.8903061 +0.9795918 Staphylococcus -0.9161273 -0.9180151 -0.9927184 +0.9263130 +0.9140319 +0.9934675 Streptococcus -0.6160635 +0.6162346 0.0000000 -0.6160635 +0.6162346 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 bf35284d..18868765 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 7007358c..03445ff7 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 090a588b..a37757e6 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 42c7f33c..b39e4d32 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/articles/EUCAST.html b/docs/articles/EUCAST.html index fadee99f..1389cac4 100644 --- a/docs/articles/EUCAST.html +++ b/docs/articles/EUCAST.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0.9000 + 0.7.0.9013
@@ -125,13 +125,6 @@ Create frequency tables -
  • - - - - Use the G-test - -
  • @@ -199,7 +192,7 @@

    How to apply EUCAST rules

    Matthijs S. Berends

    -

    07 June 2019

    +

    22 June 2019

    diff --git a/docs/articles/MDR.html b/docs/articles/MDR.html index 2ae79f6e..1fd50a0a 100644 --- a/docs/articles/MDR.html +++ b/docs/articles/MDR.html @@ -40,7 +40,7 @@
    AMR (for R) - 0.7.0.9000 + 0.7.0.9013 @@ -125,13 +125,6 @@ Create frequency tables
  • -
  • - - - - Use the G-test - -
  • @@ -199,7 +192,7 @@

    How to determine multi-drug resistance (MDR)

    Matthijs S. Berends

    -

    07 June 2019

    +

    22 June 2019

    @@ -242,19 +235,19 @@

    The data set looks like this now:

    +# 5 R +# 6 I

    We can now add the interpretation of MDR-TB to our data set:

    my_TB_data$mdr <- mdr_tb(my_TB_data)
     # NOTE: No column found as input for `col_mo`, assuming all records contain Mycobacterium tuberculosis.
    @@ -284,40 +277,40 @@ Unique: 5

    1 Mono-resistance -3,283 +3,284 65.7% -3,283 +3,284 65.7% 2 Negative -650 -13.0% -3,933 -78.7% +675 +13.5% +3,959 +79.2% 3 Multidrug resistance -593 -11.9% -4,526 -90.5% +570 +11.4% +4,529 +90.6% 4 Poly-resistance -259 -5.2% -4,785 -95.7% +263 +5.3% +4,792 +95.8% 5 Extensive drug resistance -215 -4.3% +208 +4.2% 5,000 100.0% diff --git a/docs/articles/SPSS.html b/docs/articles/SPSS.html index 05da7bf4..a169c1cb 100644 --- a/docs/articles/SPSS.html +++ b/docs/articles/SPSS.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0.9000 + 0.7.0.9013
    @@ -125,13 +125,6 @@ Create frequency tables
  • -
  • - - - - Use the G-test - -
  • @@ -199,7 +192,7 @@

    How to import data from SPSS / SAS / Stata

    Matthijs S. Berends

    -

    07 June 2019

    +

    22 June 2019

    @@ -259,7 +252,7 @@
    # the Gram stain is avaiable for all bacteria: mo_gramstain("E. coli") -# [1] "Gram negative" +# [1] "Gram-negative" # Klebsiella is intrinsic resistant to amoxicllin, according to EUCAST: klebsiella_test <- data.frame(mo = "klebsiella", diff --git a/docs/articles/WHONET.html b/docs/articles/WHONET.html index ee88f81a..1f2802d0 100644 --- a/docs/articles/WHONET.html +++ b/docs/articles/WHONET.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0.9000 + 0.7.0.9013 @@ -125,13 +125,6 @@ Create frequency tables
  • -
  • - - - - Use the G-test - -
  • @@ -199,7 +192,7 @@

    How to work with WHONET data

    Matthijs S. Berends

    -

    07 June 2019

    +

    22 June 2019

    diff --git a/docs/articles/ab_property.html b/docs/articles/ab_property.html index f9c7b7cf..861a9bcb 100644 --- a/docs/articles/ab_property.html +++ b/docs/articles/ab_property.html @@ -40,7 +40,7 @@
    AMR (for R) - 0.7.0.9000 + 0.7.0.9013 @@ -125,13 +125,6 @@ Create frequency tables
  • -
  • - - - - Use the G-test - -
  • @@ -199,7 +192,7 @@

    How to get properties of an antibiotic

    Matthijs S. Berends

    -

    07 June 2019

    +

    22 June 2019

    diff --git a/docs/articles/benchmarks.html b/docs/articles/benchmarks.html index 323fcb5b..75515ea9 100644 --- a/docs/articles/benchmarks.html +++ b/docs/articles/benchmarks.html @@ -40,7 +40,7 @@
    AMR (for R) - 0.7.0.9000 + 0.7.0.9013 @@ -125,13 +125,6 @@ Create frequency tables
  • -
  • - - - - Use the G-test - -
  • @@ -199,7 +192,7 @@

    Benchmarks

    Matthijs S. Berends

    -

    07 June 2019

    +

    22 June 2019

    @@ -224,14 +217,14 @@
    times = 10) print(S.aureus, unit = "ms", signif = 2) # Unit: milliseconds -# expr min lq mean median uq max neval -# as.mo("sau") 18 18.0 18 18.0 18.0 19 10 -# as.mo("stau") 41 41.0 50 42.0 43.0 86 10 -# as.mo("staaur") 18 18.0 22 18.0 18.0 64 10 -# as.mo("STAAUR") 18 18.0 40 19.0 63.0 97 10 -# as.mo("S. aureus") 28 28.0 33 28.0 29.0 73 10 -# as.mo("S. aureus") 28 28.0 37 28.0 28.0 120 10 -# as.mo("Staphylococcus aureus") 8 8.1 13 8.1 8.3 53 10
    +# expr min lq mean median uq max neval +# as.mo("sau") 18.0 18.0 22 18.0 18.0 63 10 +# as.mo("stau") 66.0 66.0 71 66.0 66.0 110 10 +# as.mo("staaur") 18.0 18.0 18 18.0 18.0 18 10 +# as.mo("STAAUR") 18.0 18.0 18 18.0 18.0 20 10 +# as.mo("S. aureus") 53.0 53.0 70 53.0 55.0 180 10 +# as.mo("S. aureus") 52.0 53.0 73 54.0 97.0 110 10 +# as.mo("Staphylococcus aureus") 8.2 8.2 17 8.3 8.4 53 10

    In the table above, all measurements are shown in milliseconds (thousands of seconds). A value of 5 milliseconds means it can determine 200 input values per second. It case of 100 milliseconds, this is only 10 input values per second. The second input is the only one that has to be looked up thoroughly. All the others are known codes (the first one is a WHONET code) or common laboratory codes, or common full organism names like the last one. Full organism names are always preferred.

    To achieve this speed, the as.mo function also takes into account the prevalence of human pathogenic microorganisms. The downside is of course that less prevalent microorganisms will be determined less fast. See this example for the ID of Thermus islandicus (B_THERMS_ISL), a bug probably never found before in humans:

    T.islandicus <- microbenchmark(as.mo("theisl"),
    @@ -243,12 +236,12 @@
     print(T.islandicus, unit = "ms", signif = 2)
     # Unit: milliseconds
     #                         expr min  lq mean median  uq max neval
    -#              as.mo("theisl") 370 370  390    370 420 420    10
    -#              as.mo("THEISL") 370 420  420    420 420 440    10
    -#       as.mo("T. islandicus") 190 190  200    190 230 250    10
    -#      as.mo("T.  islandicus") 190 190  210    210 230 240    10
    -#  as.mo("Thermus islandicus")  73  73   83     74  74 120    10
    -

    That takes 8.6 times as much time on average. A value of 100 milliseconds means it can only determine ~10 different input values per second. We can conclude that looking up arbitrary codes of less prevalent microorganisms is the worst way to go, in terms of calculation performance. Full names (like Thermus islandicus) are almost fast - these are the most probable input from most data sets.

    +# as.mo("theisl") 400 400 430 430 450 450 10 +# as.mo("THEISL") 390 400 420 420 450 460 10 +# as.mo("T. islandicus") 210 210 260 240 270 430 10 +# as.mo("T. islandicus") 210 210 250 260 260 270 10 +# as.mo("Thermus islandicus") 74 75 94 76 120 120 10 +

    That takes 7 times as much time on average. A value of 100 milliseconds means it can only determine ~10 different input values per second. We can conclude that looking up arbitrary codes of less prevalent microorganisms is the worst way to go, in terms of calculation performance. Full names (like Thermus islandicus) are almost fast - these are the most probable input from most data sets.

    In the figure below, we compare Escherichia coli (which is very common) with Prevotella brevis (which is moderately common) and with Thermus islandicus (which is very uncommon):

    par(mar = c(5, 16, 4, 2)) # set more space for left margin text (16)
     
    @@ -294,8 +287,8 @@
     print(run_it, unit = "ms", signif = 3)
     # Unit: milliseconds
     #            expr  min   lq mean median   uq  max neval
    -#  mo_fullname(x) 1220 1320 1410   1390 1540 1570    10
    -

    So transforming 500,000 values (!!) of 50 unique values only takes 1.39 seconds (1393 ms). You only lose time on your unique input values.

    +# mo_fullname(x) 1090 1130 1190 1170 1230 1320 10 +

    So transforming 500,000 values (!!) of 50 unique values only takes 1.17 seconds (1167 ms). You only lose time on your unique input values.

    @@ -307,11 +300,11 @@ times = 10) print(run_it, unit = "ms", signif = 3) # Unit: milliseconds -# expr min lq mean median uq max neval -# A 13.70 13.90 14.40 14.40 14.60 15.30 10 -# B 25.60 26.10 26.80 26.80 27.40 28.30 10 -# C 1.59 1.78 1.95 1.96 2.06 2.39 10

    -

    So going from mo_fullname("Staphylococcus aureus") to "Staphylococcus aureus" takes 0.002 seconds - it doesn’t even start calculating if the result would be the same as the expected resulting value. That goes for all helper functions:

    +# expr min lq mean median uq max neval +# A 13.00 13.20 13.70 13.60 14.10 14.70 10 +# B 50.40 50.90 57.80 51.80 52.80 104.00 10 +# C 1.72 1.77 1.86 1.83 1.98 2.02 10 +

    So going from mo_fullname("Staphylococcus aureus") to "Staphylococcus aureus" takes 0.0018 seconds - it doesn’t even start calculating if the result would be the same as the expected resulting value. That goes for all helper functions:

    run_it <- microbenchmark(A = mo_species("aureus"),
                              B = mo_genus("Staphylococcus"),
                              C = mo_fullname("Staphylococcus aureus"),
    @@ -324,14 +317,14 @@
     print(run_it, unit = "ms", signif = 3)
     # Unit: milliseconds
     #  expr   min    lq  mean median    uq   max neval
    -#     A 0.555 0.585 0.666  0.619 0.777 0.788    10
    -#     B 0.574 0.653 0.771  0.740 0.857 1.080    10
    -#     C 1.630 1.790 1.950  1.930 2.120 2.280    10
    -#     D 0.571 0.671 0.726  0.702 0.725 1.090    10
    -#     E 0.528 0.569 0.704  0.762 0.807 0.833    10
    -#     F 0.511 0.556 0.618  0.580 0.694 0.752    10
    -#     G 0.481 0.538 0.649  0.674 0.736 0.791    10
    -#     H 0.213 0.282 0.336  0.298 0.348 0.636    10
    +# A 0.591 0.635 0.719 0.681 0.808 0.968 10 +# B 0.575 0.643 0.702 0.688 0.738 0.893 10 +# C 1.550 1.660 1.780 1.730 1.920 2.170 10 +# D 0.594 0.685 0.725 0.732 0.760 0.928 10 +# E 0.584 0.614 0.667 0.650 0.730 0.782 10 +# F 0.473 0.479 0.617 0.629 0.712 0.810 10 +# G 0.495 0.526 0.576 0.559 0.602 0.756 10 +# H 0.489 0.519 0.565 0.575 0.607 0.647 10

    Of course, when running mo_phylum("Firmicutes") the function has zero knowledge about the actual microorganism, namely S. aureus. But since the result would be "Firmicutes" too, there is no point in calculating the result. And because this package ‘knows’ all phyla of all known bacteria (according to the Catalogue of Life), it can just return the initial value immediately.

    @@ -357,14 +350,14 @@ times = 10) print(run_it, unit = "ms", signif = 4) # Unit: milliseconds -# expr min lq mean median uq max neval -# en 18.63 19.06 19.30 19.19 19.41 20.33 10 -# de 21.18 21.46 21.63 21.54 21.97 22.09 10 -# nl 34.84 35.19 40.04 35.54 36.43 80.26 10 -# es 21.00 21.17 21.58 21.49 21.62 23.30 10 -# it 21.10 21.26 30.82 21.66 22.58 67.88 10 -# fr 20.99 21.25 21.88 21.54 22.50 23.15 10 -# pt 21.11 21.24 21.59 21.55 21.91 22.34 10
    +# expr min lq mean median uq max neval +# en 43.75 43.82 44.07 43.93 44.28 44.90 10 +# de 45.96 46.09 47.68 46.20 46.65 59.40 10 +# nl 59.57 59.72 64.49 59.88 60.34 104.30 10 +# es 45.82 45.89 50.72 46.30 46.60 90.94 10 +# it 45.77 45.94 55.86 46.46 48.05 96.85 10 +# fr 45.67 45.99 55.17 46.39 46.78 92.03 10 +# pt 45.84 45.92 46.27 46.04 46.36 47.24 10

    Currently supported are German, Dutch, Spanish, Italian, French and Portuguese.

    diff --git a/docs/articles/benchmarks_files/figure-html/unnamed-chunk-5-1.png b/docs/articles/benchmarks_files/figure-html/unnamed-chunk-5-1.png index df4a0b10..bf33e9bf 100644 Binary files a/docs/articles/benchmarks_files/figure-html/unnamed-chunk-5-1.png and b/docs/articles/benchmarks_files/figure-html/unnamed-chunk-5-1.png differ diff --git a/docs/articles/freq.html b/docs/articles/freq.html index 94217729..ca20393e 100644 --- a/docs/articles/freq.html +++ b/docs/articles/freq.html @@ -40,7 +40,7 @@ AMR (for R) - 0.7.0.9000 + 0.7.0.9013 @@ -125,13 +125,6 @@ Create frequency tables
  • -
  • - - - - Use the G-test - -
  • @@ -199,7 +192,7 @@

    How to create frequency tables

    Matthijs S. Berends

    -

    07 June 2019

    +

    22 June 2019

    diff --git a/docs/articles/index.html b/docs/articles/index.html index 3385d535..c14d7908 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -78,7 +78,7 @@
    AMR (for R) - 0.7.0.9012 + 0.7.0.9013 diff --git a/docs/authors.html b/docs/authors.html index 76db20c7..28de45f2 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.0.9012 + 0.7.0.9013 diff --git a/docs/index.html b/docs/index.html index 0b9d76aa..e2688f80 100644 --- a/docs/index.html +++ b/docs/index.html @@ -42,7 +42,7 @@ AMR (for R) - 0.7.0.9012 + 0.7.0.9013 diff --git a/docs/reference/AMR-deprecated.html b/docs/reference/AMR-deprecated.html index 61d39f11..41b9eaf5 100644 --- a/docs/reference/AMR-deprecated.html +++ b/docs/reference/AMR-deprecated.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/AMR.html b/docs/reference/AMR.html index 41e0f71f..05714ec0 100644 --- a/docs/reference/AMR.html +++ b/docs/reference/AMR.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/WHOCC.html b/docs/reference/WHOCC.html index b8d90fe8..8454fb4b 100644 --- a/docs/reference/WHOCC.html +++ b/docs/reference/WHOCC.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/WHONET.html b/docs/reference/WHONET.html index a6e962a9..9e008a6f 100644 --- a/docs/reference/WHONET.html +++ b/docs/reference/WHONET.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/ab_property.html b/docs/reference/ab_property.html index b31e4131..d8f706cb 100644 --- a/docs/reference/ab_property.html +++ b/docs/reference/ab_property.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/age.html b/docs/reference/age.html index b0657a03..77af99da 100644 --- a/docs/reference/age.html +++ b/docs/reference/age.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/age_groups.html b/docs/reference/age_groups.html index 2932d4c6..456531d6 100644 --- a/docs/reference/age_groups.html +++ b/docs/reference/age_groups.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/antibiotics.html b/docs/reference/antibiotics.html index 8fd92f2e..dee4f360 100644 --- a/docs/reference/antibiotics.html +++ b/docs/reference/antibiotics.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/as.ab.html b/docs/reference/as.ab.html index da9d3743..2db50e4d 100644 --- a/docs/reference/as.ab.html +++ b/docs/reference/as.ab.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/as.atc.html b/docs/reference/as.atc.html index 9743ac63..dd776413 100644 --- a/docs/reference/as.atc.html +++ b/docs/reference/as.atc.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/as.disk.html b/docs/reference/as.disk.html index 13691eed..bb4b05e0 100644 --- a/docs/reference/as.disk.html +++ b/docs/reference/as.disk.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/as.mic.html b/docs/reference/as.mic.html index d666316e..f8e985d4 100644 --- a/docs/reference/as.mic.html +++ b/docs/reference/as.mic.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/as.mo.html b/docs/reference/as.mo.html index c40288d4..092bc91b 100644 --- a/docs/reference/as.mo.html +++ b/docs/reference/as.mo.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 @@ -385,9 +385,10 @@ The mo_property functions (like as.mo("Staphylococcus aureus") as.mo("Staphylococcus aureus (MRSA)") as.mo("Sthafilokkockus aaureuz") # handles incorrect spelling -as.mo("MRSA") # Methicillin Resistant S. aureus -as.mo("VISA") # Vancomycin Intermediate S. aureus -as.mo("VRSA") # Vancomycin Resistant S. aureus +as.mo("MRSA") # Methicillin Resistant S. aureus +as.mo("VISA") # Vancomycin Intermediate S. aureus +as.mo("VRSA") # Vancomycin Resistant S. aureus +as.mo(22242419) # Catalogue of Life ID # Dyslexia is no problem - these all work: as.mo("Ureaplasma urealyticum") diff --git a/docs/reference/as.rsi.html b/docs/reference/as.rsi.html index 0fc87a5b..05f0b17a 100644 --- a/docs/reference/as.rsi.html +++ b/docs/reference/as.rsi.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/atc_online.html b/docs/reference/atc_online.html index 3db83e71..7c3285f1 100644 --- a/docs/reference/atc_online.html +++ b/docs/reference/atc_online.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/availability.html b/docs/reference/availability.html index 8fa96a1f..f866ab4a 100644 --- a/docs/reference/availability.html +++ b/docs/reference/availability.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/catalogue_of_life.html b/docs/reference/catalogue_of_life.html index e18b85f2..312988b9 100644 --- a/docs/reference/catalogue_of_life.html +++ b/docs/reference/catalogue_of_life.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/catalogue_of_life_version.html b/docs/reference/catalogue_of_life_version.html index f31976e9..a71d7d5f 100644 --- a/docs/reference/catalogue_of_life_version.html +++ b/docs/reference/catalogue_of_life_version.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/count.html b/docs/reference/count.html index e587b516..5e7b4107 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.0.9012 + 0.7.0.9013 diff --git a/docs/reference/eucast_rules.html b/docs/reference/eucast_rules.html index c9558b24..a5c14893 100644 --- a/docs/reference/eucast_rules.html +++ b/docs/reference/eucast_rules.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/extended-functions.html b/docs/reference/extended-functions.html index ad3c83a5..4e94d910 100644 --- a/docs/reference/extended-functions.html +++ b/docs/reference/extended-functions.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/filter_ab_class.html b/docs/reference/filter_ab_class.html index 46639864..dd0d78ca 100644 --- a/docs/reference/filter_ab_class.html +++ b/docs/reference/filter_ab_class.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/first_isolate.html b/docs/reference/first_isolate.html index 748e086e..7e573a49 100644 --- a/docs/reference/first_isolate.html +++ b/docs/reference/first_isolate.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/freq.html b/docs/reference/freq.html index 8b9c6824..6a945861 100644 --- a/docs/reference/freq.html +++ b/docs/reference/freq.html @@ -81,7 +81,7 @@ top_freq can be used to get the top/bottom n items of a frequency table, with co AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/g.test.html b/docs/reference/g.test.html index 7ca7beba..d3f53320 100644 --- a/docs/reference/g.test.html +++ b/docs/reference/g.test.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/ggplot_rsi.html b/docs/reference/ggplot_rsi.html index bb7fe742..abe526b4 100644 --- a/docs/reference/ggplot_rsi.html +++ b/docs/reference/ggplot_rsi.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 @@ -237,7 +237,7 @@
    -

    Use these functions to create bar plots for antimicrobial resistance analysis. All functions rely on internal ggplot2 functions.

    +

    Use these functions to create bar plots for antimicrobial resistance analysis. All functions rely on internal ggplot2 functions.

    @@ -371,11 +371,11 @@

    At default, the names of antibiotics will be shown on the plots using ab_name. This can be set with the translate_ab parameter. See count_df.

    The functions
    geom_rsi will take any variable from the data that has an rsi class (created with as.rsi) using fun (count_df at default, can also be portion_df) and will plot bars with the percentage R, I and S. The default behaviour is to have the bars stacked and to have the different antibiotics on the x axis.

    -

    facet_rsi creates 2d plots (at default based on S/I/R) using facet_wrap.

    +

    facet_rsi creates 2d plots (at default based on S/I/R) using facet_wrap.

    scale_y_percent transforms the y axis to a 0 to 100% range using scale_continuous.

    scale_rsi_colours sets colours to the bars: pastel blue for S, pastel turquoise for I and pastel red for R, using scale_brewer.

    -

    theme_rsi is a ggplot theme with minimal distraction.

    -

    labels_rsi_count print datalabels on the bars with percentage and amount of isolates using geom_text

    +

    theme_rsi is a ggplot theme with minimal distraction.

    +

    labels_rsi_count print datalabels on the bars with percentage and amount of isolates using geom_text

    ggplot_rsi is a wrapper around all above functions that uses data as first input. This makes it possible to use this function after a pipe (%>%). See Examples.

    Read more on our website!

    @@ -390,12 +390,12 @@ library(ggplot2) # get antimicrobial results for drugs against a UTI: -ggplot(septic_patients %>% select(AMX, NIT, FOS, TMP, CIP)) + +ggplot(septic_patients %>% select(AMX, NIT, FOS, TMP, CIP)) + geom_rsi() # prettify the plot using some additional functions: df <- septic_patients %>% select(AMX, NIT, FOS, TMP, CIP) -ggplot(df) + +ggplot(df) + geom_rsi() + scale_y_percent() + scale_rsi_colours() + @@ -439,7 +439,7 @@ # for colourblind mode, use divergent colours from the viridis package: septic_patients %>% select(AMX, NIT, FOS, TMP, CIP) %>% - ggplot_rsi() + scale_fill_viridis_d() + ggplot_rsi() + scale_fill_viridis_d() # a shorter version which also adjusts data label colours: septic_patients %>% select(AMX, NIT, FOS, TMP, CIP) %>% diff --git a/docs/reference/guess_ab_col.html b/docs/reference/guess_ab_col.html index 28494847..5a95b56d 100644 --- a/docs/reference/guess_ab_col.html +++ b/docs/reference/guess_ab_col.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/index.html b/docs/reference/index.html index e0ffeb79..d12f8e78 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -78,7 +78,7 @@ AMR (for R) - 0.7.0.9012 + 0.7.0.9013 diff --git a/docs/reference/join.html b/docs/reference/join.html index 4b400f16..abe6592f 100644 --- a/docs/reference/join.html +++ b/docs/reference/join.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/key_antibiotics.html b/docs/reference/key_antibiotics.html index d71dc71f..e9e0ca6c 100644 --- a/docs/reference/key_antibiotics.html +++ b/docs/reference/key_antibiotics.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/kurtosis.html b/docs/reference/kurtosis.html index 5c824b5a..cd67255f 100644 --- a/docs/reference/kurtosis.html +++ b/docs/reference/kurtosis.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/like.html b/docs/reference/like.html index bca87135..608d5ea0 100644 --- a/docs/reference/like.html +++ b/docs/reference/like.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/mdro.html b/docs/reference/mdro.html index 4c518ce1..0c0f2a21 100644 --- a/docs/reference/mdro.html +++ b/docs/reference/mdro.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/microorganisms.codes.html b/docs/reference/microorganisms.codes.html index 73a6c795..b33f5886 100644 --- a/docs/reference/microorganisms.codes.html +++ b/docs/reference/microorganisms.codes.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/microorganisms.html b/docs/reference/microorganisms.html index 0cbffeb4..f8cc6619 100644 --- a/docs/reference/microorganisms.html +++ b/docs/reference/microorganisms.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/microorganisms.old.html b/docs/reference/microorganisms.old.html index 81d197bb..fa8e694b 100644 --- a/docs/reference/microorganisms.old.html +++ b/docs/reference/microorganisms.old.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/mo_property.html b/docs/reference/mo_property.html index a2d7383e..6d28affc 100644 --- a/docs/reference/mo_property.html +++ b/docs/reference/mo_property.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9012 + 0.7.0.9013 diff --git a/docs/reference/mo_source.html b/docs/reference/mo_source.html index 3362275b..d0ebf72d 100644 --- a/docs/reference/mo_source.html +++ b/docs/reference/mo_source.html @@ -81,7 +81,7 @@ This is the fastest way to have your organisation (or analysis) specific codes p AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/p.symbol.html b/docs/reference/p.symbol.html index db83ed22..7fb8f943 100644 --- a/docs/reference/p.symbol.html +++ b/docs/reference/p.symbol.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/portion.html b/docs/reference/portion.html index 92f48de4..08601c85 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.0.9012 + 0.7.0.9013 diff --git a/docs/reference/read.4D.html b/docs/reference/read.4D.html index ed9931dd..fd5bb3a4 100644 --- a/docs/reference/read.4D.html +++ b/docs/reference/read.4D.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/resistance_predict.html b/docs/reference/resistance_predict.html index 045aba48..7abd7cd0 100644 --- a/docs/reference/resistance_predict.html +++ b/docs/reference/resistance_predict.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 @@ -379,21 +379,21 @@ info = FALSE, minimum = 15) - ggplot(data, - aes(x = year)) + - geom_col(aes(y = value), + ggplot(data, + aes(x = year)) + + geom_col(aes(y = value), fill = "grey75") + - geom_errorbar(aes(ymin = se_min, + geom_errorbar(aes(ymin = se_min, ymax = se_max), colour = "grey50") + - scale_y_continuous(limits = c(0, 1), + scale_y_continuous(limits = c(0, 1), breaks = seq(0, 1, 0.1), labels = paste0(seq(0, 100, 10), "%")) + - labs(title = expression(paste("Forecast of amoxicillin resistance in ", + labs(title = expression(paste("Forecast of amoxicillin resistance in ", italic("E. coli"))), y = "%IR", x = "Year") + - theme_minimal(base_size = 13) + theme_minimal(base_size = 13) } # } diff --git a/docs/reference/rsi_translation.html b/docs/reference/rsi_translation.html index 55fea168..04680413 100644 --- a/docs/reference/rsi_translation.html +++ b/docs/reference/rsi_translation.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/septic_patients.html b/docs/reference/septic_patients.html index 2f9c1827..08aaed3c 100644 --- a/docs/reference/septic_patients.html +++ b/docs/reference/septic_patients.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/skewness.html b/docs/reference/skewness.html index 7b928cc0..92d75cbf 100644 --- a/docs/reference/skewness.html +++ b/docs/reference/skewness.html @@ -81,7 +81,7 @@ When negative: the left tail is longer; the mass of the distribution is concentr AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/docs/reference/translate.html b/docs/reference/translate.html index 1455c090..4e7cce64 100644 --- a/docs/reference/translate.html +++ b/docs/reference/translate.html @@ -80,7 +80,7 @@ AMR (for R) - 0.7.0.9009 + 0.7.0.9013 diff --git a/man/as.mo.Rd b/man/as.mo.Rd index e4b78405..2bbf53f9 100644 --- a/man/as.mo.Rd +++ b/man/as.mo.Rd @@ -158,9 +158,10 @@ as.mo("S aureus") as.mo("Staphylococcus aureus") as.mo("Staphylococcus aureus (MRSA)") as.mo("Sthafilokkockus aaureuz") # handles incorrect spelling -as.mo("MRSA") # Methicillin Resistant S. aureus -as.mo("VISA") # Vancomycin Intermediate S. aureus -as.mo("VRSA") # Vancomycin Resistant S. aureus +as.mo("MRSA") # Methicillin Resistant S. aureus +as.mo("VISA") # Vancomycin Intermediate S. aureus +as.mo("VRSA") # Vancomycin Resistant S. aureus +as.mo(22242419) # Catalogue of Life ID # Dyslexia is no problem - these all work: as.mo("Ureaplasma urealyticum") diff --git a/tests/testthat/test-mo.R b/tests/testthat/test-mo.R index d2aba489..1bfa0839 100644 --- a/tests/testthat/test-mo.R +++ b/tests/testthat/test-mo.R @@ -33,6 +33,7 @@ test_that("as.mo works", { expect_equal(as.character(as.mo("Escherichia coli")), "B_ESCHR_COL") expect_equal(as.character(as.mo("Escherichia coli")), "B_ESCHR_COL") + expect_equal(as.character(as.mo(22242416)), "B_ESCHR_COL") expect_equal(as.character(as.mo("Escherichia species")), "B_ESCHR") expect_equal(as.character(as.mo("Escherichia")), "B_ESCHR") expect_equal(as.character(as.mo("Esch spp.")), "B_ESCHR") diff --git a/tests/testthat/test-mo_property.R b/tests/testthat/test-mo_property.R index 4ef7080d..94dd4374 100644 --- a/tests/testthat/test-mo_property.R +++ b/tests/testthat/test-mo_property.R @@ -38,10 +38,12 @@ test_that("mo_property works", { expect_equal(names(mo_taxonomy("Escherichia coli")), c("kingdom", "phylum", "class", "order", "family", "genus", "species", "subspecies")) expect_equal(mo_synonyms("Escherichia coli"), NULL) - expect_gt(length(mo_synonyms("C. albicans")), 1) + expect_gt(length(mo_synonyms("Candida albicans")), 1) + expect_equal(class(mo_synonyms(c("Candida albicans", "Escherichia coli"))), "list") expect_equal(names(mo_info("Escherichia coli")), c("kingdom", "phylum", "class", "order", "family", "genus", "species", "subspecies", "synonyms", "url", "ref")) + expect_equal(class(mo_info(c("Escherichia coli", "Staphylococcus aureus"))), "list") expect_equal(mo_ref("Escherichia coli"), "Castellani et al., 1919") expect_equal(mo_authors("Escherichia coli"), "Castellani et al.") diff --git a/vignettes/ab_property.Rmd b/vignettes/ab_property.Rmd deleted file mode 100755 index bf17254f..00000000 --- a/vignettes/ab_property.Rmd +++ /dev/null @@ -1,25 +0,0 @@ ---- -title: "How to get properties of an antibiotic" -author: "Matthijs S. Berends" -date: '`r format(Sys.Date(), "%d %B %Y")`' -output: - rmarkdown::html_vignette: - toc: true -vignette: > - %\VignetteIndexEntry{How to get properties of an antibiotic} - %\VignetteEncoding{UTF-8} - %\VignetteEngine{knitr::rmarkdown} -editor_options: - chunk_output_type: console ---- - -```{r setup, include = FALSE, results = 'markup'} -knitr::opts_chunk$set( - collapse = TRUE, - comment = "#" -) -# set to original language (English) -Sys.setlocale(locale = "C") -``` - -*(will be available soon)* diff --git a/vignettes/mo_property.Rmd b/vignettes/mo_property.Rmd deleted file mode 100755 index 4ccbbdeb..00000000 --- a/vignettes/mo_property.Rmd +++ /dev/null @@ -1,25 +0,0 @@ ---- -title: "How to get properties of a microorganism" -author: "Matthijs S. Berends" -date: '`r format(Sys.Date(), "%d %B %Y")`' -output: - rmarkdown::html_vignette: - toc: true -vignette: > - %\VignetteIndexEntry{How to get properties of a microorganism} - %\VignetteEncoding{UTF-8} - %\VignetteEngine{knitr::rmarkdown} -editor_options: - chunk_output_type: console ---- - -```{r setup, include = FALSE, results = 'markup'} -knitr::opts_chunk$set( - collapse = TRUE, - comment = "#" -) -# set to original language (English) -Sys.setlocale(locale = "C") -``` - -*(will be available soon)*