as.mo improvement
| @@ -1,6 +1,6 @@ | ||||
| Package: AMR | ||||
| Version: 0.5.0.9018 | ||||
| Date: 2019-02-22 | ||||
| Date: 2019-02-23 | ||||
| Title: Antimicrobial Resistance Analysis | ||||
| Authors@R: c( | ||||
|     person( | ||||
|   | ||||
							
								
								
									
										27
									
								
								R/mo.R
									
									
									
									
									
								
							
							
						
						| @@ -84,7 +84,6 @@ | ||||
| #' \itemize{ | ||||
| #'   \item{\code{"Streptococcus group B (known as S. agalactiae)"}. The text between brackets will be removed and a warning will be thrown that the result \emph{Streptococcus group B} (\code{B_STRPT_GRB}) needs review.} | ||||
| #'   \item{\code{"S. aureus - please mind: MRSA"}. The last word will be stripped, after which the function will try to find a match. If it does not, the second last word will be stripped, etc. Again, a warning will be thrown that the result \emph{Staphylococcus aureus} (\code{B_STPHY_AUR}) needs review.} | ||||
| #'   \item{\code{"D. spartina"}. This is the abbreviation of an old taxonomic name: \emph{Didymosphaeria spartinae} (the last "e" was missing from the input). This fungus was renamed to \emph{Leptosphaeria obiones}, so a warning will be thrown that this result (\code{F_LPTSP_OBI}) needs review.} | ||||
| #'   \item{\code{"Fluoroquinolone-resistant Neisseria gonorrhoeae"}. The first word will be stripped, after which the function will try to find a match. A warning will be thrown that the result \emph{Neisseria gonorrhoeae} (\code{B_NESSR_GON}) needs review.} | ||||
| #' } | ||||
| #' | ||||
| @@ -156,6 +155,7 @@ | ||||
| #'   mutate(mo = as.mo(paste(genus, species))) | ||||
| #' } | ||||
| 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) | ||||
| @@ -170,7 +170,7 @@ is.mo <- function(x) { | ||||
|  | ||||
| #' @importFrom dplyr %>% pull left_join n_distinct progress_estimated filter | ||||
| #' @importFrom data.table data.table as.data.table setkey | ||||
| #' @importFrom crayon magenta red silver italic has_color | ||||
| #' @importFrom crayon magenta red blue silver italic has_color | ||||
| exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, | ||||
|                        allow_uncertain = TRUE, reference_df = get_mo_source(), | ||||
|                        property = "mo", clear_options = TRUE) { | ||||
| @@ -210,12 +210,12 @@ exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, | ||||
|   uncertainties <- character(0) | ||||
|   failures <- character(0) | ||||
|   x_input <- x | ||||
|   x <- trimws(x, which = "both") | ||||
|   # only check the uniques, which is way faster | ||||
|   x <- unique(x) | ||||
|   # remove empty values (to later fill them in again with NAs) | ||||
|   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}")) { | ||||
|     leftpart <- gsub("^([BFP]_[A-Z]{3,7}).*", "\\1", x) | ||||
| @@ -271,7 +271,7 @@ exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, | ||||
|  | ||||
|   } else if (!all(x %in% microorganismsDT[[property]])) { | ||||
|  | ||||
|     x_backup <- trimws(x, which = "both") | ||||
|     x_backup <- x # trimws(x, which = "both") | ||||
|  | ||||
|     # remove spp and species | ||||
|     x <- trimws(gsub(" +(spp.?|ssp.?|sp.? |ss ?.?|subsp.?|subspecies|biovar |serovar |species)", " ", x_backup, ignore.case = TRUE), which = "both") | ||||
| @@ -323,6 +323,13 @@ exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, | ||||
|  | ||||
|       progress$tick()$print() | ||||
|  | ||||
|       found <- microorganismsDT[mo == toupper(x_backup[i]), ..property][[1]] | ||||
|       # is a valid MO code | ||||
|       if (length(found) > 0) { | ||||
|         x[i] <- found[1L] | ||||
|         next | ||||
|       } | ||||
|  | ||||
|       if (tolower(x_trimmed[i]) %in% c("", "xxx", "other", "none", "unknown")) { | ||||
|         # empty and nonsense values, ignore without warning ("xxx" is WHONET code for 'no growth') | ||||
|         x[i] <- NA_character_ | ||||
| @@ -510,11 +517,11 @@ exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, | ||||
|           return(found[1L]) | ||||
|         } | ||||
|  | ||||
|         found <- data_to_check[mo == toupper(a.x_backup), ..property][[1]] | ||||
|         # is a valid mo | ||||
|         if (length(found) > 0) { | ||||
|           return(found[1L]) | ||||
|         } | ||||
|         # found <- data_to_check[mo == toupper(a.x_backup), ..property][[1]] | ||||
|         # # is a valid mo | ||||
|         # if (length(found) > 0) { | ||||
|         #   return(found[1L]) | ||||
|         # } | ||||
|         found <- data_to_check[tolower(fullname) == tolower(c.x_trimmed_without_group), ..property][[1]] | ||||
|         if (length(found) > 0) { | ||||
|           return(found[1L]) | ||||
| @@ -872,7 +879,7 @@ TEMPORARY_TAXONOMY <- function(x) { | ||||
|   x | ||||
| } | ||||
|  | ||||
| #' @importFrom crayon blue italic | ||||
| #' @importFrom crayon italic | ||||
| was_renamed <- function(name_old, name_new, ref_old = "", ref_new = "", mo = "") { | ||||
|   if (!is.na(ref_old)) { | ||||
|     ref_old <- paste0(" (", ref_old, ")") | ||||
|   | ||||
| @@ -192,7 +192,7 @@ | ||||
|       <h1>How to conduct AMR analysis</h1> | ||||
|                         <h4 class="author">Matthijs S. Berends</h4> | ||||
|              | ||||
|             <h4 class="date">22 February 2019</h4> | ||||
|             <h4 class="date">23 February 2019</h4> | ||||
|        | ||||
|        | ||||
|       <div class="hidden name"><code>AMR.Rmd</code></div> | ||||
| @@ -201,7 +201,7 @@ | ||||
|  | ||||
|      | ||||
|      | ||||
| <p><strong>Note:</strong> values on this page will change with every website update since they are based on randomly created values and the page was written in <a href="https://rmarkdown.rstudio.com/">RMarkdown</a>. However, the methodology remains unchanged. This page was generated on 22 February 2019.</p> | ||||
| <p><strong>Note:</strong> values on this page will change with every website update since they are based on randomly created values and the page was written in <a href="https://rmarkdown.rstudio.com/">RMarkdown</a>. However, the methodology remains unchanged. This page was generated on 23 February 2019.</p> | ||||
| <div id="introduction" class="section level1"> | ||||
| <h1 class="hasAnchor"> | ||||
| <a href="#introduction" class="anchor"></a>Introduction</h1> | ||||
| @@ -217,21 +217,21 @@ | ||||
| </tr></thead> | ||||
| <tbody> | ||||
| <tr class="odd"> | ||||
| <td align="center">2019-02-22</td> | ||||
| <td align="center">2019-02-23</td> | ||||
| <td align="center">abcd</td> | ||||
| <td align="center">Escherichia coli</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">2019-02-22</td> | ||||
| <td align="center">2019-02-23</td> | ||||
| <td align="center">abcd</td> | ||||
| <td align="center">Escherichia coli</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">2019-02-22</td> | ||||
| <td align="center">2019-02-23</td> | ||||
| <td align="center">efgh</td> | ||||
| <td align="center">Escherichia coli</td> | ||||
| <td align="center">R</td> | ||||
| @@ -327,70 +327,70 @@ | ||||
| </tr></thead> | ||||
| <tbody> | ||||
| <tr class="odd"> | ||||
| <td align="center">2014-11-25</td> | ||||
| <td align="center">O2</td> | ||||
| <td align="center">Hospital D</td> | ||||
| <td align="center">Escherichia coli</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">F</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">2016-11-18</td> | ||||
| <td align="center">I10</td> | ||||
| <td align="center">2011-09-14</td> | ||||
| <td align="center">N3</td> | ||||
| <td align="center">Hospital B</td> | ||||
| <td align="center">Escherichia coli</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">M</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">2014-08-15</td> | ||||
| <td align="center">G9</td> | ||||
| <td align="center">Hospital D</td> | ||||
| <td align="center">Staphylococcus aureus</td> | ||||
| <tr class="even"> | ||||
| <td align="center">2011-01-09</td> | ||||
| <td align="center">I3</td> | ||||
| <td align="center">Hospital A</td> | ||||
| <td align="center">Escherichia coli</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">M</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">2017-07-26</td> | ||||
| <td align="center">S2</td> | ||||
| <td align="center">Hospital B</td> | ||||
| <td align="center">Staphylococcus aureus</td> | ||||
| <tr class="odd"> | ||||
| <td align="center">2015-06-02</td> | ||||
| <td align="center">E8</td> | ||||
| <td align="center">Hospital A</td> | ||||
| <td align="center">Streptococcus pneumoniae</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">M</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">2011-02-06</td> | ||||
| <td align="center">S1</td> | ||||
| <td align="center">Hospital D</td> | ||||
| <td align="center">Escherichia coli</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">F</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">2017-01-25</td> | ||||
| <td align="center">H5</td> | ||||
| <td align="center">2010-01-27</td> | ||||
| <td align="center">N7</td> | ||||
| <td align="center">Hospital C</td> | ||||
| <td align="center">Escherichia coli</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">I</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">M</td> | ||||
| <td align="center">F</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">2017-03-12</td> | ||||
| <td align="center">B9</td> | ||||
| <td align="center">Hospital C</td> | ||||
| <td align="center">2017-08-11</td> | ||||
| <td align="center">U3</td> | ||||
| <td align="center">Hospital B</td> | ||||
| <td align="center">Escherichia coli</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">M</td> | ||||
| <td align="center">F</td> | ||||
| </tr> | ||||
| </tbody> | ||||
| </table> | ||||
| @@ -411,8 +411,8 @@ | ||||
| #>  | ||||
| #>      Item     Count   Percent   Cum. Count   Cum. Percent | ||||
| #> ---  -----  -------  --------  -----------  ------------- | ||||
| #> 1    M       10,377     51.9%       10,377          51.9% | ||||
| #> 2    F        9,623     48.1%       20,000         100.0%</code></pre> | ||||
| #> 1    M       10,364     51.8%       10,364          51.8% | ||||
| #> 2    F        9,636     48.2%       20,000         100.0%</code></pre> | ||||
| <p>So, we can draw at least two conclusions immediately. From a data scientist perspective, the data looks clean: only values <code>M</code> and <code>F</code>. From a researcher perspective: there are slightly more men. Nothing we didn’t already know.</p> | ||||
| <p>The data is already quite clean, but we still need to transform some variables. The <code>bacteria</code> 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 <code><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate()</a></code> function of the <code>dplyr</code> package makes this really easy:</p> | ||||
| <div class="sourceCode" id="cb12"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb12-1" title="1">data <-<span class="st"> </span>data <span class="op">%>%</span></a> | ||||
| @@ -443,10 +443,10 @@ | ||||
| <a class="sourceLine" id="cb14-19" title="19"><span class="co">#> Kingella kingae (no changes)</span></a> | ||||
| <a class="sourceLine" id="cb14-20" title="20"><span class="co">#> </span></a> | ||||
| <a class="sourceLine" id="cb14-21" title="21"><span class="co">#> EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)</span></a> | ||||
| <a class="sourceLine" id="cb14-22" title="22"><span class="co">#> Table 1:  Intrinsic resistance in Enterobacteriaceae (1284 changes)</span></a> | ||||
| <a class="sourceLine" id="cb14-22" title="22"><span class="co">#> Table 1:  Intrinsic resistance in Enterobacteriaceae (1334 changes)</span></a> | ||||
| <a class="sourceLine" id="cb14-23" title="23"><span class="co">#> Table 2:  Intrinsic resistance in non-fermentative Gram-negative bacteria (no changes)</span></a> | ||||
| <a class="sourceLine" id="cb14-24" title="24"><span class="co">#> Table 3:  Intrinsic resistance in other Gram-negative bacteria (no changes)</span></a> | ||||
| <a class="sourceLine" id="cb14-25" title="25"><span class="co">#> Table 4:  Intrinsic resistance in Gram-positive bacteria (2790 changes)</span></a> | ||||
| <a class="sourceLine" id="cb14-25" title="25"><span class="co">#> Table 4:  Intrinsic resistance in Gram-positive bacteria (2731 changes)</span></a> | ||||
| <a class="sourceLine" id="cb14-26" title="26"><span class="co">#> Table 8:  Interpretive rules for B-lactam agents and Gram-positive cocci (no changes)</span></a> | ||||
| <a class="sourceLine" id="cb14-27" title="27"><span class="co">#> Table 9:  Interpretive rules for B-lactam agents and Gram-negative rods (no changes)</span></a> | ||||
| <a class="sourceLine" id="cb14-28" title="28"><span class="co">#> Table 10: Interpretive rules for B-lactam agents and other Gram-negative bacteria (no changes)</span></a> | ||||
| @@ -462,9 +462,9 @@ | ||||
| <a class="sourceLine" id="cb14-38" title="38"><span class="co">#> Non-EUCAST: piperacillin/tazobactam = S where piperacillin = S (no changes)</span></a> | ||||
| <a class="sourceLine" id="cb14-39" title="39"><span class="co">#> Non-EUCAST: trimethoprim/sulfa = S where trimethoprim = S (no changes)</span></a> | ||||
| <a class="sourceLine" id="cb14-40" title="40"><span class="co">#> </span></a> | ||||
| <a class="sourceLine" id="cb14-41" title="41"><span class="co">#> => EUCAST rules affected 7,321 out of 20,000 rows</span></a> | ||||
| <a class="sourceLine" id="cb14-41" title="41"><span class="co">#> => EUCAST rules affected 7,419 out of 20,000 rows</span></a> | ||||
| <a class="sourceLine" id="cb14-42" title="42"><span class="co">#>    -> added 0 test results</span></a> | ||||
| <a class="sourceLine" id="cb14-43" title="43"><span class="co">#>    -> changed 4,074 test results (0 to S; 0 to I; 4,074 to R)</span></a></code></pre></div> | ||||
| <a class="sourceLine" id="cb14-43" title="43"><span class="co">#>    -> changed 4,065 test results (0 to S; 0 to I; 4,065 to R)</span></a></code></pre></div> | ||||
| </div> | ||||
| <div id="adding-new-variables" class="section level1"> | ||||
| <h1 class="hasAnchor"> | ||||
| @@ -489,8 +489,8 @@ | ||||
| <a class="sourceLine" id="cb16-3" title="3"><span class="co">#> </span><span class="al">NOTE</span><span class="co">: Using column `bacteria` as input for `col_mo`.</span></a> | ||||
| <a class="sourceLine" id="cb16-4" title="4"><span class="co">#> </span><span class="al">NOTE</span><span class="co">: Using column `date` as input for `col_date`.</span></a> | ||||
| <a class="sourceLine" id="cb16-5" title="5"><span class="co">#> </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></a> | ||||
| <a class="sourceLine" id="cb16-6" title="6"><span class="co">#> => Found 5,680 first isolates (28.4% of total)</span></a></code></pre></div> | ||||
| <p>So only 28.4% is suitable for resistance analysis! We can now filter on it with the <code><a href="https://dplyr.tidyverse.org/reference/filter.html">filter()</a></code> function, also from the <code>dplyr</code> package:</p> | ||||
| <a class="sourceLine" id="cb16-6" title="6"><span class="co">#> => Found 5,667 first isolates (28.3% of total)</span></a></code></pre></div> | ||||
| <p>So only 28.3% is suitable for resistance analysis! We can now filter on it with the <code><a href="https://dplyr.tidyverse.org/reference/filter.html">filter()</a></code> function, also from the <code>dplyr</code> package:</p> | ||||
| <div class="sourceCode" id="cb17"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb17-1" title="1">data_1st <-<span class="st"> </span>data <span class="op">%>%</span><span class="st"> </span></a> | ||||
| <a class="sourceLine" id="cb17-2" title="2"><span class="st">  </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(first <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>)</a></code></pre></div> | ||||
| <p>For future use, the above two syntaxes can be shortened with the <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> function:</p> | ||||
| @@ -516,10 +516,10 @@ | ||||
| <tbody> | ||||
| <tr class="odd"> | ||||
| <td align="center">1</td> | ||||
| <td align="center">2010-01-10</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2010-02-08</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| @@ -527,43 +527,43 @@ | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">2</td> | ||||
| <td align="center">2010-04-18</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2010-04-06</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">I</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">3</td> | ||||
| <td align="center">2010-07-02</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2010-04-25</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">FALSE</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">4</td> | ||||
| <td align="center">2010-09-21</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2010-10-05</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">I</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">5</td> | ||||
| <td align="center">2010-09-22</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2010-11-09</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| @@ -571,59 +571,59 @@ | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">6</td> | ||||
| <td align="center">2010-10-06</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2010-11-23</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">7</td> | ||||
| <td align="center">2010-10-14</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2010-12-26</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">I</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">8</td> | ||||
| <td align="center">2011-01-09</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2011-01-01</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">I</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">9</td> | ||||
| <td align="center">2011-03-31</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2011-01-21</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">I</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">10</td> | ||||
| <td align="center">2011-02-28</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">10</td> | ||||
| <td align="center">2011-03-31</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| </tr> | ||||
| </tbody> | ||||
| </table> | ||||
| <p>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 <code><a href="../reference/key_antibiotics.html">key_antibiotics()</a></code> 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.</p> | ||||
| @@ -637,7 +637,7 @@ | ||||
| <a class="sourceLine" id="cb19-7" title="7"><span class="co">#> </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></a> | ||||
| <a class="sourceLine" id="cb19-8" title="8"><span class="co">#> </span><span class="al">NOTE</span><span class="co">: Using column `keyab` as input for `col_keyantibiotics`. Use col_keyantibiotics  = FALSE to prevent this.</span></a> | ||||
| <a class="sourceLine" id="cb19-9" title="9"><span class="co">#> [Criterion] Inclusion based on key antibiotics, ignoring I.</span></a> | ||||
| <a class="sourceLine" id="cb19-10" title="10"><span class="co">#> => Found 15,854 first weighted isolates (79.3% of total)</span></a></code></pre></div> | ||||
| <a class="sourceLine" id="cb19-10" title="10"><span class="co">#> => Found 15,851 first weighted isolates (79.3% of total)</span></a></code></pre></div> | ||||
| <table class="table"> | ||||
| <thead><tr class="header"> | ||||
| <th align="center">isolate</th> | ||||
| @@ -654,10 +654,10 @@ | ||||
| <tbody> | ||||
| <tr class="odd"> | ||||
| <td align="center">1</td> | ||||
| <td align="center">2010-01-10</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2010-02-08</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| @@ -666,47 +666,47 @@ | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">2</td> | ||||
| <td align="center">2010-04-18</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">I</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| <td align="center">FALSE</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">3</td> | ||||
| <td align="center">2010-07-02</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2010-04-06</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| <td align="center">FALSE</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">4</td> | ||||
| <td align="center">2010-09-21</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">5</td> | ||||
| <td align="center">2010-09-22</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">3</td> | ||||
| <td align="center">2010-04-25</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">FALSE</td> | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">4</td> | ||||
| <td align="center">2010-10-05</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">I</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">FALSE</td> | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">5</td> | ||||
| <td align="center">2010-11-09</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| @@ -714,23 +714,23 @@ | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">6</td> | ||||
| <td align="center">2010-10-06</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2010-11-23</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">7</td> | ||||
| <td align="center">2010-10-14</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2010-12-26</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">I</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| @@ -738,47 +738,47 @@ | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">8</td> | ||||
| <td align="center">2011-01-09</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2011-01-01</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">I</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">9</td> | ||||
| <td align="center">2011-03-31</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">2011-01-21</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">I</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">TRUE</td> | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">10</td> | ||||
| <td align="center">2011-03-31</td> | ||||
| <td align="center">X9</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">FALSE</td> | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">10</td> | ||||
| <td align="center">2011-02-28</td> | ||||
| <td align="center">H1</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">TRUE</td> | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| </tbody> | ||||
| </table> | ||||
| <p>Instead of 2, now 8 isolates are flagged. In total, 79.3% 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.</p> | ||||
| <p>Instead of 2, now 10 isolates are flagged. In total, 79.3% 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.</p> | ||||
| <p>As with <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code>, there’s a shortcut for this new algorithm too:</p> | ||||
| <div class="sourceCode" id="cb20"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb20-1" title="1">data_1st <-<span class="st"> </span>data <span class="op">%>%</span><span class="st"> </span></a> | ||||
| <a class="sourceLine" id="cb20-2" title="2"><span class="st">  </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_weighted_isolate</a></span>()</a></code></pre></div> | ||||
| <p>So we end up with 15,854 isolates for analysis.</p> | ||||
| <p>So we end up with 15,851 isolates for analysis.</p> | ||||
| <p>We can remove unneeded columns:</p> | ||||
| <div class="sourceCode" id="cb21"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb21-1" title="1">data_1st <-<span class="st"> </span>data_1st <span class="op">%>%</span><span class="st"> </span></a> | ||||
| <a class="sourceLine" id="cb21-2" title="2"><span class="st">  </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(<span class="op">-</span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(first, keyab))</a></code></pre></div> | ||||
| @@ -786,7 +786,6 @@ | ||||
| <div class="sourceCode" id="cb22"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb22-1" title="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/utils/topics/head">head</a></span>(data_1st)</a></code></pre></div> | ||||
| <table class="table"> | ||||
| <thead><tr class="header"> | ||||
| <th></th> | ||||
| <th align="center">date</th> | ||||
| <th align="center">patient_id</th> | ||||
| <th align="center">hospital</th> | ||||
| @@ -803,14 +802,13 @@ | ||||
| </tr></thead> | ||||
| <tbody> | ||||
| <tr class="odd"> | ||||
| <td>2</td> | ||||
| <td align="center">2016-11-18</td> | ||||
| <td align="center">I10</td> | ||||
| <td align="center">2011-09-14</td> | ||||
| <td align="center">N3</td> | ||||
| <td align="center">Hospital B</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">M</td> | ||||
| <td align="center">Gram negative</td> | ||||
| @@ -819,10 +817,9 @@ | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td>5</td> | ||||
| <td align="center">2017-01-25</td> | ||||
| <td align="center">H5</td> | ||||
| <td align="center">Hospital C</td> | ||||
| <td align="center">2011-01-09</td> | ||||
| <td align="center">I3</td> | ||||
| <td align="center">Hospital A</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| @@ -835,67 +832,63 @@ | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td>6</td> | ||||
| <td align="center">2017-03-12</td> | ||||
| <td align="center">B9</td> | ||||
| <td align="center">Hospital C</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">2015-06-02</td> | ||||
| <td align="center">E8</td> | ||||
| <td align="center">Hospital A</td> | ||||
| <td align="center">B_STRPT_PNE</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">M</td> | ||||
| <td align="center">Gram negative</td> | ||||
| <td align="center">Escherichia</td> | ||||
| <td align="center">coli</td> | ||||
| <td align="center">Gram positive</td> | ||||
| <td align="center">Streptococcus</td> | ||||
| <td align="center">pneumoniae</td> | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td>7</td> | ||||
| <td align="center">2015-08-12</td> | ||||
| <td align="center">Y4</td> | ||||
| <td align="center">Hospital B</td> | ||||
| <td align="center">B_STPHY_AUR</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">2011-02-06</td> | ||||
| <td align="center">S1</td> | ||||
| <td align="center">Hospital D</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">F</td> | ||||
| <td align="center">Gram positive</td> | ||||
| <td align="center">Staphylococcus</td> | ||||
| <td align="center">aureus</td> | ||||
| <td align="center">Gram negative</td> | ||||
| <td align="center">Escherichia</td> | ||||
| <td align="center">coli</td> | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td>9</td> | ||||
| <td align="center">2016-01-24</td> | ||||
| <td align="center">L10</td> | ||||
| <td align="center">Hospital A</td> | ||||
| <td align="center">2010-01-27</td> | ||||
| <td align="center">N7</td> | ||||
| <td align="center">Hospital C</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">I</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">M</td> | ||||
| <td align="center">F</td> | ||||
| <td align="center">Gram negative</td> | ||||
| <td align="center">Escherichia</td> | ||||
| <td align="center">coli</td> | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td>12</td> | ||||
| <td align="center">2013-09-11</td> | ||||
| <td align="center">H6</td> | ||||
| <td align="center">2017-08-11</td> | ||||
| <td align="center">U3</td> | ||||
| <td align="center">Hospital B</td> | ||||
| <td align="center">B_STPHY_AUR</td> | ||||
| <td align="center">B_ESCHR_COL</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">R</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">M</td> | ||||
| <td align="center">Gram positive</td> | ||||
| <td align="center">Staphylococcus</td> | ||||
| <td align="center">aureus</td> | ||||
| <td align="center">S</td> | ||||
| <td align="center">F</td> | ||||
| <td align="center">Gram negative</td> | ||||
| <td align="center">Escherichia</td> | ||||
| <td align="center">coli</td> | ||||
| <td align="center">TRUE</td> | ||||
| </tr> | ||||
| </tbody> | ||||
| @@ -915,9 +908,9 @@ | ||||
| <div class="sourceCode" id="cb23"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb23-1" title="1"><span class="kw"><a href="../reference/freq.html">freq</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/paste">paste</a></span>(data_1st<span class="op">$</span>genus, data_1st<span class="op">$</span>species))</a></code></pre></div> | ||||
| <p>Or can be used like the <code>dplyr</code> way, which is easier readable:</p> | ||||
| <div class="sourceCode" id="cb24"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb24-1" title="1">data_1st <span class="op">%>%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(genus, species)</a></code></pre></div> | ||||
| <p><strong>Frequency table of <code>genus</code> and <code>species</code> from a <code>data.frame</code> (15,854 x 13)</strong></p> | ||||
| <p><strong>Frequency table of <code>genus</code> and <code>species</code> from a <code>data.frame</code> (15,851 x 13)</strong></p> | ||||
| <p>Columns: 2<br> | ||||
| Length: 15,854 (of which NA: 0 = 0.00%)<br> | ||||
| Length: 15,851 (of which NA: 0 = 0.00%)<br> | ||||
| Unique: 4</p> | ||||
| <p>Shortest: 16<br> | ||||
| Longest: 24</p> | ||||
| @@ -934,33 +927,33 @@ Longest: 24</p> | ||||
| <tr class="odd"> | ||||
| <td align="left">1</td> | ||||
| <td align="left">Escherichia coli</td> | ||||
| <td align="right">7,918</td> | ||||
| <td align="right">49.9%</td> | ||||
| <td align="right">7,918</td> | ||||
| <td align="right">49.9%</td> | ||||
| <td align="right">7,800</td> | ||||
| <td align="right">49.2%</td> | ||||
| <td align="right">7,800</td> | ||||
| <td align="right">49.2%</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="left">2</td> | ||||
| <td align="left">Staphylococcus aureus</td> | ||||
| <td align="right">3,930</td> | ||||
| <td align="right">24.8%</td> | ||||
| <td align="right">11,848</td> | ||||
| <td align="right">74.7%</td> | ||||
| <td align="right">4,008</td> | ||||
| <td align="right">25.3%</td> | ||||
| <td align="right">11,808</td> | ||||
| <td align="right">74.5%</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="left">3</td> | ||||
| <td align="left">Streptococcus pneumoniae</td> | ||||
| <td align="right">2,498</td> | ||||
| <td align="right">15.8%</td> | ||||
| <td align="right">14,346</td> | ||||
| <td align="right">90.5%</td> | ||||
| <td align="right">2,445</td> | ||||
| <td align="right">15.4%</td> | ||||
| <td align="right">14,253</td> | ||||
| <td align="right">89.9%</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="left">4</td> | ||||
| <td align="left">Klebsiella pneumoniae</td> | ||||
| <td align="right">1,508</td> | ||||
| <td align="right">9.5%</td> | ||||
| <td align="right">15,854</td> | ||||
| <td align="right">1,598</td> | ||||
| <td align="right">10.1%</td> | ||||
| <td align="right">15,851</td> | ||||
| <td align="right">100.0%</td> | ||||
| </tr> | ||||
| </tbody> | ||||
| @@ -971,7 +964,7 @@ Longest: 24</p> | ||||
| <a href="#resistance-percentages" class="anchor"></a>Resistance percentages</h2> | ||||
| <p>The functions <code>portion_R</code>, <code>portion_RI</code>, <code>portion_I</code>, <code>portion_IS</code> and <code>portion_S</code> can be used to determine the portion of a specific antimicrobial outcome. They can be used on their own:</p> | ||||
| <div class="sourceCode" id="cb25"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb25-1" title="1">data_1st <span class="op">%>%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_IR</a></span>(amox)</a> | ||||
| <a class="sourceLine" id="cb25-2" title="2"><span class="co">#> [1] 0.4726883</span></a></code></pre></div> | ||||
| <a class="sourceLine" id="cb25-2" title="2"><span class="co">#> [1] 0.4828087</span></a></code></pre></div> | ||||
| <p>Or can be used in conjuction with <code><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by()</a></code> and <code><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise()</a></code>, both from the <code>dplyr</code> package:</p> | ||||
| <div class="sourceCode" id="cb26"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb26-1" title="1">data_1st <span class="op">%>%</span><span class="st"> </span></a> | ||||
| <a class="sourceLine" id="cb26-2" title="2"><span class="st">  </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(hospital) <span class="op">%>%</span><span class="st"> </span></a> | ||||
| @@ -984,19 +977,19 @@ Longest: 24</p> | ||||
| <tbody> | ||||
| <tr class="odd"> | ||||
| <td align="center">Hospital A</td> | ||||
| <td align="center">0.4737395</td> | ||||
| <td align="center">0.4877378</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">Hospital B</td> | ||||
| <td align="center">0.4763709</td> | ||||
| <td align="center">0.4750000</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">Hospital C</td> | ||||
| <td align="center">0.4739257</td> | ||||
| <td align="center">0.4869240</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">Hospital D</td> | ||||
| <td align="center">0.4636854</td> | ||||
| <td align="center">0.4860406</td> | ||||
| </tr> | ||||
| </tbody> | ||||
| </table> | ||||
| @@ -1014,23 +1007,23 @@ Longest: 24</p> | ||||
| <tbody> | ||||
| <tr class="odd"> | ||||
| <td align="center">Hospital A</td> | ||||
| <td align="center">0.4737395</td> | ||||
| <td align="center">4760</td> | ||||
| <td align="center">0.4877378</td> | ||||
| <td align="center">4730</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">Hospital B</td> | ||||
| <td align="center">0.4763709</td> | ||||
| <td align="center">5544</td> | ||||
| <td align="center">0.4750000</td> | ||||
| <td align="center">5560</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">Hospital C</td> | ||||
| <td align="center">0.4739257</td> | ||||
| <td align="center">2397</td> | ||||
| <td align="center">0.4869240</td> | ||||
| <td align="center">2409</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">Hospital D</td> | ||||
| <td align="center">0.4636854</td> | ||||
| <td align="center">3153</td> | ||||
| <td align="center">0.4860406</td> | ||||
| <td align="center">3152</td> | ||||
| </tr> | ||||
| </tbody> | ||||
| </table> | ||||
| @@ -1050,27 +1043,27 @@ Longest: 24</p> | ||||
| <tbody> | ||||
| <tr class="odd"> | ||||
| <td align="center">Escherichia</td> | ||||
| <td align="center">0.7350341</td> | ||||
| <td align="center">0.9051528</td> | ||||
| <td align="center">0.9761303</td> | ||||
| <td align="center">0.7452564</td> | ||||
| <td align="center">0.9002564</td> | ||||
| <td align="center">0.9765385</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">Klebsiella</td> | ||||
| <td align="center">0.7274536</td> | ||||
| <td align="center">0.9177719</td> | ||||
| <td align="center">0.9781167</td> | ||||
| <td align="center">0.7509387</td> | ||||
| <td align="center">0.9030038</td> | ||||
| <td align="center">0.9724656</td> | ||||
| </tr> | ||||
| <tr class="odd"> | ||||
| <td align="center">Staphylococcus</td> | ||||
| <td align="center">0.7432570</td> | ||||
| <td align="center">0.9216285</td> | ||||
| <td align="center">0.9788804</td> | ||||
| <td align="center">0.7262974</td> | ||||
| <td align="center">0.9224052</td> | ||||
| <td align="center">0.9790419</td> | ||||
| </tr> | ||||
| <tr class="even"> | ||||
| <td align="center">Streptococcus</td> | ||||
| <td align="center">0.7273819</td> | ||||
| <td align="center">0.7325153</td> | ||||
| <td align="center">0.0000000</td> | ||||
| <td align="center">0.7273819</td> | ||||
| <td align="center">0.7325153</td> | ||||
| </tr> | ||||
| </tbody> | ||||
| </table> | ||||
|   | ||||
| Before Width: | Height: | Size: 33 KiB After Width: | Height: | Size: 33 KiB | 
| Before Width: | Height: | Size: 21 KiB After Width: | Height: | Size: 21 KiB | 
| Before Width: | Height: | Size: 68 KiB After Width: | Height: | Size: 68 KiB | 
| Before Width: | Height: | Size: 50 KiB After Width: | Height: | Size: 50 KiB | 
| @@ -192,7 +192,7 @@ | ||||
|       <h1>How to apply EUCAST rules</h1> | ||||
|                         <h4 class="author">Matthijs S. Berends</h4> | ||||
|              | ||||
|             <h4 class="date">22 February 2019</h4> | ||||
|             <h4 class="date">23 February 2019</h4> | ||||
|        | ||||
|        | ||||
|       <div class="hidden name"><code>EUCAST.Rmd</code></div> | ||||
|   | ||||
| @@ -192,7 +192,7 @@ | ||||
|       <h1>How to use the <em>G</em>-test</h1> | ||||
|                         <h4 class="author">Matthijs S. Berends</h4> | ||||
|              | ||||
|             <h4 class="date">22 February 2019</h4> | ||||
|             <h4 class="date">23 February 2019</h4> | ||||
|        | ||||
|        | ||||
|       <div class="hidden name"><code>G_test.Rmd</code></div> | ||||
|   | ||||
| @@ -192,7 +192,7 @@ | ||||
|       <h1>How to work with WHONET data</h1> | ||||
|                         <h4 class="author">Matthijs S. Berends</h4> | ||||
|              | ||||
|             <h4 class="date">22 February 2019</h4> | ||||
|             <h4 class="date">23 February 2019</h4> | ||||
|        | ||||
|        | ||||
|       <div class="hidden name"><code>WHONET.Rmd</code></div> | ||||
|   | ||||
| @@ -192,7 +192,7 @@ | ||||
|       <h1>How to get properties of an antibiotic</h1> | ||||
|                         <h4 class="author">Matthijs S. Berends</h4> | ||||
|              | ||||
|             <h4 class="date">22 February 2019</h4> | ||||
|             <h4 class="date">23 February 2019</h4> | ||||
|        | ||||
|        | ||||
|       <div class="hidden name"><code>atc_property.Rmd</code></div> | ||||
|   | ||||
| @@ -192,7 +192,7 @@ | ||||
|       <h1>Benchmarks</h1> | ||||
|                         <h4 class="author">Matthijs S. Berends</h4> | ||||
|              | ||||
|             <h4 class="date">22 February 2019</h4> | ||||
|             <h4 class="date">23 February 2019</h4> | ||||
|        | ||||
|        | ||||
|       <div class="hidden name"><code>benchmarks.Rmd</code></div> | ||||
| @@ -217,14 +217,14 @@ | ||||
| <a class="sourceLine" id="cb2-8" title="8">                           <span class="dt">times =</span> <span class="dv">10</span>)</a> | ||||
| <a class="sourceLine" id="cb2-9" title="9"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(S.aureus, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">3</span>)</a> | ||||
| <a class="sourceLine" id="cb2-10" title="10"><span class="co">#> Unit: milliseconds</span></a> | ||||
| <a class="sourceLine" id="cb2-11" title="11"><span class="co">#>                            expr  min   lq mean median   uq   max neval</span></a> | ||||
| <a class="sourceLine" id="cb2-12" title="12"><span class="co">#>                    as.mo("sau") 42.9 43.2 43.9   44.0 44.2  45.1    10</span></a> | ||||
| <a class="sourceLine" id="cb2-13" title="13"><span class="co">#>                   as.mo("stau") 86.8 87.0 88.9   87.3 88.2 101.0    10</span></a> | ||||
| <a class="sourceLine" id="cb2-14" title="14"><span class="co">#>                 as.mo("staaur") 42.6 43.6 51.5   43.8 44.5  82.8    10</span></a> | ||||
| <a class="sourceLine" id="cb2-15" title="15"><span class="co">#>              as.mo("S. aureus") 23.2 23.3 31.0   23.5 23.6  61.8    10</span></a> | ||||
| <a class="sourceLine" id="cb2-16" title="16"><span class="co">#>             as.mo("S.  aureus") 23.1 23.3 26.4   23.7 24.4  51.2    10</span></a> | ||||
| <a class="sourceLine" id="cb2-17" title="17"><span class="co">#>                 as.mo("STAAUR") 42.8 43.4 44.5   44.3 44.5  47.8    10</span></a> | ||||
| <a class="sourceLine" id="cb2-18" title="18"><span class="co">#>  as.mo("Staphylococcus aureus") 14.3 14.5 20.4   14.8 16.0  64.6    10</span></a></code></pre></div> | ||||
| <a class="sourceLine" id="cb2-11" title="11"><span class="co">#>                            expr  min   lq mean median    uq   max neval</span></a> | ||||
| <a class="sourceLine" id="cb2-12" title="12"><span class="co">#>                    as.mo("sau") 10.4 10.5 10.7   10.6  10.7  11.2    10</span></a> | ||||
| <a class="sourceLine" id="cb2-13" title="13"><span class="co">#>                   as.mo("stau") 84.4 84.7 95.6   85.2 101.0 136.0    10</span></a> | ||||
| <a class="sourceLine" id="cb2-14" title="14"><span class="co">#>                 as.mo("staaur") 10.5 10.6 10.8   10.6  11.1  11.2    10</span></a> | ||||
| <a class="sourceLine" id="cb2-15" title="15"><span class="co">#>              as.mo("S. aureus") 21.3 21.4 31.4   21.9  41.6  60.3    10</span></a> | ||||
| <a class="sourceLine" id="cb2-16" title="16"><span class="co">#>             as.mo("S.  aureus") 21.3 21.4 21.8   21.4  21.5  24.9    10</span></a> | ||||
| <a class="sourceLine" id="cb2-17" title="17"><span class="co">#>                 as.mo("STAAUR") 10.5 10.6 23.5   10.6  43.8  65.0    10</span></a> | ||||
| <a class="sourceLine" id="cb2-18" title="18"><span class="co">#>  as.mo("Staphylococcus aureus") 16.1 16.2 20.7   16.4  17.5  57.7    10</span></a></code></pre></div> | ||||
| <p>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 more an input value resembles a full name, the faster the result will be found.</p> | ||||
| <p>To achieve this speed, the <code>as.mo</code> 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 <em>Mycoplasma leonicaptivi</em> (<code>B_MYCPL_LEO</code>), a bug probably never found before in humans:</p> | ||||
| <div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb3-1" title="1">M.leonicaptivi <-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/microbenchmark/topics/microbenchmark">microbenchmark</a></span>(<span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"myle"</span>),</a> | ||||
| @@ -237,13 +237,13 @@ | ||||
| <a class="sourceLine" id="cb3-8" title="8"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(M.leonicaptivi, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">3</span>)</a> | ||||
| <a class="sourceLine" id="cb3-9" title="9"><span class="co">#> Unit: milliseconds</span></a> | ||||
| <a class="sourceLine" id="cb3-10" title="10"><span class="co">#>                              expr min  lq mean median  uq max neval</span></a> | ||||
| <a class="sourceLine" id="cb3-11" title="11"><span class="co">#>                     as.mo("myle") 141 142  162    142 142 299    10</span></a> | ||||
| <a class="sourceLine" id="cb3-12" title="12"><span class="co">#>                   as.mo("mycleo") 479 481  520    525 530 634    10</span></a> | ||||
| <a class="sourceLine" id="cb3-13" title="13"><span class="co">#>          as.mo("M. leonicaptivi") 241 242  273    263 281 382    10</span></a> | ||||
| <a class="sourceLine" id="cb3-14" title="14"><span class="co">#>         as.mo("M.  leonicaptivi") 239 241  268    282 283 299    10</span></a> | ||||
| <a class="sourceLine" id="cb3-15" title="15"><span class="co">#>                   as.mo("MYCLEO") 487 520  525    524 528 601    10</span></a> | ||||
| <a class="sourceLine" id="cb3-16" title="16"><span class="co">#>  as.mo("Mycoplasma leonicaptivi") 152 156  183    174 200 261    10</span></a></code></pre></div> | ||||
| <p>That takes 7.3 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.</p> | ||||
| <a class="sourceLine" id="cb3-11" title="11"><span class="co">#>                     as.mo("myle") 131 132  132    132 133 133    10</span></a> | ||||
| <a class="sourceLine" id="cb3-12" title="12"><span class="co">#>                   as.mo("mycleo") 439 445  471    481 488 505    10</span></a> | ||||
| <a class="sourceLine" id="cb3-13" title="13"><span class="co">#>          as.mo("M. leonicaptivi") 202 205  234    243 247 262    10</span></a> | ||||
| <a class="sourceLine" id="cb3-14" title="14"><span class="co">#>         as.mo("M.  leonicaptivi") 202 202  221    212 242 249    10</span></a> | ||||
| <a class="sourceLine" id="cb3-15" title="15"><span class="co">#>                   as.mo("MYCLEO") 441 449  469    480 486 493    10</span></a> | ||||
| <a class="sourceLine" id="cb3-16" title="16"><span class="co">#>  as.mo("Mycoplasma leonicaptivi") 143 143  165    165 185 190    10</span></a></code></pre></div> | ||||
| <p>That takes 9.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.</p> | ||||
| <p>In the figure below, we compare <em>Escherichia coli</em> (which is very common) with <em>Prevotella brevis</em> (which is moderately common) and with <em>Mycoplasma leonicaptivi</em> (which is very uncommon):</p> | ||||
| <div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb4-1" title="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/par">par</a></span>(<span class="dt">mar =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="dv">5</span>, <span class="dv">16</span>, <span class="dv">4</span>, <span class="dv">2</span>)) <span class="co"># set more space for left margin text (16)</span></a> | ||||
| <a class="sourceLine" id="cb4-2" title="2"></a> | ||||
| @@ -283,8 +283,8 @@ | ||||
| <a class="sourceLine" id="cb5-18" title="18"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(run_it, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">3</span>)</a> | ||||
| <a class="sourceLine" id="cb5-19" title="19"><span class="co">#> Unit: milliseconds</span></a> | ||||
| <a class="sourceLine" id="cb5-20" title="20"><span class="co">#>            expr min  lq mean median  uq max neval</span></a> | ||||
| <a class="sourceLine" id="cb5-21" title="21"><span class="co">#>  mo_fullname(x) 400 405  463    441 533 558    10</span></a></code></pre></div> | ||||
| <p>So transforming 500,000 values (!) of 95 unique values only takes 0.44 seconds (441 ms). You only lose time on your unique input values.</p> | ||||
| <a class="sourceLine" id="cb5-21" title="21"><span class="co">#>  mo_fullname(x) 618 653  729    695 813 846    10</span></a></code></pre></div> | ||||
| <p>So transforming 500,000 values (!) of 95 unique values only takes 0.69 seconds (694 ms). You only lose time on your unique input values.</p> | ||||
| </div> | ||||
| <div id="precalculated-results" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| @@ -296,10 +296,10 @@ | ||||
| <a class="sourceLine" id="cb6-4" title="4">                         <span class="dt">times =</span> <span class="dv">10</span>)</a> | ||||
| <a class="sourceLine" id="cb6-5" title="5"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(run_it, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">3</span>)</a> | ||||
| <a class="sourceLine" id="cb6-6" title="6"><span class="co">#> Unit: milliseconds</span></a> | ||||
| <a class="sourceLine" id="cb6-7" title="7"><span class="co">#>  expr    min    lq   mean median     uq    max neval</span></a> | ||||
| <a class="sourceLine" id="cb6-8" title="8"><span class="co">#>     A 39.000 39.80 40.000 40.100 40.300 41.100    10</span></a> | ||||
| <a class="sourceLine" id="cb6-9" title="9"><span class="co">#>     B 24.400 24.70 25.000 24.900 25.200 25.600    10</span></a> | ||||
| <a class="sourceLine" id="cb6-10" title="10"><span class="co">#>     C  0.294  0.39  0.422  0.401  0.505  0.535    10</span></a></code></pre></div> | ||||
| <a class="sourceLine" id="cb6-7" title="7"><span class="co">#>  expr    min     lq   mean median     uq    max neval</span></a> | ||||
| <a class="sourceLine" id="cb6-8" title="8"><span class="co">#>     A  6.460  6.560  6.660  6.650  6.720  6.950    10</span></a> | ||||
| <a class="sourceLine" id="cb6-9" title="9"><span class="co">#>     B 22.300 22.400 22.700 22.700 22.900 23.000    10</span></a> | ||||
| <a class="sourceLine" id="cb6-10" title="10"><span class="co">#>     C  0.254  0.263  0.378  0.396  0.413  0.563    10</span></a></code></pre></div> | ||||
| <p>So going from <code><a href="../reference/mo_property.html">mo_fullname("Staphylococcus aureus")</a></code> to <code>"Staphylococcus aureus"</code> takes 0.0004 seconds - it doesn’t even start calculating <em>if the result would be the same as the expected resulting value</em>. That goes for all helper functions:</p> | ||||
| <div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb7-1" title="1">run_it <-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/microbenchmark/topics/microbenchmark">microbenchmark</a></span>(<span class="dt">A =</span> <span class="kw"><a href="../reference/mo_property.html">mo_species</a></span>(<span class="st">"aureus"</span>),</a> | ||||
| <a class="sourceLine" id="cb7-2" title="2">                         <span class="dt">B =</span> <span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(<span class="st">"Staphylococcus"</span>),</a> | ||||
| @@ -313,14 +313,14 @@ | ||||
| <a class="sourceLine" id="cb7-10" title="10"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(run_it, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">3</span>)</a> | ||||
| <a class="sourceLine" id="cb7-11" title="11"><span class="co">#> Unit: milliseconds</span></a> | ||||
| <a class="sourceLine" id="cb7-12" title="12"><span class="co">#>  expr   min    lq  mean median    uq   max neval</span></a> | ||||
| <a class="sourceLine" id="cb7-13" title="13"><span class="co">#>     A 0.298 0.327 0.398  0.400 0.452 0.535    10</span></a> | ||||
| <a class="sourceLine" id="cb7-14" title="14"><span class="co">#>     B 0.251 0.287 0.339  0.344 0.377 0.436    10</span></a> | ||||
| <a class="sourceLine" id="cb7-15" title="15"><span class="co">#>     C 0.293 0.403 0.451  0.487 0.500 0.537    10</span></a> | ||||
| <a class="sourceLine" id="cb7-16" title="16"><span class="co">#>     D 0.250 0.262 0.300  0.277 0.336 0.395    10</span></a> | ||||
| <a class="sourceLine" id="cb7-17" title="17"><span class="co">#>     E 0.249 0.261 0.306  0.313 0.344 0.384    10</span></a> | ||||
| <a class="sourceLine" id="cb7-18" title="18"><span class="co">#>     F 0.273 0.283 0.325  0.326 0.338 0.420    10</span></a> | ||||
| <a class="sourceLine" id="cb7-19" title="19"><span class="co">#>     G 0.238 0.293 0.312  0.325 0.342 0.356    10</span></a> | ||||
| <a class="sourceLine" id="cb7-20" title="20"><span class="co">#>     H 0.250 0.262 0.304  0.316 0.337 0.358    10</span></a></code></pre></div> | ||||
| <a class="sourceLine" id="cb7-13" title="13"><span class="co">#>     A 0.303 0.338 0.414  0.431 0.453 0.550    10</span></a> | ||||
| <a class="sourceLine" id="cb7-14" title="14"><span class="co">#>     B 0.244 0.282 0.339  0.363 0.372 0.395    10</span></a> | ||||
| <a class="sourceLine" id="cb7-15" title="15"><span class="co">#>     C 0.302 0.404 0.437  0.430 0.490 0.527    10</span></a> | ||||
| <a class="sourceLine" id="cb7-16" title="16"><span class="co">#>     D 0.257 0.279 0.315  0.310 0.344 0.378    10</span></a> | ||||
| <a class="sourceLine" id="cb7-17" title="17"><span class="co">#>     E 0.219 0.270 0.306  0.298 0.355 0.377    10</span></a> | ||||
| <a class="sourceLine" id="cb7-18" title="18"><span class="co">#>     F 0.248 0.296 0.312  0.317 0.334 0.349    10</span></a> | ||||
| <a class="sourceLine" id="cb7-19" title="19"><span class="co">#>     G 0.228 0.248 0.287  0.278 0.336 0.367    10</span></a> | ||||
| <a class="sourceLine" id="cb7-20" title="20"><span class="co">#>     H 0.250 0.255 0.312  0.312 0.352 0.398    10</span></a></code></pre></div> | ||||
| <p>Of course, when running <code><a href="../reference/mo_property.html">mo_phylum("Firmicutes")</a></code> the function has zero knowledge about the actual microorganism, namely <em>S. aureus</em>. But since the result would be <code>"Firmicutes"</code> 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.</p> | ||||
| </div> | ||||
| <div id="results-in-other-languages" class="section level3"> | ||||
| @@ -347,13 +347,13 @@ | ||||
| <a class="sourceLine" id="cb8-18" title="18"><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/print">print</a></span>(run_it, <span class="dt">unit =</span> <span class="st">"ms"</span>, <span class="dt">signif =</span> <span class="dv">4</span>)</a> | ||||
| <a class="sourceLine" id="cb8-19" title="19"><span class="co">#> Unit: milliseconds</span></a> | ||||
| <a class="sourceLine" id="cb8-20" title="20"><span class="co">#>  expr   min    lq  mean median    uq   max neval</span></a> | ||||
| <a class="sourceLine" id="cb8-21" title="21"><span class="co">#>    en 10.78 11.11 11.15  11.14 11.30 11.41    10</span></a> | ||||
| <a class="sourceLine" id="cb8-22" title="22"><span class="co">#>    de 19.60 19.65 23.24  19.76 20.61 52.47    10</span></a> | ||||
| <a class="sourceLine" id="cb8-23" title="23"><span class="co">#>    nl 19.14 19.71 19.75  19.72 19.87 20.22    10</span></a> | ||||
| <a class="sourceLine" id="cb8-24" title="24"><span class="co">#>    es 19.64 19.73 28.36  20.60 25.91 64.67    10</span></a> | ||||
| <a class="sourceLine" id="cb8-25" title="25"><span class="co">#>    it 19.33 19.49 23.13  19.68 19.97 52.72    10</span></a> | ||||
| <a class="sourceLine" id="cb8-26" title="26"><span class="co">#>    fr 19.43 19.54 20.08  19.72 20.60 21.46    10</span></a> | ||||
| <a class="sourceLine" id="cb8-27" title="27"><span class="co">#>    pt 19.34 19.66 23.15  19.80 20.48 52.40    10</span></a></code></pre></div> | ||||
| <a class="sourceLine" id="cb8-21" title="21"><span class="co">#>    en 12.45 12.60 15.94  12.66 12.69 45.75    10</span></a> | ||||
| <a class="sourceLine" id="cb8-22" title="22"><span class="co">#>    de 20.73 20.87 24.50  21.13 21.29 54.54    10</span></a> | ||||
| <a class="sourceLine" id="cb8-23" title="23"><span class="co">#>    nl 21.02 21.14 24.63  21.22 21.44 54.44    10</span></a> | ||||
| <a class="sourceLine" id="cb8-24" title="24"><span class="co">#>    es 20.56 21.15 21.46  21.21 22.02 22.39    10</span></a> | ||||
| <a class="sourceLine" id="cb8-25" title="25"><span class="co">#>    it 20.54 20.80 21.08  20.93 21.19 22.15    10</span></a> | ||||
| <a class="sourceLine" id="cb8-26" title="26"><span class="co">#>    fr 20.86 21.11 24.55  21.21 21.45 54.12    10</span></a> | ||||
| <a class="sourceLine" id="cb8-27" title="27"><span class="co">#>    pt 20.74 20.93 28.96  21.17 21.60 66.52    10</span></a></code></pre></div> | ||||
| <p>Currently supported are German, Dutch, Spanish, Italian, French and Portuguese.</p> | ||||
| </div> | ||||
|   </div> | ||||
|   | ||||
| Before Width: | Height: | Size: 29 KiB After Width: | Height: | Size: 28 KiB | 
| @@ -192,7 +192,7 @@ | ||||
|       <h1>How to create frequency tables</h1> | ||||
|                         <h4 class="author">Matthijs S. Berends</h4> | ||||
|              | ||||
|             <h4 class="date">22 February 2019</h4> | ||||
|             <h4 class="date">23 February 2019</h4> | ||||
|        | ||||
|        | ||||
|       <div class="hidden name"><code>freq.Rmd</code></div> | ||||
|   | ||||
| @@ -192,7 +192,7 @@ | ||||
|       <h1>How to get properties of a microorganism</h1> | ||||
|                         <h4 class="author">Matthijs S. Berends</h4> | ||||
|              | ||||
|             <h4 class="date">22 February 2019</h4> | ||||
|             <h4 class="date">23 February 2019</h4> | ||||
|        | ||||
|        | ||||
|       <div class="hidden name"><code>mo_property.Rmd</code></div> | ||||
|   | ||||
| @@ -192,7 +192,7 @@ | ||||
|       <h1>How to predict antimicrobial resistance</h1> | ||||
|                         <h4 class="author">Matthijs S. Berends</h4> | ||||
|              | ||||
|             <h4 class="date">22 February 2019</h4> | ||||
|             <h4 class="date">23 February 2019</h4> | ||||
|        | ||||
|        | ||||
|       <div class="hidden name"><code>resistance_predict.Rmd</code></div> | ||||
|   | ||||
| @@ -323,7 +323,6 @@ When using <code>allow_uncertain = TRUE</code> (which is the default setting), i | ||||
|     <p>Examples:</p><ul> | ||||
| <li><p><code>"Streptococcus group B (known as S. agalactiae)"</code>. The text between brackets will be removed and a warning will be thrown that the result <em>Streptococcus group B</em> (<code>B_STRPT_GRB</code>) needs review.</p></li> | ||||
| <li><p><code>"S. aureus - please mind: MRSA"</code>. The last word will be stripped, after which the function will try to find a match. If it does not, the second last word will be stripped, etc. Again, a warning will be thrown that the result <em>Staphylococcus aureus</em> (<code>B_STPHY_AUR</code>) needs review.</p></li> | ||||
| <li><p><code>"D. spartina"</code>. This is the abbreviation of an old taxonomic name: <em>Didymosphaeria spartinae</em> (the last "e" was missing from the input). This fungus was renamed to <em>Leptosphaeria obiones</em>, so a warning will be thrown that this result (<code>F_LPTSP_OBI</code>) needs review.</p></li> | ||||
| <li><p><code>"Fluoroquinolone-resistant Neisseria gonorrhoeae"</code>. The first word will be stripped, after which the function will try to find a match. A warning will be thrown that the result <em>Neisseria gonorrhoeae</em> (<code>B_NESSR_GON</code>) needs review.</p></li> | ||||
| </ul> | ||||
|     <p>Use <code>mo_failures()</code> to get a vector with all values that could not be coerced to a valid value.</p> | ||||
|   | ||||
| @@ -91,7 +91,6 @@ Examples: | ||||
| \itemize{ | ||||
|   \item{\code{"Streptococcus group B (known as S. agalactiae)"}. The text between brackets will be removed and a warning will be thrown that the result \emph{Streptococcus group B} (\code{B_STRPT_GRB}) needs review.} | ||||
|   \item{\code{"S. aureus - please mind: MRSA"}. The last word will be stripped, after which the function will try to find a match. If it does not, the second last word will be stripped, etc. Again, a warning will be thrown that the result \emph{Staphylococcus aureus} (\code{B_STPHY_AUR}) needs review.} | ||||
|   \item{\code{"D. spartina"}. This is the abbreviation of an old taxonomic name: \emph{Didymosphaeria spartinae} (the last "e" was missing from the input). This fungus was renamed to \emph{Leptosphaeria obiones}, so a warning will be thrown that this result (\code{F_LPTSP_OBI}) needs review.} | ||||
|   \item{\code{"Fluoroquinolone-resistant Neisseria gonorrhoeae"}. The first word will be stripped, after which the function will try to find a match. A warning will be thrown that the result \emph{Neisseria gonorrhoeae} (\code{B_NESSR_GON}) needs review.} | ||||
| } | ||||
|  | ||||
|   | ||||