1
0
mirror of https://github.com/msberends/AMR.git synced 2025-10-26 19:36:21 +01:00

fix for antibiograms on R < 3.5

This commit is contained in:
2023-02-24 09:43:10 +01:00
parent e70f2cd32c
commit 049baf0a71
13 changed files with 108 additions and 101 deletions

View File

@@ -1,6 +1,6 @@
Package: AMR
Version: 1.8.2.9142
Date: 2023-02-23
Version: 1.8.2.9143
Date: 2023-02-24
Title: Antimicrobial Resistance Data Analysis
Description: Functions to simplify and standardise antimicrobial resistance (AMR)
data analysis and to work with microbial and antimicrobial properties by

View File

@@ -1,4 +1,4 @@
# AMR 1.8.2.9142
# AMR 1.8.2.9143
*(this beta version will eventually become v2.0! We're happy to reach a new major milestone soon!)*

View File

@@ -988,7 +988,7 @@ pm_summarise.default <- function(.data, ...) {
if (is.list(x_res)) I(x_res) else x_res
}
)
res <- as.data.frame(res)
res <- as.data.frame(res, stringsAsFactors = FALSE)
fn_names <- names(fns)
colnames(res) <- if (is.null(fn_names)) fns else fn_names
if (pm_groups_exist) res <- cbind(group, res, row.names = NULL)

View File

