diff --git a/NAMESPACE b/NAMESPACE index a4708cc3..15abcb3d 100755 --- a/NAMESPACE +++ b/NAMESPACE @@ -217,6 +217,7 @@ importFrom(dplyr,bind_cols) importFrom(dplyr,bind_rows) importFrom(dplyr,case_when) importFrom(dplyr,desc) +importFrom(dplyr,distinct) importFrom(dplyr,everything) importFrom(dplyr,filter) importFrom(dplyr,filter_all) diff --git a/R/freq.R b/R/freq.R index 1f8f5aac..d498932b 100755 --- a/R/freq.R +++ b/R/freq.R @@ -682,7 +682,7 @@ format_header <- function(x, markdown = FALSE, decimal.mark = ".", big.mark = ", # numeric values if (has_length == TRUE & any(x_class %in% c("double", "integer", "numeric", "raw", "single"))) { header$sd <- paste0(header$sd, " (CV: ", header$cv, ", MAD: ", header$mad, ")") - header$fivenum <- paste0(paste(header$fivenum, collapse = " | "), " (IQR: ", header$IQR, ", CQV: ", header$cqv, ")") + header$fivenum <- paste0(paste(trimws(header$fivenum), collapse = " | "), " (IQR: ", header$IQR, ", CQV: ", header$cqv, ")") header$outliers_total <- paste0(header$outliers_total, " (unique count: ", header$outliers_unique, ")") header <- header[!names(header) %in% c("cv", "mad", "IQR", "cqv", "outliers_unique")] } diff --git a/R/mo.R b/R/mo.R index df08ec54..66deefa2 100755 --- a/R/mo.R +++ b/R/mo.R @@ -165,30 +165,44 @@ #' mutate(mo = as.mo(paste(genus, species))) #' } as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, allow_uncertain = TRUE, reference_df = get_mo_source()) { + if (!"AMR" %in% base::.packages()) { + library("AMR") + # check onLoad() in R/zzz.R: data tables are created there. + } + if (all(x %in% AMR::microorganisms$mo) & isFALSE(Becker) & isFALSE(Lancefield) & is.null(reference_df)) { y <- x - } else if (all(x %in% AMR::microorganisms$fullname) - & isFALSE(Becker) - & isFALSE(Lancefield) - & is.null(reference_df)) { - # we need special treatment for very prevalent full names, they are likely! + + } else if (all(tolower(x) %in% microorganismsDT$fullname_lower) + & isFALSE(Becker) + & isFALSE(Lancefield) + & is.null(reference_df)) { + # we need special treatment for very prevalent full names, they are likely! (case insensitive) # e.g. as.mo("Staphylococcus aureus") - y <- microorganismsDT[prevalence == 1][data.table(fullname = x), on = "fullname", "mo"][[1]] + y <- microorganismsDT[prevalence == 1][data.table(fullname_lower = tolower(x)), + on = "fullname_lower", + "mo"][[1]] if (any(is.na(y))) { - y[is.na(y)] <- microorganismsDT[prevalence == 2][data.table(fullname = x[is.na(y)]), on = "fullname", "mo"][[1]] + y[is.na(y)] <- microorganismsDT[prevalence == 2][data.table(fullname_lower = tolower(x[is.na(y)])), + on = "fullname_lower", + "mo"][[1]] } if (any(is.na(y))) { - y[is.na(y)] <- microorganismsDT[prevalence == 3][data.table(fullname = x[is.na(y)]), on = "fullname", "mo"][[1]] + y[is.na(y)] <- microorganismsDT[prevalence == 3][data.table(fullname_lower = tolower(x[is.na(y)])), + on = "fullname_lower", + "mo"][[1]] } + } else { # will be checked for mo class in validation and uses exec_as.mo internally if necessary y <- mo_validate(x = x, property = "mo", Becker = Becker, Lancefield = Lancefield, allow_uncertain = allow_uncertain, reference_df = reference_df) } + structure(.Data = y, class = "mo") } @@ -198,7 +212,7 @@ is.mo <- function(x) { identical(class(x), "mo") } -#' @importFrom dplyr %>% pull left_join n_distinct progress_estimated filter +#' @importFrom dplyr %>% pull left_join n_distinct progress_estimated filter distinct #' @importFrom data.table data.table as.data.table setkey #' @importFrom crayon magenta red blue silver italic has_color exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, @@ -298,22 +312,30 @@ exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, # existing mo codes when not looking for property "mo", like mo_genus("B_ESCHR_COL") y <- microorganismsDT[prevalence == 1][data.table(mo = x), on = "mo", ..property][[1]] if (any(is.na(y))) { - y[is.na(y)] <- microorganismsDT[prevalence == 2][data.table(mo = x[is.na(y)]), on = "mo", ..property][[1]] + y[is.na(y)] <- microorganismsDT[prevalence == 2][data.table(mo = x[is.na(y)]), + on = "mo", + ..property][[1]] } if (any(is.na(y))) { - y[is.na(y)] <- microorganismsDT[prevalence == 3][data.table(mo = x[is.na(y)]), on = "mo", ..property][[1]] + y[is.na(y)] <- microorganismsDT[prevalence == 3][data.table(mo = x[is.na(y)]), + on = "mo", + ..property][[1]] } x <- y - } else if (all(x %in% AMR::microorganisms$fullname)) { + } else if (all(tolower(x) %in% microorganismsDT$fullname_lower)) { # we need special treatment for very prevalent full names, they are likely! # e.g. as.mo("Staphylococcus aureus") - y <- microorganismsDT[prevalence == 1][data.table(fullname = x), on = "fullname", ..property][[1]] + y <- microorganismsDT[prevalence == 1][data.table(fullname_lower = tolower(x)), on = "fullname_lower", ..property][[1]] if (any(is.na(y))) { - y[is.na(y)] <- microorganismsDT[prevalence == 2][data.table(fullname = x[is.na(y)]), on = "fullname", ..property][[1]] + y[is.na(y)] <- microorganismsDT[prevalence == 2][data.table(fullname_lower = tolower(x[is.na(y)])), + on = "fullname_lower", + ..property][[1]] } if (any(is.na(y))) { - y[is.na(y)] <- microorganismsDT[prevalence == 3][data.table(fullname = x[is.na(y)]), on = "fullname", ..property][[1]] + y[is.na(y)] <- microorganismsDT[prevalence == 3][data.table(fullname_lower = tolower(x[is.na(y)])), + on = "fullname_lower", + ..property][[1]] } x <- y @@ -521,13 +543,13 @@ exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, # FIRST TRY FULLNAMES AND CODES # if only genus is available, return only genus if (all(!c(x[i], x_trimmed[i]) %like% " ")) { - found <- microorganismsDT[tolower(fullname) %in% tolower(c(x_species[i], x_trimmed_species[i])), ..property][[1]] + found <- microorganismsDT[fullname_lower %in% tolower(c(x_species[i], x_trimmed_species[i])), ..property][[1]] if (length(found) > 0) { x[i] <- found[1L] next } if (nchar(x_trimmed[i]) >= 6) { - found <- microorganismsDT[tolower(fullname) %like% paste0(x_withspaces_start_only[i], "[a-z]+ species"), ..property][[1]] + found <- microorganismsDT[fullname_lower %like% paste0(x_withspaces_start_only[i], "[a-z]+ species"), ..property][[1]] if (length(found) > 0) { x[i] <- found[1L] next @@ -564,13 +586,13 @@ exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, e.x_withspaces_start_only, f.x_withspaces_end_only) { - found <- data_to_check[tolower(fullname) %in% tolower(c(a.x_backup, b.x_trimmed)), ..property][[1]] + found <- data_to_check[fullname_lower %in% tolower(c(a.x_backup, b.x_trimmed)), ..property][[1]] # most probable: is exact match in fullname if (length(found) > 0) { return(found[1L]) } - found <- data_to_check[tolower(fullname) == tolower(c.x_trimmed_without_group), ..property][[1]] + found <- data_to_check[fullname_lower == tolower(c.x_trimmed_without_group), ..property][[1]] if (length(found) > 0) { return(found[1L]) } @@ -664,7 +686,7 @@ exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, # MISCELLANEOUS ---- # look for old taxonomic names ---- - found <- microorganisms.oldDT[tolower(fullname) == tolower(x_backup[i]) + found <- microorganisms.oldDT[fullname_lower == tolower(x_backup[i]) | fullname %like% x_withspaces_start_end[i],] if (NROW(found) > 0) { col_id_new <- found[1, col_id_new] @@ -693,7 +715,7 @@ exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, if (nchar(b.x_trimmed) > 4 & !b.x_trimmed %like% " ") { if (!grepl("^[A-Z][a-z]+", b.x_trimmed, ignore.case = FALSE)) { # not when input is like Genustext, because then Neospora would lead to Actinokineospora - found <- microorganismsDT[tolower(fullname) %like% paste(b.x_trimmed, "species"), ..property][[1]] + found <- microorganismsDT[fullname_lower %like% paste(b.x_trimmed, "species"), ..property][[1]] if (length(found) > 0) { x[i] <- found[1L] uncertainties <<- rbind(uncertainties, diff --git a/R/zzz.R b/R/zzz.R index 5403922f..1bd04758 100755 --- a/R/zzz.R +++ b/R/zzz.R @@ -28,6 +28,7 @@ if (!all(c("microorganismsDT", "microorganisms.oldDT") %in% ls(envir = asNamespace("AMR")))) { microorganisms.oldDT <- as.data.table(AMR::microorganisms.old) + microorganisms.oldDT$fullname_lower <- tolower(microorganisms.oldDT$fullname) setkey(microorganisms.oldDT, col_id, fullname) assign(x = "microorganisms", @@ -84,6 +85,7 @@ make <- function() { #' @importFrom data.table as.data.table setkey make_DT <- function() { microorganismsDT <- as.data.table(make()) + microorganismsDT$fullname_lower <- tolower(microorganismsDT$fullname) setkey(microorganismsDT, kingdom, prevalence, diff --git a/docs/articles/AMR.html b/docs/articles/AMR.html index 915b8c7d..3e234c50 100644 --- a/docs/articles/AMR.html +++ b/docs/articles/AMR.html @@ -327,68 +327,68 @@ -2015-01-18 -F9 -Hospital B -Escherichia coli +2011-10-07 +O2 +Hospital C +Streptococcus pneumoniae R S -R S -M +S +F -2017-12-07 -H7 +2013-10-20 +C10 Hospital A -Klebsiella pneumoniae -R +Escherichia coli S +R S S M -2016-02-14 -J4 +2014-08-25 +O4 Hospital A Escherichia coli -R -I -S -S -M - - -2010-12-25 -P2 -Hospital B -Streptococcus pneumoniae S S S S F - -2016-12-26 -S8 -Hospital A + +2011-10-28 +E3 +Hospital B Streptococcus pneumoniae S -I S S -F +S +M + + +2010-08-31 +H1 +Hospital A +Klebsiella pneumoniae +R +S +R +S +M -2010-03-27 -R7 -Hospital D -Klebsiella pneumoniae -S +2014-11-03 +U7 +Hospital A +Staphylococcus aureus S S +R S F @@ -411,8 +411,8 @@ #> #> Item Count Percent Cum. Count Cum. Percent #> --- ----- ------- -------- ----------- ------------- -#> 1 M 10,386 51.9% 10,386 51.9% -#> 2 F 9,614 48.1% 20,000 100.0% +#> 1 M 10,303 51.5% 10,303 51.5% +#> 2 F 9,697 48.5% 20,000 100.0%

So, we can draw at least two conclusions immediately. From a data scientist perspective, the data looks clean: only values M and F. From a researcher 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 %>%
@@ -443,10 +443,10 @@
 #> Kingella kingae (no changes)
 #> 
 #> EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)
-#> Table 1:  Intrinsic resistance in Enterobacteriaceae (1291 changes)
+#> Table 1:  Intrinsic resistance in Enterobacteriaceae (1256 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 (2787 changes)
+#> Table 4:  Intrinsic resistance in Gram-positive bacteria (2821 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)
@@ -462,9 +462,9 @@
 #> Non-EUCAST: piperacillin/tazobactam = S where piperacillin = S (no changes)
 #> Non-EUCAST: trimethoprim/sulfa = S where trimethoprim = S (no changes)
 #> 
-#> => EUCAST rules affected 7,442 out of 20,000 rows
+#> => EUCAST rules affected 7,457 out of 20,000 rows
 #>    -> added 0 test results
-#>    -> changed 4,078 test results (0 to S; 0 to I; 4,078 to R)
+#> -> changed 4,077 test results (0 to S; 0 to I; 4,077 to R)

@@ -489,7 +489,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,707 first isolates (28.5% of total)

+#> => Found 5,704 first isolates (28.5% of total)

So only 28.5% 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)
@@ -516,96 +516,96 @@ 1 -2010-02-12 -I9 +2010-01-18 +I8 B_ESCHR_COL +I S S S -R TRUE 2 -2010-02-12 -I9 +2010-03-30 +I8 B_ESCHR_COL -R S +I S S FALSE 3 -2010-02-22 -I9 +2010-10-05 +I8 B_ESCHR_COL R -S R S +S FALSE 4 -2010-03-05 -I9 +2011-01-26 +I8 B_ESCHR_COL S -S +R R S -FALSE +TRUE 5 -2010-03-08 -I9 +2011-02-01 +I8 B_ESCHR_COL S S -R -R +S +S FALSE 6 -2010-03-17 -I9 +2011-03-08 +I8 B_ESCHR_COL +R S -S -S +R S FALSE 7 -2010-05-03 -I9 +2011-04-11 +I8 B_ESCHR_COL S -S +R S S FALSE 8 -2010-07-03 -I9 +2011-04-23 +I8 B_ESCHR_COL S S -S +R S FALSE 9 -2010-09-11 -I9 +2011-06-21 +I8 B_ESCHR_COL R S @@ -615,18 +615,18 @@ 10 -2010-09-24 -I9 +2011-07-06 +I8 B_ESCHR_COL S -R +S S S FALSE -

