diff --git a/R/mo.R b/R/mo.R index fcce4506..2256c09a 100755 --- a/R/mo.R +++ b/R/mo.R @@ -97,7 +97,7 @@ #' The artificial intelligence takes into account microbial prevalence of pathogens in humans. It uses three groups and every (sub)species is in the group it matches first. These groups are: #' \itemize{ #' \item{1 (most prevalent): class is Gammaproteobacteria \strong{or} genus is one of: \emph{Enterococcus}, \emph{Staphylococcus}, \emph{Streptococcus}.} -#' \item{2: phylum is one of: Proteobacteria, Firmicutes, Actinobacteria, Sarcomastigophora \strong{or} genus is one of: \emph{Aspergillus}, \emph{Bacteroides}, \emph{Candida}, \emph{Capnocytophaga}, \emph{Chryseobacterium}, \emph{Cryptococcus}, \emph{Elisabethkingia}, \emph{Flavobacterium}, \emph{Fusobacterium}, \emph{Giardia}, \emph{Leptotrichia}, \emph{Mycoplasma}, \emph{Prevotella}, \emph{Rhodotorula}, \emph{Treponema}, \emph{Trichophyton}.} +#' \item{2: phylum is one of: Proteobacteria, Firmicutes, Actinobacteria, Sarcomastigophora \strong{or} genus is one of: \emph{Aspergillus}, \emph{Bacteroides}, \emph{Candida}, \emph{Capnocytophaga}, \emph{Chryseobacterium}, \emph{Cryptococcus}, \emph{Elisabethkingia}, \emph{Flavobacterium}, \emph{Fusobacterium}, \emph{Giardia}, \emph{Leptotrichia}, \emph{Mycoplasma}, \emph{Prevotella}, \emph{Rhodotorula}, \emph{Treponema}, \emph{Trichophyton}, \emph{Ureaplasma}.} #' \item{3 (least prevalent): all others.} #' } #' @@ -167,10 +167,9 @@ #' } as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, allow_uncertain = TRUE, reference_df = get_mo_source()) { # will be checked for mo class in validation - mo <- mo_validate(x = x, property = "mo", - Becker = Becker, Lancefield = Lancefield, - allow_uncertain = allow_uncertain, reference_df = reference_df) - structure(.Data = mo, class = "mo") + mo_validate(x = x, property = "mo", + Becker = Becker, Lancefield = Lancefield, + allow_uncertain = allow_uncertain, reference_df = reference_df) } #' @rdname as.mo @@ -229,7 +228,7 @@ exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, x <- x[!is.na(x) & !is.null(x) & !identical(x, "")] # conversion of old MO codes from v0.5.0 (ITIS) to later versions (Catalogue of Life) - if (any(x %like% "^[BFP]_[A-Z]{3,7}")) { + if (any(x %like% "^[BFP]_[A-Z]{3,7}") & !all(x %in% microorganisms$mo)) { leftpart <- gsub("^([BFP]_[A-Z]{3,7}).*", "\\1", x) if (any(leftpart %in% names(mo_codes_v0.5.0))) { rightpart <- gsub("^[BFP]_[A-Z]{3,7}(.*)", "\\1", x) @@ -256,40 +255,52 @@ exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, # all empty if (all(identical(trimws(x_input), "") | is.na(x_input))) { if (property == "mo") { - return(structure(rep(NA_character_, length(x_input)), class = "mo")) + return(structure(rep(NA_character_, length(x_input)), + class = "mo")) } else { return(rep(NA_character_, length(x_input))) } } else if (all(x %in% reference_df[, 1]) - & all(reference_df[, "mo"] %in% microorganismsDT[, "mo"][[1]])) { + & all(reference_df[, "mo"] %in% AMR::microorganisms$mo)) { # all in reference df colnames(reference_df)[1] <- "x" suppressWarnings( x <- data.frame(x = x, stringsAsFactors = FALSE) %>% left_join(reference_df, by = "x") %>% - left_join(microorganisms, by = "mo") %>% + left_join(AMR::microorganisms, by = "mo") %>% pull(property) ) - } else if (all(x %in% microorganismsDT[, "mo"][[1]])) { + } else if (all(x %in% AMR::microorganisms$mo)) { # existing mo codes when not looking for property "mo", like mo_genus("B_ESCHR_COL") - x <- microorganismsDT[data.table(mo = x), on = "mo", ..property][[1]] + 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]] + } + if (any(is.na(y))) { + 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% microorganismsDT[prevalence == 1, "fullname"][[1]])) { + } else if (all(x %in% AMR::microorganisms$fullname)) { # we need special treatment for very prevalent full names, they are likely! # e.g. as.mo("Staphylococcus aureus") - x <- microorganismsDT[prevalence == 1][data.table(fullname = x), on = "fullname", ..property][[1]] - } else if (all(x %in% microorganismsDT[prevalence == 2, "fullname"][[1]])) { - # same for common full names, they are also likely - x <- microorganismsDT[prevalence == 2][data.table(fullname = x), on = "fullname", ..property][[1]] + y <- microorganismsDT[prevalence == 1][data.table(fullname = x), on = "fullname", ..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]] + } + if (any(is.na(y))) { + y[is.na(y)] <- microorganismsDT[prevalence == 3][data.table(fullname = x[is.na(y)]), on = "fullname", ..property][[1]] + } + x <- y - } else if (all(toupper(x) %in% microorganisms.codes[, "code"])) { + } else if (all(toupper(x) %in% AMR::microorganisms.codes$code)) { # commonly used MO codes - y <- as.data.table(microorganisms.codes)[data.table(code = toupper(x)), on = "code", ] + y <- as.data.table(AMR::microorganisms.codes)[data.table(code = toupper(x)), on = "code", ] x <- microorganismsDT[data.table(mo = y[["mo"]]), on = "mo", ..property][[1]] - } else if (!all(x %in% microorganismsDT[, ..property][[1]])) { + } else if (!all(x %in% AMR::microorganisms[, property])) { x_backup <- x @@ -504,8 +515,8 @@ exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, } # TRY OTHER SOURCES ---- - if (toupper(x_backup[i]) %in% microorganisms.codes[, 1]) { - mo_found <- microorganisms.codes[toupper(x_backup[i]) == microorganisms.codes[, 1], "mo"][1L] + if (toupper(x_backup[i]) %in% AMR::microorganisms.codes[, 1]) { + mo_found <- AMR::microorganisms.codes[toupper(x_backup[i]) == AMR::microorganisms.codes[, 1], "mo"][1L] if (length(mo_found) > 0) { x[i] <- microorganismsDT[mo == mo_found, ..property][[1]][1L] next diff --git a/R/mo_property.R b/R/mo_property.R index 2e7f4f51..0d3dc940 100755 --- a/R/mo_property.R +++ b/R/mo_property.R @@ -494,7 +494,7 @@ mo_validate <- function(x, property, ...) { # check onLoad() in R/zzz.R: data tables are created there. } - if (!all(x %in% microorganismsDT[, ..property][[1]]) + if (!all(x %in% microorganisms[, property]) | Becker %in% c(TRUE, "all") | Lancefield %in% c(TRUE, "all")) { exec_as.mo(x, property = property, ...) diff --git a/R/zzz.R b/R/zzz.R index d5156bba..5403922f 100755 --- a/R/zzz.R +++ b/R/zzz.R @@ -30,6 +30,10 @@ microorganisms.oldDT <- as.data.table(AMR::microorganisms.old) setkey(microorganisms.oldDT, col_id, fullname) + assign(x = "microorganisms", + value = make(), + envir = asNamespace("AMR")) + assign(x = "microorganismsDT", value = make_DT(), envir = asNamespace("AMR")) @@ -45,9 +49,8 @@ } #' @importFrom dplyr mutate case_when -#' @importFrom data.table as.data.table setkey -make_DT <- function() { - microorganismsDT <- AMR::microorganisms %>% +make <- function() { + AMR::microorganisms %>% mutate(prevalence = case_when( class == "Gammaproteobacteria" | genus %in% c("Enterococcus", "Staphylococcus", "Streptococcus") @@ -71,11 +74,16 @@ make_DT <- function() { "Prevotella", "Rhodotorula", "Treponema", - "Trichophyton") + "Trichophyton", + "Ureaplasma") ~ 2, TRUE ~ 3 - )) %>% - as.data.table() + )) +} + +#' @importFrom data.table as.data.table setkey +make_DT <- function() { + microorganismsDT <- as.data.table(make()) setkey(microorganismsDT, kingdom, prevalence, diff --git a/docs/articles/AMR.html b/docs/articles/AMR.html index 3f2aa1fa..9975163c 100644 --- a/docs/articles/AMR.html +++ b/docs/articles/AMR.html @@ -327,70 +327,70 @@
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 (1369 changes)
+#> Table 1: Intrinsic resistance in Enterobacteriaceae (1340 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 (2815 changes)
+#> Table 4: Intrinsic resistance in Gram-positive bacteria (2699 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,563 out of 20,000 rows
+#> => EUCAST rules affected 7,406 out of 20,000 rows
#> -> added 0 test results
-#> -> changed 4,184 test results (0 to S; 0 to I; 4,184 to R)
So only 28.9% is suitable for resistance analysis! We can now filter on it with the filter()
function, also from the dplyr
package:
So only 28.4% 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:
isolate | @@ -654,8 +654,8 @@||||||||||||||
---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|
1 | -2010-01-05 | -G4 | +2010-03-12 | +I7 | B_ESCHR_COL | S | S | @@ -666,8 +666,20 @@|||||||
2 | -2010-03-10 | -G4 | +2010-04-30 | +I7 | +B_ESCHR_COL | +S | +S | +R | +S | +FALSE | +TRUE | +|||
3 | +2010-06-28 | +I7 | B_ESCHR_COL | R | S | @@ -676,22 +688,10 @@FALSE | TRUE | |||||||
3 | -2010-07-15 | -G4 | -B_ESCHR_COL | -R | -S | -S | -S | -FALSE | -FALSE | -|||||
4 | -2010-09-07 | -G4 | +2010-07-08 | +I7 | B_ESCHR_COL | S | S | @@ -702,11 +702,11 @@|||||||
5 | -2010-11-10 | -G4 | +2010-08-22 | +I7 | B_ESCHR_COL | R | -S | +I | S | S | FALSE | @@ -714,23 +714,23 @@|||
6 | -2011-01-23 | -G4 | +2010-09-04 | +I7 | B_ESCHR_COL | -I | R | +I | S | S | -TRUE | -TRUE | +FALSE | +FALSE |
7 | -2011-02-21 | -G4 | +2010-11-16 | +I7 | B_ESCHR_COL | +R | S | -I | S | S | FALSE | @@ -738,47 +738,47 @@|||
8 | -2011-02-25 | -G4 | +2011-03-31 | +I7 | B_ESCHR_COL | +S | +S | R | S | -S | -S | -FALSE | +TRUE | TRUE |
9 | -2011-02-28 | -G4 | +2011-05-25 | +I7 | B_ESCHR_COL | S | S | -S | +R | S | FALSE | -TRUE | +FALSE | |
10 | -2011-04-03 | -G4 | +2011-08-25 | +I7 | B_ESCHR_COL | R | S | -S | +R | S | FALSE | TRUE |
Instead of 2, now 8 isolates are flagged. In total, 79.8% of all isolates are marked ‘first weighted’ - 50.9% 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 7 isolates are flagged. In total, 79.7% of all isolates are marked ‘first weighted’ - 51.3% 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:
So we end up with 15,963 isolates for analysis.
+So we end up with 15,935 isolates for analysis.
We can remove unneeded columns:
@@ -786,7 +786,6 @@date | patient_id | hospital | @@ -803,101 +802,95 @@||||||||||||||||||
---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|
1 | -2016-10-19 | -U5 | +2010-07-18 | +Z5 | Hospital B | -B_ESCHR_COL | +B_STRPT_PNE | +S | S | S | R | -S | F | -Gram negative | -Escherichia | -coli | +Gram positive | +Streptococcus | +pneumoniae | TRUE |
3 | -2014-11-05 | -A2 | -Hospital A | -B_STPHY_AUR | -S | -S | -R | -S | -M | -Gram positive | -Staphylococcus | -aureus | -TRUE | -|||||||
5 | -2010-03-02 | -X6 | -Hospital B | -B_ESCHR_COL | -S | -S | -S | -S | -F | -Gram negative | -Escherichia | -coli | -TRUE | -|||||||
6 | -2015-08-17 | -B8 | -Hospital D | -B_STPHY_AUR | -R | -S | -S | -S | -M | -Gram positive | -Staphylococcus | -aureus | -TRUE | -|||||||
7 | -2013-01-25 | -M3 | -Hospital A | -B_STPHY_AUR | -R | -R | -S | -S | -M | -Gram positive | -Staphylococcus | -aureus | -TRUE | -|||||||
8 | -2013-07-27 | -E2 | +2017-01-13 | +P8 | Hospital C | +B_ESCHR_COL | +R | +S | +S | +S | +F | +Gram negative | +Escherichia | +coli | +TRUE | +|||||
2014-07-31 | +K5 | +Hospital B | +B_ESCHR_COL | +S | +S | +S | +S | +M | +Gram negative | +Escherichia | +coli | +TRUE | +||||||||
2017-07-12 | +U8 | +Hospital B | B_KLBSL_PNE | R | S | S | S | -M | +F | Gram negative | Klebsiella | pneumoniae | TRUE | |||||||
2013-09-10 | +Y1 | +Hospital B | +B_KLBSL_PNE | +R | +R | +S | +S | +F | +Gram negative | +Klebsiella | +pneumoniae | +TRUE | +||||||||
2017-07-30 | +X10 | +Hospital C | +B_STRPT_PNE | +S | +S | +S | +R | +F | +Gram positive | +Streptococcus | +pneumoniae | +TRUE | +
Time for the analysis!
@@ -915,9 +908,9 @@Or can be used like the dplyr
way, which is easier readable:
Frequency table of genus
and species
from a data.frame
(15,963 x 13)
Frequency table of genus
and species
from a data.frame
(15,935 x 13)
Columns: 2
-Length: 15,963 (of which NA: 0 = 0.00%)
+Length: 15,935 (of which NA: 0 = 0.00%)
Unique: 4
Shortest: 16
Longest: 24
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:
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
Hospital A
-0.4765396
+0.4740616
Hospital B
-0.4750632
+0.4748265
Hospital C
-0.4830405
+0.4910305
Hospital D
-0.4657107
+0.4777953
@@ -1014,23 +1007,23 @@ Longest: 24
Hospital A
-0.4765396
-4774
+0.4740616
+4742
Hospital B
-0.4750632
-5534
+0.4748265
+5621
Hospital C
-0.4830405
-2447
+0.4910305
+2397
Hospital D
-0.4657107
-3208
+0.4777953
+3175
@@ -1050,27 +1043,27 @@ Longest: 24
Escherichia
-0.7353982
-0.8972187
-0.9734513
+0.7295518
+0.9013674
+0.9772094
Klebsiella
-0.7369359
-0.9014252
-0.9786223
+0.7517505
+0.9000637
+0.9789943
Staphylococcus
-0.7413217
-0.9161738
-0.9763435
+0.7353747
+0.9168534
+0.9788399
Streptococcus
-0.7181452
+0.7390772
0.0000000
-0.7181452
+0.7390772
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 f154850a..6f5f6c3b 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 7c7015b5..6f22a8ba 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 566ac025..c954d5c6 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 80319c61..08fe5b7b 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 71f64d91..87f36dc1 100644
--- a/docs/articles/benchmarks.html
+++ b/docs/articles/benchmarks.html
@@ -210,56 +210,47 @@
S.aureus <- microbenchmark(as.mo("sau"),
as.mo("stau"),
as.mo("staaur"),
- as.mo("S. aureus"),
- as.mo("S. aureus"),
- as.mo("STAAUR"),
+ as.mo("STAAUR"),
+ as.mo("S. aureus"),
+ as.mo("S. aureus"),
as.mo("Staphylococcus aureus"),
times = 10)
print(S.aureus, unit = "ms", signif = 3)
#> Unit: milliseconds
#> expr min lq mean median uq max neval
-#> as.mo("sau") 16.4 16.5 28.4 16.8 54.9 55.8 10
-#> as.mo("stau") 86.0 86.5 97.3 88.9 100.0 132.0 10
-#> as.mo("staaur") 16.3 16.6 23.0 16.8 21.0 56.8 10
-#> as.mo("S. aureus") 25.3 25.9 39.4 27.2 64.0 74.5 10
-#> as.mo("S. aureus") 25.2 25.3 29.7 25.6 27.0 64.3 10
-#> as.mo("STAAUR") 16.3 16.7 21.1 17.0 18.0 56.8 10
-#> as.mo("Staphylococcus aureus") 13.5 13.9 20.5 14.4 17.5 51.2 10
+#> as.mo("sau") 12.1 12.2 12.3 12.2 12.3 12.6 10
+#> as.mo("stau") 81.3 81.9 97.3 82.7 120.0 155.0 10
+#> as.mo("staaur") 12.2 12.3 12.7 12.6 13.2 13.5 10
+#> as.mo("STAAUR") 12.2 12.3 16.5 12.6 13.4 50.7 10
+#> as.mo("S. aureus") 20.1 20.1 25.2 20.1 20.2 69.9 10
+#> as.mo("S. aureus") 20.1 20.2 20.7 20.3 21.6 22.0 10
+#> as.mo("Staphylococcus aureus") 11.2 11.3 11.5 11.3 11.5 12.4 10
In the table above, all measurements are shown in milliseconds (thousands of seconds). A value of 10 milliseconds means it can determine 100 input values per second. It case of 50 milliseconds, this is only 20 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 is a WHONET code) or common laboratory codes, or common full organism names like the last one.
-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 Mycoplasma leonicaptivi (B_MYCPL_LEO
), a bug probably never found before in humans:
M.leonicaptivi <- microbenchmark(as.mo("myle"),
- as.mo("mycleo"),
- as.mo("M. leonicaptivi"),
- as.mo("M. leonicaptivi"),
- as.mo("MYCLEO"),
- as.mo("Mycoplasma leonicaptivi"),
- times = 10)
-print(M.leonicaptivi, unit = "ms", signif = 3)
-#> Unit: milliseconds
-#> expr min lq mean median uq max
-#> as.mo("myle") 135.0 135.0 147.0 135.0 174.0 176.0
-#> as.mo("mycleo") 211.0 213.0 233.0 232.0 251.0 262.0
-#> as.mo("M. leonicaptivi") 59.2 59.2 63.6 59.4 59.6 98.7
-#> as.mo("M. leonicaptivi") 59.0 59.1 59.3 59.3 59.3 59.7
-#> as.mo("MYCLEO") 211.0 211.0 220.0 211.0 222.0 250.0
-#> as.mo("Mycoplasma leonicaptivi") 22.5 22.5 26.5 22.6 22.7 61.0
-#> neval
-#> 10
-#> 10
-#> 10
-#> 10
-#> 10
-#> 10
That takes 3.4 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.
-In the figure below, we compare Escherichia coli (which is very common) with Prevotella brevis (which is moderately common) and with Mycoplasma leonicaptivi (which is very uncommon):
+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"),
+ as.mo("THEISL"),
+ as.mo("T. islandicus"),
+ as.mo("T. islandicus"),
+ as.mo("Thermus islandicus"),
+ times = 10)
+print(T.islandicus, unit = "ms", signif = 3)
+#> Unit: milliseconds
+#> expr min lq mean median uq max neval
+#> as.mo("theisl") 446.0 452.0 478.0 486.0 488.0 506 10
+#> as.mo("THEISL") 446.0 446.0 471.0 467.0 489.0 528 10
+#> as.mo("T. islandicus") 76.5 77.1 87.4 77.2 85.4 127 10
+#> as.mo("T. islandicus") 76.9 76.9 81.4 77.1 79.1 116 10
+#> as.mo("Thermus islandicus") 67.6 67.7 80.0 67.9 106.0 112 10
That takes 8.5 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)
-boxplot(microbenchmark(as.mo("M. leonicaptivi"),
- as.mo("Mycoplasma leonicaptivi"),
- as.mo("P. brevis"),
- as.mo("Prevotella brevis"),
- as.mo("E. coli"),
- as.mo("Escherichia coli"),
+boxplot(microbenchmark(as.mo("Thermus islandicus"),
+ as.mo("Prevotella brevis"),
+ as.mo("Escherichia coli"),
+ as.mo("T. islandicus"),
+ as.mo("P. brevis"),
+ as.mo("E. coli"),
times = 50),
horizontal = TRUE, las = 1, unit = "s", log = FALSE,
xlab = "", ylab = "Time in seconds",
@@ -271,27 +262,33 @@
Repetitive results
Repetitive results mean that unique values are present more than once. Unique values will only be calculated once by as.mo()
. We will use mo_fullname()
for this test - a helper function that returns the full microbial name (genus, species and possibly subspecies) which uses as.mo()
internally.
library(dplyr)
-# take 500,000 random MO codes from the septic_patients data set
-x = septic_patients %>%
- sample_n(500000, replace = TRUE) %>%
- pull(mo)
-
-# got the right length?
-length(x)
-#> [1] 500000
-
-# and how many unique values do we have?
-n_distinct(x)
-#> [1] 95
-
-# now let's see:
-run_it <- microbenchmark(mo_fullname(x),
- times = 10)
-print(run_it, unit = "ms", signif = 3)
-#> Unit: milliseconds
-#> expr min lq mean median uq max neval
-#> mo_fullname(x) 610 641 644 644 657 665 10
-So transforming 500,000 values (!) of 95 unique values only takes 0.64 seconds (644 ms). You only lose time on your unique input values.
+# take all MO codes from the septic_patients data set
+x <- septic_patients$mo %>%
+ # keep only the unique ones
+ unique() %>%
+ # pick 50 of them at random
+ sample(50) %>%
+ # paste that 10,000 times
+ rep(10000) %>%
+ # scramble it
+ sample()
+
+# got indeed 50 times 10,000 = half a million?
+length(x)
+#> [1] 500000
+
+# and how many unique values do we have?
+n_distinct(x)
+#> [1] 50
+
+# now let's see:
+run_it <- microbenchmark(mo_fullname(x),
+ times = 10)
+print(run_it, unit = "ms", signif = 3)
+#> Unit: milliseconds
+#> expr min lq mean median uq max neval
+#> mo_fullname(x) 679 731 768 762 779 886 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.
So going from mo_fullname("Staphylococcus aureus")
to "Staphylococcus aureus"
takes 0.0007 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:
So going from mo_fullname("Staphylococcus aureus")
to "Staphylococcus aureus"
takes 0.0004 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"),
@@ -320,14 +317,14 @@
print(run_it, unit = "ms", signif = 3)
#> Unit: milliseconds
#> expr min lq mean median uq max neval
-#> A 0.704 0.806 0.897 0.867 1.040 1.130 10
-#> B 0.671 0.722 0.841 0.807 0.903 1.110 10
-#> C 0.702 0.768 0.856 0.816 0.967 1.160 10
-#> D 0.641 0.695 0.746 0.746 0.755 0.976 10
-#> E 0.627 0.702 0.781 0.762 0.789 1.100 10
-#> F 0.651 0.694 0.779 0.733 0.761 1.220 10
-#> G 0.552 0.745 0.801 0.764 0.815 1.090 10
-#> H 0.637 0.661 0.722 0.724 0.766 0.803 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.
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 05045eea..d61c4155 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/reference/as.mo.html b/docs/reference/as.mo.html index b3818aa3..982f5f61 100644 --- a/docs/reference/as.mo.html +++ b/docs/reference/as.mo.html @@ -334,7 +334,7 @@ When usingallow_uncertain = TRUE
(which is the default setting), i
The artificial intelligence takes into account microbial prevalence of pathogens in humans. It uses three groups and every (sub)species is in the group it matches first. These groups are:
1 (most prevalent): class is Gammaproteobacteria or genus is one of: Enterococcus, Staphylococcus, Streptococcus.
2: phylum is one of: Proteobacteria, Firmicutes, Actinobacteria, Sarcomastigophora or genus is one of: Aspergillus, Bacteroides, Candida, Capnocytophaga, Chryseobacterium, Cryptococcus, Elisabethkingia, Flavobacterium, Fusobacterium, Giardia, Leptotrichia, Mycoplasma, Prevotella, Rhodotorula, Treponema, Trichophyton.
2: phylum is one of: Proteobacteria, Firmicutes, Actinobacteria, Sarcomastigophora or genus is one of: Aspergillus, Bacteroides, Candida, Capnocytophaga, Chryseobacterium, Cryptococcus, Elisabethkingia, Flavobacterium, Fusobacterium, Giardia, Leptotrichia, Mycoplasma, Prevotella, Rhodotorula, Treponema, Trichophyton, Ureaplasma.
3 (least prevalent): all others.
Group 1 contains all common Gram negatives, like all Enterobacteriaceae and e.g. Pseudomonas and Legionella.
diff --git a/man/as.mo.Rd b/man/as.mo.Rd index a2ed36a4..81eb4b9d 100644 --- a/man/as.mo.Rd +++ b/man/as.mo.Rd @@ -105,7 +105,7 @@ Use \code{mo_renamed()} to get a vector with all values that could be coerced ba The artificial intelligence takes into account microbial prevalence of pathogens in humans. It uses three groups and every (sub)species is in the group it matches first. These groups are: \itemize{ \item{1 (most prevalent): class is Gammaproteobacteria \strong{or} genus is one of: \emph{Enterococcus}, \emph{Staphylococcus}, \emph{Streptococcus}.} - \item{2: phylum is one of: Proteobacteria, Firmicutes, Actinobacteria, Sarcomastigophora \strong{or} genus is one of: \emph{Aspergillus}, \emph{Bacteroides}, \emph{Candida}, \emph{Capnocytophaga}, \emph{Chryseobacterium}, \emph{Cryptococcus}, \emph{Elisabethkingia}, \emph{Flavobacterium}, \emph{Fusobacterium}, \emph{Giardia}, \emph{Leptotrichia}, \emph{Mycoplasma}, \emph{Prevotella}, \emph{Rhodotorula}, \emph{Treponema}, \emph{Trichophyton}.} + \item{2: phylum is one of: Proteobacteria, Firmicutes, Actinobacteria, Sarcomastigophora \strong{or} genus is one of: \emph{Aspergillus}, \emph{Bacteroides}, \emph{Candida}, \emph{Capnocytophaga}, \emph{Chryseobacterium}, \emph{Cryptococcus}, \emph{Elisabethkingia}, \emph{Flavobacterium}, \emph{Fusobacterium}, \emph{Giardia}, \emph{Leptotrichia}, \emph{Mycoplasma}, \emph{Prevotella}, \emph{Rhodotorula}, \emph{Treponema}, \emph{Trichophyton}, \emph{Ureaplasma}.} \item{3 (least prevalent): all others.} } diff --git a/vignettes/benchmarks.Rmd b/vignettes/benchmarks.Rmd index 46b94f6a..cf2891d9 100755 --- a/vignettes/benchmarks.Rmd +++ b/vignettes/benchmarks.Rmd @@ -44,9 +44,9 @@ But the calculation time differs a lot. Here, the AI effect can be reviewed best S.aureus <- microbenchmark(as.mo("sau"), as.mo("stau"), as.mo("staaur"), + as.mo("STAAUR"), as.mo("S. aureus"), as.mo("S. aureus"), - as.mo("STAAUR"), as.mo("Staphylococcus aureus"), times = 10) print(S.aureus, unit = "ms", signif = 3) @@ -54,32 +54,31 @@ print(S.aureus, unit = "ms", signif = 3) In the table above, all measurements are shown in milliseconds (thousands of seconds). A value of 10 milliseconds means it can determine 100 input values per second. It case of 50 milliseconds, this is only 20 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 is a WHONET code) or common laboratory codes, or common full organism names like the last one. -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 *Mycoplasma leonicaptivi* (`B_MYCPL_LEO`), a bug probably never found before in humans: +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: ```{r} -M.leonicaptivi <- microbenchmark(as.mo("myle"), - as.mo("mycleo"), - as.mo("M. leonicaptivi"), - as.mo("M. leonicaptivi"), - as.mo("MYCLEO"), - as.mo("Mycoplasma leonicaptivi"), +T.islandicus <- microbenchmark(as.mo("theisl"), + as.mo("THEISL"), + as.mo("T. islandicus"), + as.mo("T. islandicus"), + as.mo("Thermus islandicus"), times = 10) -print(M.leonicaptivi, unit = "ms", signif = 3) +print(T.islandicus, unit = "ms", signif = 3) ``` -That takes `r round(mean(M.leonicaptivi$time, na.rm = TRUE) / mean(S.aureus$time, na.rm = TRUE), 1)` 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. +That takes `r round(mean(T.islandicus$time, na.rm = TRUE) / mean(S.aureus$time, na.rm = TRUE), 1)` 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 *Mycoplasma leonicaptivi* (which is very uncommon): +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): ```{r} par(mar = c(5, 16, 4, 2)) # set more space for left margin text (16) -boxplot(microbenchmark(as.mo("M. leonicaptivi"), - as.mo("Mycoplasma leonicaptivi"), - as.mo("P. brevis"), +boxplot(microbenchmark(as.mo("Thermus islandicus"), as.mo("Prevotella brevis"), - as.mo("E. coli"), as.mo("Escherichia coli"), + as.mo("T. islandicus"), + as.mo("P. brevis"), + as.mo("E. coli"), times = 50), horizontal = TRUE, las = 1, unit = "s", log = FALSE, xlab = "", ylab = "Time in seconds", @@ -94,12 +93,18 @@ Repetitive results mean that unique values are present more than once. Unique va ```{r, message = FALSE} library(dplyr) -# take 500,000 random MO codes from the septic_patients data set -x = septic_patients %>% - sample_n(500000, replace = TRUE) %>% - pull(mo) +# take all MO codes from the septic_patients data set +x <- septic_patients$mo %>% + # keep only the unique ones + unique() %>% + # pick 50 of them at random + sample(50) %>% + # paste that 10,000 times + rep(10000) %>% + # scramble it + sample() -# got the right length? +# got indeed 50 times 10,000 = half a million? length(x) # and how many unique values do we have? @@ -111,7 +116,7 @@ run_it <- microbenchmark(mo_fullname(x), print(run_it, unit = "ms", signif = 3) ``` -So transforming 500,000 values (!) of `r n_distinct(x)` unique values only takes `r round(median(run_it$time, na.rm = TRUE) / 1e9, 2)` seconds (`r as.integer(median(run_it$time, na.rm = TRUE) / 1e6)` ms). You only lose time on your unique input values. +So transforming 500,000 values (!!) of `r n_distinct(x)` unique values only takes `r round(median(run_it$time, na.rm = TRUE) / 1e9, 2)` seconds (`r as.integer(median(run_it$time, na.rm = TRUE) / 1e6)` ms). You only lose time on your unique input values. ### Precalculated results