@@ -49,7 +49,11 @@
#' @details This function returns a table with values between 0 and 100 for *susceptibility*, not resistance.
#'
#' **Remember that you should filter your data to let it contain only first isolates!** This is needed to exclude duplicates and to reduce selection bias. Use [first_isolate()] to determine them in your data set with one of the four available algorithms.
#'
#' All types of antibiograms as listed below can be plotted (using [ggplot2::autoplot()] or base \R [plot()]/[barplot()]). The `antibiogram` object can also be used directly in R Markdown / Quarto (i.e., `knitr`) for reports. In this case, [knitr::kable()] will be applied automatically and microorganism names will even be printed in italics at default (see argument `italicise`). You can also use functions from specific 'table reporting' packages to transform the output of [antibiogram()] to your needs, e.g. with [`as_flextable()`][flextable::as_flextable()] or [`gt()`][gt::gt()].
#'
#' ### Antibiogram Types
#'
#' There are four antibiogram types, as proposed by Klinker *et al.* (2021, \doi{10.1177/20499361211011373}), and they are all supported by [antibiogram()]:
#'
#' 1. **Traditional Antibiogram**
@@ -103,8 +107,6 @@
#' "Study Group", "Control Group"))
#' ```
#'
#' All types of antibiograms can be generated with the functions as described on this page, and can be plotted (using [ggplot2::autoplot()] or base \R [plot()]/[barplot()]) or directly used into R Markdown / Quarto formats for reports (in the last case, [knitr::kable()] will be applied automatically). Use functions from specific 'table reporting' packages to transform the output of [antibiogram()] to your needs, e.g. `flextable::as_flextable()` or `gt::gt()`.
#'
#' Note that for combination antibiograms, it is important to realise that susceptibility can be calculated in two ways, which can be set with the `only_all_tested` argument (default is `FALSE`). See this example for two antibiotics, Drug A and Drug B, about how [antibiogram()] works to calculate the %SI:
#'
#' ```
@@ -125,6 +127,7 @@
#' <NA> <NA> - - - -
#' --------------------------------------------------------------------
#' ```
#'
#' @source
#' * Klinker KP *et al.* (2021). **Antimicrobial stewardship and antibiograms: importance of moving beyond traditional antibiograms**. *Therapeutic Advances in Infectious Disease*, May 5;8:20499361211011373; \doi{10.1177/20499361211011373}
#' * Barbieri E *et al.* (2021). **Development of a Weighted-Incidence Syndromic Combination Antibiogram (WISCA) to guide the choice of the empiric antibiotic treatment for urinary tract infection in paediatric patients: a Bayesian approach** *Antimicrobial Resistance & Infection Control* May 1;10(1):74; \doi{10.1186/s13756-021-00939-2}
@@ -208,6 +211,7 @@
#' "WISCA Group 1", "WISCA Group 2"
#' )
#' )
#'
#'
#' # Print the output for R Markdown / Quarto -----------------------------
#'
@@ -504,6 +508,7 @@ antibiogram <- function(x,
out <- as_original_data_class(new_df, class(x), extra_class = "antibiogram")
rownames(out) <- NULL
structure(out,
has_syndromic_group = has_syndromic_group,
long = long,
combine_SI = combine_SI
)
@@ -578,39 +583,25 @@ autoplot.antibiogram <- function(object, ...) {
}
# will be exported in zzz.R
#' @param italicise a [logical] to indicate whether the microorganism names in the [knitr][knitr::kable()] table should be made italic, using [italicise_taxonomy()]. This only works when the output format is markdown, such as in HTML output.
#' @method knit_print antibiogram
#' @param italicise a [logical] to indicate whether the microorganism names in the [knitr][knitr::kable()] table should be made italic, using [italicise_taxonomy()].
#' @param na character to use for showing `NA` values
#' @rdname antibiogram
knit_print.antibiogram <- function(x, italicise = TRUE, na = getOption("knitr.kable.NA", default = ""), ...) {
stop_ifnot_installed("knitr")
meet_criteria(italicise, allow_class = "logical", has_length = 1)
meet_criteria(na, allow_class = "character", has_length = 1, allow_NA = TRUE)
if (isTRUE(italicise)) {
# make all microorganism names italic, according to nomenclature
names_col <- ifelse(isTRUE(attributes(x)$has_syndromic_group), 2, 1)
x[[names_col]] <- italicise_taxonomy(x[[names_col]], type = "markdown")
}
old_option <- getOption("knitr.kable.NA")
options(knitr.kable.NA = na)
on.exit(options(knitr.kable.NA = old_option))
out <- knitr::kable(x, ..., output = FALSE)
format <- attributes(out)$format
if (isTRUE(italicise) &&
!is.null(format) &&
format %in% c("markdown", "pipe")) {
# try to italicise the output
rows_with_txt <- which(out %like% "[a-z]")
rows_without_txt <- setdiff(seq_len(length(out)), rows_with_txt)
out[rows_with_txt] <- gsub("^[|]", "| ", out[rows_with_txt])
# put hyphen directly after second character
out[rows_without_txt] <- gsub("^[|](.)", "|\\1-", out[rows_without_txt])
out_ita <- italicise_taxonomy(as.character(out), type = "markdown")
if (length(unique(nchar(out_ita))) != 1) {
# so there has been alterations done by italicise_taxonomy()
to_fill <- which(nchar(out_ita) < max(nchar(out_ita)))
out_ita[intersect(to_fill, rows_with_txt)] <- gsub("(^[|].*?)([|])(.*)", "\\1 \\2\\3", out_ita[intersect(to_fill, rows_with_txt)], perl = TRUE)
out_ita[intersect(to_fill, rows_without_txt)] <- gsub("(^[|].*?)([|])(.*)", "\\1--\\2\\3", out_ita[intersect(to_fill, rows_without_txt)], perl = TRUE)
}
attributes(out_ita) <- attributes(out)
out <- out_ita
}
res <- paste(c("", "", out), collapse = "\n")
knitr::asis_output(res)
out <- paste(c("", "", knitr::kable(x, ..., output = FALSE)), collapse = "\n")
knitr::asis_output(out)
}

View File

@@ -39,7 +39,7 @@
#' @param ... arguments passed on to `FUN`
#' @inheritParams sir_df
#' @inheritParams base::formatC
#' @details The function [format()] calculates the resistance per bug-drug combination. Use `combine_SI = TRUE` (default) to test R vs. S+I and `combine_SI = FALSE` to test R+I vs. S.
#' @details The function [format()] calculates the resistance per bug-drug combination and returns a table ready for reporting/publishing. Use `combine_SI = TRUE` (default) to test R vs. S+I and `combine_SI = FALSE` to test R+I vs. S. This table can also directly be used in R Markdown / Quarto without the need for e.g. [knitr::kable()].
#' @export
#' @rdname bug_drug_combinations
#' @return The function [bug_drug_combinations()] returns a [data.frame] with columns "mo", "ab", "S", "I", "R" and "total".
@@ -327,7 +327,15 @@ format.bug_drug_combinations <- function(x,
}
rownames(y) <- NULL
as_original_data_class(y, class(x.bak)) # will remove tibble groups
as_original_data_class(y, class(x.bak), extra_class = "formatted_bug_drug_combinations") # will remove tibble groups
}
# will be exported in zzz.R
knit_print.formatted_bug_drug_combinations <- function(x, ...) {
stop_ifnot_installed("knitr")
# make columns with MO names italic according to nomenclature
colnames(x)[3:NCOL(x)] <- italicise_taxonomy(colnames(x)[3:NCOL(x)], type = "markdown")
knitr::asis_output(paste("", "", knitr::kable(x, ...), collapse = "\n"))
}
#' @method print bug_drug_combinations