Only 1 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.

+

Only 2 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(.)) %>% 
@@ -637,7 +637,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,861 first weighted isolates (79.3% of total)
+#> => Found 15,909 first weighted isolates (79.5% of total) @@ -654,104 +654,104 @@ - - + + + - - - + + - + - + - - + + - + - - + + - + - + - - + + - - + + - - + + + - - + - - + + - + - + - - + + - + - + - - + + @@ -762,11 +762,11 @@ - - + + - + @@ -774,11 +774,11 @@
isolate
12010-02-12I92010-01-18I8 B_ESCHR_COLI S S SR TRUE TRUE
22010-02-12I92010-03-30I8 B_ESCHR_COLR SI S S FALSETRUEFALSE
32010-02-22I92010-10-05I8 B_ESCHR_COL RS R SS FALSE TRUE
42010-03-05I92011-01-26I8 B_ESCHR_COL SSR R SFALSETRUE TRUE
52010-03-08I92011-02-01I8 B_ESCHR_COL S SRRSS FALSE TRUE
62010-03-17I92011-03-08I8 B_ESCHR_COLR SSSR S FALSE TRUE
72010-05-03I92011-04-11I8 B_ESCHR_COL SSR S S FALSEFALSETRUE
82010-07-03I92011-04-23I8 B_ESCHR_COL S SSR S FALSEFALSETRUE
92010-09-11I92011-06-21I8 B_ESCHR_COL R S
102010-09-24I92011-07-06I8 B_ESCHR_COL SRS S S FALSE
-

Instead of 1, now 8 isolates are flagged. In total, 79.3% of all isolates are marked ‘first weighted’ - 50.8% 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 2, now 9 isolates are flagged. In total, 79.5% of all isolates are marked ‘first weighted’ - 51% 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,861 isolates for analysis.

+

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

We can remove unneeded columns:

data_1st <- data_1st %>% 
   select(-c(first, keyab))
@@ -786,7 +786,6 @@
head(data_1st)
- @@ -803,44 +802,11 @@ - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - + + + - + @@ -851,51 +817,78 @@ - - - + + - - - + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + - - - - + + + + - - + - - - - - + + + + + + - - - - - - + + + + @@ -915,9 +908,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 a data.frame (15,861 x 13)

+

Frequency table of genus and species from a data.frame (15,909 x 13)

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

Shortest: 16
Longest: 24

@@ -934,33 +927,33 @@ Longest: 24

- - - - + + + + - - - - + + + + - - - - + + + + - - - + + + @@ -971,7 +964,7 @@ 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.4744341
+#> [1] 0.4787856

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

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

- + - + - + - +
date patient_id hospital
12015-01-18F9Hospital BB_ESCHR_COLRSRSMGram negativeEscherichiacoliTRUE
32016-02-14J4Hospital AB_ESCHR_COLRISSMGram negativeEscherichiacoliTRUE
42010-12-25P2Hospital B2011-10-07O2Hospital C B_STRPT_PNESR S S RTRUE
52016-12-26S82013-10-20C10 Hospital AB_STRPT_PNESIB_ESCHR_COL S RSSMGram negativeEscherichiacoliTRUE
2014-08-25O4Hospital AB_ESCHR_COLSSSS FGram negativeEscherichiacoliTRUE
2011-10-28E3Hospital BB_STRPT_PNESSSRM Gram positive Streptococcus pneumoniae TRUE
62010-03-27R7Hospital D2010-08-31H1Hospital A B_KLBSL_PNE R SR SSFM Gram negative Klebsiella pneumoniae TRUE
82016-08-08K8Hospital BB_KLBSL_PNE2014-11-03U7Hospital AB_STPHY_AURSS RI SSMGram negativeKlebsiellapneumoniaeFGram positiveStaphylococcusaureus TRUE
1 Escherichia coli7,87949.7%7,87949.7%7,83749.3%7,83749.3%
2 Staphylococcus aureus3,91524.7%11,79474.4%3,94024.8%11,77774.0%
3 Streptococcus pneumoniae2,48215.6%14,27690.0%2,55416.1%14,33190.1%
4 Klebsiella pneumoniae1,58510.0%15,8611,5789.9%15,909 100.0%
Hospital A0.47599160.4717819
Hospital B0.48089970.4802632
Hospital C0.46827790.4870184
Hospital D0.46510150.4804169
@@ -1014,23 +1007,23 @@ Longest: 24