Binary file not shown.

View File

@@ -128,8 +128,9 @@ if (utf8_supported && !is_latex) {
s3_register("ggplot2::fortify", "sir")
s3_register("ggplot2::fortify", "mic")
s3_register("ggplot2::fortify", "disk")
# Support for knitr / R Markdown
# Support for knitr (R Markdown/Quarto)
s3_register("knitr::knit_print", "antibiogram")
s3_register("knitr::knit_print", "formatted_bug_drug_combinations")
# Support vctrs package for use in e.g. dplyr verbs
# S3: ab_selector
s3_register("vctrs::vec_ptype2", "character.ab_selector")

View File

@@ -2,7 +2,7 @@
title: "Generating antibiograms with the AMR package"
author: "AMR package developers"
date: "`r Sys.Date()`"
output: html_document
output: pdf_document
---
```{r setup, include=FALSE}

View File

@@ -11,7 +11,7 @@
<meta name="author" content="AMR package developers" />
<meta name="date" content="2023-02-23" />
<meta name="date" content="2023-02-24" />
<title>Generating antibiograms with the AMR package</title>
@@ -299,23 +299,17 @@ overflow-y: auto;
border: 1px solid #ddd;
border-radius: 4px;
}
.tabset-dropdown > .nav-tabs > li.active:before {
content: "";
.tabset-dropdown > .nav-tabs > li.active:before, .tabset-dropdown > .nav-tabs.nav-tabs-open:before {
content: "\e259";
font-family: 'Glyphicons Halflings';
display: inline-block;
padding: 10px;
border-right: 1px solid #ddd;
}
.tabset-dropdown > .nav-tabs.nav-tabs-open > li.active:before {
content: "";
border: none;
}
.tabset-dropdown > .nav-tabs.nav-tabs-open:before {
content: "";
content: "\e258";
font-family: 'Glyphicons Halflings';
display: inline-block;
padding: 10px;
border-right: 1px solid #ddd;
border: none;
}
.tabset-dropdown > .nav-tabs > li.active {
display: block;
@@ -359,7 +353,7 @@ display: none;
<h1 class="title toc-ignore">Generating antibiograms with the AMR
package</h1>
<h4 class="author">AMR package developers</h4>
<h4 class="date">2023-02-23</h4>
<h4 class="date">2023-02-24</h4>
</div>
@@ -370,26 +364,25 @@ package</h1>
looks like:</p>
<pre class="r"><code>example_isolates</code></pre>
<pre><code>## # A tibble: 2,000 × 46
## date patient age gender ward mo PEN
## &lt;date&gt; &lt;chr&gt; &lt;dbl&gt; &lt;chr&gt; &lt;chr&gt; &lt;mo&gt; &lt;sir&gt;
## 1 2002-01-02 A77334 65 F Clini B_ESCHR_COLI R
## 2 2002-01-03 A77334 65 F Clini B_ESCHR_COLI R
## 3 2002-01-07 067927 45 F ICU B_STPHY_EPDR R
## 4 2002-01-07 067927 45 F ICU B_STPHY_EPDR R
## 5 2002-01-13 067927 45 F ICU B_STPHY_EPDR R
## 6 2002-01-13 067927 45 F ICU B_STPHY_EPDR R
## 7 2002-01-14 462729 78 M Clini B_STPHY_AURS R
## 8 2002-01-14 462729 78 M Clini B_STPHY_AURS R
## 9 2002-01-16 067927 45 F ICU B_STPHY_EPDR R
## 10 2002-01-17 858515 79 F ICU B_STPHY_EPDR R
## # … with 1,990 more rows, and 39 more variables: OXA &lt;sir&gt;,
## # FLC &lt;sir&gt;, AMX &lt;sir&gt;, AMC &lt;sir&gt;, AMP &lt;sir&gt;, TZP &lt;sir&gt;,
## # CZO &lt;sir&gt;, FEP &lt;sir&gt;, CXM &lt;sir&gt;, FOX &lt;sir&gt;, CTX &lt;sir&gt;,
## # CAZ &lt;sir&gt;, CRO &lt;sir&gt;, GEN &lt;sir&gt;, TOB &lt;sir&gt;, AMK &lt;sir&gt;,
## # KAN &lt;sir&gt;, TMP &lt;sir&gt;, SXT &lt;sir&gt;, NIT &lt;sir&gt;, FOS &lt;sir&gt;,
## # LNZ &lt;sir&gt;, CIP &lt;sir&gt;, MFX &lt;sir&gt;, VAN &lt;sir&gt;, TEC &lt;sir&gt;,
## # TCY &lt;sir&gt;, TGC &lt;sir&gt;, DOX &lt;sir&gt;, ERY &lt;sir&gt;, …
## # Use `print(n = ...)` to see more rows, and `colnames()` to see all variable names</code></pre>
## date patient age gender ward mo PEN OXA FLC AMX
## &lt;date&gt; &lt;chr&gt; &lt;dbl&gt; &lt;chr&gt; &lt;chr&gt; &lt;mo&gt; &lt;sir&gt; &lt;sir&gt; &lt;sir&gt; &lt;sir&gt;
## 1 2002-01-02 A77334 65 F Clinical B_ESCHR_COLI R NA NA NA
## 2 2002-01-03 A77334 65 F Clinical B_ESCHR_COLI R NA NA NA
## 3 2002-01-07 067927 45 F ICU B_STPHY_EPDR R NA R NA
## 4 2002-01-07 067927 45 F ICU B_STPHY_EPDR R NA R NA
## 5 2002-01-13 067927 45 F ICU B_STPHY_EPDR R NA R NA
## 6 2002-01-13 067927 45 F ICU B_STPHY_EPDR R NA R NA
## 7 2002-01-14 462729 78 M Clinical B_STPHY_AURS R NA S R
## 8 2002-01-14 462729 78 M Clinical B_STPHY_AURS R NA S R
## 9 2002-01-16 067927 45 F ICU B_STPHY_EPDR R NA R NA
## 10 2002-01-17 858515 79 F ICU B_STPHY_EPDR R NA S NA
## # … with 1,990 more rows, and 36 more variables: AMC &lt;sir&gt;, AMP &lt;sir&gt;,
## # TZP &lt;sir&gt;, CZO &lt;sir&gt;, FEP &lt;sir&gt;, CXM &lt;sir&gt;, FOX &lt;sir&gt;, CTX &lt;sir&gt;,
## # CAZ &lt;sir&gt;, CRO &lt;sir&gt;, GEN &lt;sir&gt;, TOB &lt;sir&gt;, AMK &lt;sir&gt;, KAN &lt;sir&gt;,
## # TMP &lt;sir&gt;, SXT &lt;sir&gt;, NIT &lt;sir&gt;, FOS &lt;sir&gt;, LNZ &lt;sir&gt;, CIP &lt;sir&gt;,
## # MFX &lt;sir&gt;, VAN &lt;sir&gt;, TEC &lt;sir&gt;, TCY &lt;sir&gt;, TGC &lt;sir&gt;, DOX &lt;sir&gt;,
## # ERY &lt;sir&gt;, CLI &lt;sir&gt;, AZM &lt;sir&gt;, IPM &lt;sir&gt;, MEM &lt;sir&gt;, MTR &lt;sir&gt;,
## # CHL &lt;sir&gt;, COL &lt;sir&gt;, MUP &lt;sir&gt;, RIF &lt;sir&gt;</code></pre>
<div id="traditional-antibiogram" class="section level3">
<h3>Traditional Antibiogram</h3>
<pre class="r"><code>antibiogram(example_isolates,
@@ -397,7 +390,7 @@ looks like:</p>
<table>
<thead>
<tr class="header">
<th align="left">Pathogeen (N min-max)</th>
<th align="left">Pathogen (N min-max)</th>
<th align="right">AMK</th>
<th align="right">GEN</th>
<th align="right">IPM</th>
@@ -408,7 +401,7 @@ looks like:</p>
</thead>
<tbody>
<tr class="odd">
<td align="left">CNS (43-309)</td>
<td align="left">CoNS (43-309)</td>
<td align="right">0</td>
<td align="right">86</td>
<td align="right">52</td>
@@ -507,7 +500,7 @@ looks like:</p>
<table>
<thead>
<tr class="header">
<th align="left">Pathogeen (N min-max)</th>
<th align="left">Pathogen (N min-max)</th>
<th align="right">TZP</th>
<th align="right">TZP + GEN</th>
<th align="right">TZP + TOB</th>
@@ -515,7 +508,7 @@ looks like:</p>
</thead>
<tbody>
<tr class="odd">
<td align="left">CNS (29-274)</td>
<td align="left">CoNS (29-274)</td>
<td align="right">30</td>
<td align="right">97</td>
<td align="right"></td>
@@ -577,10 +570,20 @@ looks like:</p>
antibiotics = c(aminoglycosides(), carbapenems()),
syndromic_group = &quot;ward&quot;)</code></pre>
<table>
<colgroup>
<col width="25%" />
<col width="37%" />
<col width="6%" />
<col width="6%" />
<col width="6%" />
<col width="6%" />
<col width="6%" />
<col width="6%" />
</colgroup>
<thead>
<tr class="header">
<th align="left">Syndroomgroep</th>
<th align="left">Pathogeen (N min-max)</th>
<th align="left">Syndromic Group</th>
<th align="left">Pathogen (N min-max)</th>
<th align="right">AMK</th>
<th align="right">GEN</th>
<th align="right">IPM</th>
@@ -592,7 +595,7 @@ looks like:</p>
<tbody>
<tr class="odd">
<td align="left">Clinical</td>
<td align="left">CNS (23-205)</td>
<td align="left">CoNS (23-205)</td>
<td align="right"></td>
<td align="right">89</td>
<td align="right">57</td>
@@ -602,7 +605,7 @@ looks like:</p>
</tr>
<tr class="even">
<td align="left">ICU</td>
<td align="left">CNS (10-73)</td>
<td align="left">CoNS (10-73)</td>
<td align="right"></td>
<td align="right">79</td>
<td align="right"></td>
@@ -612,7 +615,7 @@ looks like:</p>
</tr>
<tr class="odd">
<td align="left">Outpatient</td>
<td align="left">CNS (3-31)</td>
<td align="left">CoNS (3-31)</td>
<td align="right"></td>
<td align="right">84</td>
<td align="right"></td>
@@ -622,7 +625,7 @@ looks like:</p>
</tr>
<tr class="even">
<td align="left">Clinical</td>
<td align="left">E. <em>coli</em> (0-299)</td>
<td align="left"><em>E. coli</em> (0-299)</td>
<td align="right">100</td>
<td align="right">98</td>
<td align="right">100</td>
@@ -632,7 +635,7 @@ looks like:</p>
</tr>
<tr class="odd">
<td align="left">ICU</td>
<td align="left">E. <em>coli</em> (0-137)</td>
<td align="left"><em>E. coli</em> (0-137)</td>
<td align="right">100</td>
<td align="right">99</td>
<td align="right">100</td>
@@ -642,7 +645,7 @@ looks like:</p>
</tr>
<tr class="even">
<td align="left">Clinical</td>
<td align="left">K. <em>pneumoniae</em> (0-51)</td>
<td align="left"><em>K. pneumoniae</em> (0-51)</td>
<td align="right"></td>
<td align="right">92</td>
<td align="right">100</td>
@@ -652,7 +655,7 @@ looks like:</p>
</tr>
<tr class="odd">
<td align="left">Clinical</td>
<td align="left">P. <em>mirabilis</em> (0-30)</td>
<td align="left"><em>P. mirabilis</em> (0-30)</td>
<td align="right"></td>
<td align="right">100</td>
<td align="right"></td>
@@ -662,7 +665,7 @@ looks like:</p>
</tr>
<tr class="even">
<td align="left">Clinical</td>
<td align="left">S. <em>aureus</em> (2-150)</td>
<td align="left"><em>S. aureus</em> (2-150)</td>
<td align="right"></td>
<td align="right">99</td>
<td align="right"></td>
@@ -672,7 +675,7 @@ looks like:</p>
</tr>
<tr class="odd">
<td align="left">ICU</td>
<td align="left">S. <em>aureus</em> (0-66)</td>
<td align="left"><em>S. aureus</em> (0-66)</td>
<td align="right"></td>
<td align="right">100</td>
<td align="right"></td>
@@ -682,7 +685,7 @@ looks like:</p>
</tr>
<tr class="even">
<td align="left">Clinical</td>
<td align="left">S. <em>epidermidis</em> (4-79)</td>
<td align="left"><em>S. epidermidis</em> (4-79)</td>
<td align="right"></td>
<td align="right">82</td>
<td align="right"></td>
@@ -692,7 +695,7 @@ looks like:</p>
</tr>
<tr class="odd">
<td align="left">ICU</td>
<td align="left">S. <em>epidermidis</em> (4-75)</td>
<td align="left"><em>S. epidermidis</em> (4-75)</td>
<td align="right"></td>
<td align="right">72</td>
<td align="right"></td>
@@ -702,7 +705,7 @@ looks like:</p>
</tr>
<tr class="even">
<td align="left">Clinical</td>
<td align="left">S. <em>hominis</em> (1-45)</td>
<td align="left"><em>S. hominis</em> (1-45)</td>
<td align="right"></td>
<td align="right">96</td>
<td align="right"></td>
@@ -712,7 +715,7 @@ looks like:</p>
</tr>
<tr class="odd">
<td align="left">Clinical</td>
<td align="left">S. <em>pneumoniae</em> (5-78)</td>
<td align="left"><em>S. pneumoniae</em> (5-78)</td>
<td align="right">0</td>
<td align="right">0</td>
<td align="right"></td>
@@ -722,7 +725,7 @@ looks like:</p>
</tr>
<tr class="even">
<td align="left">ICU</td>
<td align="left">S. <em>pneumoniae</em> (5-30)</td>
<td align="left"><em>S. pneumoniae</em> (5-30)</td>
<td align="right">0</td>
<td align="right">0</td>
<td align="right"></td>
@@ -742,9 +745,9 @@ looks like:</p>
syndromic_group = ifelse(example_isolates$age &gt;= 65 &amp;
example_isolates$gender == &quot;M&quot;,
&quot;WISCA Group 1&quot;, &quot;WISCA Group 2&quot;))</code></pre>
<table style="width:100%;">
<table>
<colgroup>
<col width="22%" />
<col width="23%" />
<col width="35%" />
<col width="5%" />
<col width="14%" />
@@ -753,8 +756,8 @@ looks like:</p>
</colgroup>
<thead>
<tr class="header">
<th align="left">Syndroomgroep</th>
<th align="left">Pathogeen (N min-max)</th>
<th align="left">Syndromic Group</th>
<th align="left">Pathogen (N min-max)</th>
<th align="right">AMC</th>
<th align="right">AMC + CIP</th>
<th align="right">TZP</th>
@@ -764,7 +767,7 @@ looks like:</p>
<tbody>
<tr class="odd">
<td align="left">WISCA Group 1</td>
<td align="left">Gram-negatief (261-285)</td>
<td align="left">Gram-negative (261-285)</td>
<td align="right">76</td>
<td align="right">95</td>
<td align="right">89</td>
@@ -772,7 +775,7 @@ looks like:</p>
</tr>
<tr class="even">
<td align="left">WISCA Group 2</td>
<td align="left">Gram-negatief (380-442)</td>
<td align="left">Gram-negative (380-442)</td>
<td align="right">76</td>
<td align="right">98</td>
<td align="right">88</td>
@@ -780,7 +783,7 @@ looks like:</p>
</tr>
<tr class="odd">
<td align="left">WISCA Group 1</td>
<td align="left">Gram-positief (123-406)</td>
<td align="left">Gram-positive (123-406)</td>
<td align="right">76</td>
<td align="right">89</td>
<td align="right">81</td>
@@ -788,7 +791,7 @@ looks like:</p>
</tr>
<tr class="even">
<td align="left">WISCA Group 2</td>
<td align="left">Gram-positief (222-732)</td>
<td align="left">Gram-positive (222-732)</td>
<td align="right">76</td>
<td align="right">89</td>
<td align="right">88</td>

BIN
data-raw/antibiograms.pdf Normal file

Binary file not shown.

View File

@@ -107,3 +107,4 @@ contents <- c(
writeLines(contents, "R/aa_helper_pm_functions.R")
# note: pm_left_join() will be overwritten by aaa_helper_functions.R, which contains a faster implementation
# replace `res <- as.data.frame(res)` with `res <- as.data.frame(res, stringsAsFactors = FALSE)`

View File

@@ -35,7 +35,7 @@ antibiogram(
\method{autoplot}{antibiogram}(object, ...)
knit_print.antibiogram(
\method{knit_print}{antibiogram}(
x,
italicise = TRUE,
na = getOption("knitr.kable.NA", default = ""),
@@ -75,7 +75,7 @@ knit_print.antibiogram(
\item{object}{an \code{\link[=antibiogram]{antibiogram()}} object}
\item{italicise}{a \link{logical} to indicate whether the microorganism names in the \link[knitr:kable]{knitr} table should be made italic, using \code{\link[=italicise_taxonomy]{italicise_taxonomy()}}. This only works when the output format is markdown, such as in HTML output.}
\item{italicise}{a \link{logical} to indicate whether the microorganism names in the \link[knitr:kable]{knitr} table should be made italic, using \code{\link[=italicise_taxonomy]{italicise_taxonomy()}}.}
\item{na}{character to use for showing \code{NA} values}
}
@@ -87,6 +87,9 @@ This function returns a table with values between 0 and 100 for \emph{susceptibi
\strong{Remember that you should filter your data to let it contain only first isolates!} This is needed to exclude duplicates and to reduce selection bias. Use \code{\link[=first_isolate]{first_isolate()}} to determine them in your data set with one of the four available algorithms.
All types of antibiograms as listed below can be plotted (using \code{\link[ggplot2:autoplot]{ggplot2::autoplot()}} or base \R \code{\link[=plot]{plot()}}/\code{\link[=barplot]{barplot()}}). The \code{antibiogram} object can also be used directly in R Markdown / Quarto (i.e., \code{knitr}) for reports. In this case, \code{\link[knitr:kable]{knitr::kable()}} will be applied automatically and microorganism names will even be printed in italics at default (see argument \code{italicise}). You can also use functions from specific 'table reporting' packages to transform the output of \code{\link[=antibiogram]{antibiogram()}} to your needs, e.g. with \code{\link[flextable:as_flextable]{as_flextable()}} or \code{\link[gt:gt]{gt()}}.
\subsection{Antibiogram Types}{
There are four antibiogram types, as proposed by Klinker \emph{et al.} (2021, \doi{10.1177/20499361211011373}), and they are all supported by \code{\link[=antibiogram]{antibiogram()}}:
\enumerate{
\item \strong{Traditional Antibiogram}
@@ -134,8 +137,6 @@ your_data \%>\%
}\if{html}{\out{</div>}}
}
All types of antibiograms can be generated with the functions as described on this page, and can be plotted (using \code{\link[ggplot2:autoplot]{ggplot2::autoplot()}} or base \R \code{\link[=plot]{plot()}}/\code{\link[=barplot]{barplot()}}) or directly used into R Markdown / Quarto formats for reports (in the last case, \code{\link[knitr:kable]{knitr::kable()}} will be applied automatically). Use functions from specific 'table reporting' packages to transform the output of \code{\link[=antibiogram]{antibiogram()}} to your needs, e.g. \code{flextable::as_flextable()} or \code{gt::gt()}.
Note that for combination antibiograms, it is important to realise that susceptibility can be calculated in two ways, which can be set with the \code{only_all_tested} argument (default is \code{FALSE}). See this example for two antibiotics, Drug A and Drug B, about how \code{\link[=antibiogram]{antibiogram()}} works to calculate the \%SI:
\if{html}{\out{<div class="sourceCode">}}\preformatted{--------------------------------------------------------------------
@@ -156,6 +157,7 @@ Note that for combination antibiograms, it is important to realise that suscepti
--------------------------------------------------------------------
}\if{html}{\out{</div>}}
}
}
\examples{
# example_isolates is a data set available in the AMR package.
# run ?example_isolates for more info.
@@ -233,6 +235,7 @@ antibiogram(example_isolates,
)
)
# Print the output for R Markdown / Quarto -----------------------------
ureido <- antibiogram(example_isolates,

View File

@@ -55,7 +55,7 @@ The function \code{\link[=bug_drug_combinations]{bug_drug_combinations()}} retur
Determine antimicrobial resistance (AMR) of all bug-drug combinations in your data set where at least 30 (default) isolates are available per species. Use \code{\link[=format]{format()}} on the result to prettify it to a publishable/printable format, see \emph{Examples}.
}
\details{
The function \code{\link[=format]{format()}} calculates the resistance per bug-drug combination. Use \code{combine_SI = TRUE} (default) to test R vs. S+I and \code{combine_SI = FALSE} to test R+I vs. S.
The function \code{\link[=format]{format()}} calculates the resistance per bug-drug combination and returns a table ready for reporting/publishing. Use \code{combine_SI = TRUE} (default) to test R vs. S+I and \code{combine_SI = FALSE} to test R+I vs. S. This table can also directly be used in R Markdown / Quarto without the need for e.g. \code{\link[knitr:kable]{knitr::kable()}}.
}
\examples{
# example_isolates is a data set available in the AMR package.