Hospital A -0.4759916 -4790 +0.4717819 +4731 Hospital B -0.4808997 -5602 +0.4802632 +5624 Hospital C -0.4682779 -2317 +0.4870184 +2388 Hospital D -0.4651015 -3152 +0.4804169 +3166 @@ -1050,27 +1043,27 @@ Longest: 24

Escherichia -0.7292804 -0.8975758 -0.9772814 +0.7256603 +0.8983029 +0.9729488 Klebsiella -0.7438486 -0.9015773 -0.9741325 +0.7338403 +0.8935361 +0.9689480 Staphylococcus -0.7315453 -0.9154534 -0.9793103 +0.7309645 +0.9233503 +0.9794416 Streptococcus -0.7352941 +0.7372749 0.0000000 -0.7352941 +0.7372749 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 946ecc29..90345fcf 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 377470a0..0d8369c9 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 1f14285d..0c510f53 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 9b15ee06..a57a3b57 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/benchmarks.html b/docs/articles/benchmarks.html index 43526b59..a0eb0d4e 100644 --- a/docs/articles/benchmarks.html +++ b/docs/articles/benchmarks.html @@ -217,14 +217,14 @@ times = 10) print(S.aureus, unit = "ms", signif = 3) #> Unit: milliseconds -#> expr min lq mean median uq max neval -#> as.mo("sau") 15.40 15.50 22.70 15.60 15.90 53.3 10 -#> as.mo("stau") 84.20 84.30 86.60 84.60 86.60 102.0 10 -#> as.mo("staaur") 15.40 15.40 19.70 15.50 15.60 57.1 10 -#> as.mo("STAAUR") 15.40 15.40 15.50 15.50 15.60 15.9 10 -#> as.mo("S. aureus") 23.50 23.50 31.10 23.50 23.60 61.7 10 -#> as.mo("S. aureus") 23.50 23.50 36.50 23.50 61.60 74.3 10 -#> as.mo("Staphylococcus aureus") 7.19 7.27 9.01 7.44 7.67 23.2 10
+#> expr min lq mean median uq max neval +#> as.mo("sau") 16.30 16.40 20.9 16.60 18.70 55.6 10 +#> as.mo("stau") 33.70 33.70 37.9 33.80 33.90 74.4 10 +#> as.mo("staaur") 16.30 16.30 16.6 16.40 16.70 17.8 10 +#> as.mo("STAAUR") 16.30 16.30 25.6 16.40 16.50 63.9 10 +#> as.mo("S. aureus") 24.20 24.30 27.2 24.60 26.70 45.2 10 +#> as.mo("S. aureus") 24.20 24.20 39.1 24.90 64.00 85.6 10 +#> as.mo("Staphylococcus aureus") 7.28 7.33 11.1 7.36 7.44 40.6 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"),
@@ -235,13 +235,13 @@
                                  times = 10)
 print(T.islandicus, unit = "ms", signif = 3)
 #> Unit: milliseconds
-#>                         expr   min    lq  mean median    uq   max neval
-#>              as.mo("theisl") 444.0 449.0 479.0  488.0 493.0 506.0    10
-#>              as.mo("THEISL") 444.0 484.0 488.0  491.0 507.0 514.0    10
-#>       as.mo("T. islandicus")  80.5  80.8  87.8   81.3  89.9 118.0    10
-#>      as.mo("T.  islandicus")  79.8  80.4  82.0   80.7  81.2  93.5    10
-#>  as.mo("Thermus islandicus")  63.4  63.5  72.3   64.0  64.5 107.0    10
-

That takes 7.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.

+#> expr min lq mean median uq max neval +#> as.mo("theisl") 287.0 296.0 329.0 330.0 334.0 432 10 +#> as.mo("THEISL") 286.0 292.0 333.0 329.0 366.0 433 10 +#> as.mo("T. islandicus") 72.9 73.1 90.1 75.7 94.1 161 10 +#> as.mo("T. islandicus") 72.8 73.5 89.4 79.7 115.0 125 10 +#> as.mo("Thermus islandicus") 65.8 66.0 76.8 67.7 85.2 107 10 +

That takes 7.2 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)
 
@@ -287,8 +287,8 @@
 print(run_it, unit = "ms", signif = 3)
 #> Unit: milliseconds
 #>            expr min  lq mean median  uq max neval
-#>  mo_fullname(x) 743 771  805    798 844 886    10
-

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

+#> mo_fullname(x) 716 738 778 763 778 899 10 +

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

@@ -300,11 +300,11 @@ times = 10) print(run_it, unit = "ms", signif = 3) #> Unit: milliseconds -#> expr min lq mean median uq max neval -#> A 10.900 11.100 11.200 11.200 11.300 11.400 10 -#> B 21.300 21.400 21.600 21.600 21.700 22.000 10 -#> C 0.302 0.313 0.492 0.532 0.569 0.725 10

-

So going from mo_fullname("Staphylococcus aureus") to "Staphylococcus aureus" takes 0.0005 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 10.90 11.600 26.700 21.200 47.80 51.000 10 +#> B 22.00 22.500 26.900 22.900 25.70 49.800 10 +#> C 0.32 0.557 0.565 0.565 0.59 0.828 10 +

So going from mo_fullname("Staphylococcus aureus") to "Staphylococcus aureus" takes 0.0006 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"),
@@ -317,14 +317,14 @@
 print(run_it, unit = "ms", signif = 3)
 #> Unit: milliseconds
 #>  expr   min    lq  mean median    uq   max neval
-#>     A 0.330 0.399 0.444  0.425 0.480 0.599    10
-#>     B 0.343 0.362 0.386  0.376 0.425 0.439    10
-#>     C 0.327 0.454 0.550  0.571 0.640 0.816    10
-#>     D 0.273 0.306 0.329  0.319 0.366 0.392    10
-#>     E 0.246 0.266 0.295  0.286 0.323 0.364    10
-#>     F 0.260 0.265 0.320  0.312 0.364 0.407    10
-#>     G 0.238 0.252 0.281  0.270 0.319 0.339    10
-#>     H 0.251 0.278 0.316  0.320 0.358 0.381    10
+#> A 0.297 0.343 0.399 0.388 0.457 0.518 10 +#> B 0.330 0.349 0.397 0.394 0.430 0.496 10 +#> C 0.345 0.365 0.521 0.519 0.689 0.697 10 +#> D 0.250 0.257 0.321 0.345 0.354 0.372 10 +#> E 0.270 0.315 0.339 0.329 0.362 0.444 10 +#> F 0.256 0.272 0.328 0.307 0.321 0.580 10 +#> G 0.237 0.277 0.299 0.304 0.320 0.349 10 +#> H 0.243 0.268 0.318 0.321 0.350 0.415 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.

@@ -351,13 +351,13 @@ print(run_it, unit = "ms", signif = 4) #> Unit: milliseconds #> expr min lq mean median uq max neval -#> en 14.37 14.43 17.91 14.64 14.82 47.42 10 -#> de 22.59 22.88 27.57 23.00 23.55 67.95 10 -#> nl 22.50 22.91 26.39 22.94 23.01 57.05 10 -#> es 22.56 22.76 26.83 23.05 24.02 57.31 10 -#> it 22.53 22.86 29.52 22.97 23.29 56.11 10 -#> fr 22.49 22.92 23.06 23.01 23.18 23.99 10 -#> pt 22.49 22.86 23.21 23.06 23.62 24.09 10
+#> en 14.79 15.17 16.14 15.30 15.69 22.59 10 +#> de 23.40 23.86 28.56 23.94 25.25 64.07 10 +#> nl 23.27 23.75 35.29 24.41 26.41 92.65 10 +#> es 23.64 23.85 31.38 24.29 24.87 63.61 10 +#> it 23.47 23.82 25.22 24.91 27.04 27.69 10 +#> fr 23.57 23.74 27.93 23.82 23.90 64.43 10 +#> pt 23.74 23.88 28.84 24.74 34.01 44.33 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 e4fd0ba2..9e93bdfe 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