This commit is contained in:
dr. M.S. (Matthijs) Berends 2019-05-13 12:21:57 +02:00
parent 38a4421450
commit 0dc0715dc6
21 changed files with 137 additions and 68 deletions

View File

@ -140,6 +140,7 @@ export(mo_fullname)
export(mo_genus)
export(mo_gramstain)
export(mo_kingdom)
export(mo_name)
export(mo_order)
export(mo_phylum)
export(mo_property)

View File

@ -3,6 +3,7 @@
#### New
* Support for translation of disk diffusion and MIC values to RSI values (i.e. antimicrobial interpretations). Supported guidelines are EUCAST (2011 to 2019) and CLSI (2011 to 2019). Use `as.rsi()` on an MIC value (created with `as.mic()`), a disk diffusion value (created with the new `as.disk()`) or on a complete date set containing columns with MIC or disk diffusion values.
* Function `mo_name()` as alias of `mo_fullname()`
#### Changed
* Completely reworked the `antibiotics` data set:

View File

@ -374,42 +374,42 @@ eucast_exceptional_phenotypes <- function(x, country = "EUCAST", ...) {
mdro(x = x, country = "EUCAST", ...)
}
is_ESBL <- function(x, col_mo = NULL, ...) {
col_mo <- get_column_mo(tbl = x, col_mo = col_mo)
cols_ab <- get_column_abx(tbl = x,
soft_dependencies = c("AMX", "AMP"),
hard_dependencies = c("CAZ"),
...)
if (!any(c("AMX", "AMP") %in% names(cols_ab))) {
# both ampicillin and amoxicillin are missing
generate_warning_abs_missing(c("AMX", "AMP"), any = TRUE)
return(rep(NA, nrow(x)))
}
ESBLs <- rep(NA, nrow(x))
# first make all eligible cases FALSE
ESBLs[which(mo_family(x[, col_mo]) == "Enterobacteriaceae"
& x[, get_ab_col(cols_ab, "AMX")] %in% c("R", "I", "S")
& x[, get_ab_col(cols_ab, "AMX")] %in% c("R", "I", "S")
& x[, get_ab_col(cols_ab, "AMX")] %in% c("R", "I", "S")
)] <- FALSE
# now make the positives cases TRUE
ESBLs[which(!is.na(ESBLs)
& x[, get_ab_col(cols_ab, "AMX")] == "R"
& x[, get_ab_col(cols_ab, "CAZ")] == "R")] <- TRUE
ESBLs
}
is_3MRGN <- function(x, ...) {
}
is_4MRGN <- function(x, ...) {
}
# is_ESBL <- function(x, col_mo = NULL, ...) {
# col_mo <- get_column_mo(tbl = x, col_mo = col_mo)
# cols_ab <- get_column_abx(tbl = x,
# soft_dependencies = c("AMX", "AMP"),
# hard_dependencies = c("CAZ"),
# ...)
#
# if (!any(c("AMX", "AMP") %in% names(cols_ab))) {
# # both ampicillin and amoxicillin are missing
# generate_warning_abs_missing(c("AMX", "AMP"), any = TRUE)
# return(rep(NA, nrow(x)))
# }
#
# ESBLs <- rep(NA, nrow(x))
#
# # first make all eligible cases FALSE
# ESBLs[which(mo_family(x[, col_mo]) == "Enterobacteriaceae"
# & x[, get_ab_col(cols_ab, "AMX")] %in% c("R", "I", "S")
# & x[, get_ab_col(cols_ab, "AMX")] %in% c("R", "I", "S")
# & x[, get_ab_col(cols_ab, "AMX")] %in% c("R", "I", "S")
# )] <- FALSE
# # now make the positives cases TRUE
# ESBLs[which(!is.na(ESBLs)
# & x[, get_ab_col(cols_ab, "AMX")] == "R"
# & x[, get_ab_col(cols_ab, "CAZ")] == "R")] <- TRUE
# ESBLs
#
# }
#
# is_3MRGN <- function(x, ...) {
#
# }
#
# is_4MRGN <- function(x, ...) {
#
# }
get_column_mo <- function(tbl, col_mo = NULL) {
# throws a blue note about which column will be used if guessed

View File

@ -306,17 +306,17 @@ get_column_abx <- function(tbl,
TOB = TOB, TMP = TMP, SXT = SXT, VAN = VAN)
if (!is.null(hard_dependencies)) {
if (!all(hard_dependencies %in% names(columns_available))) {
if (!all(hard_dependencies %in% names(columns_available[!is.na(columns_available)]))) {
# missing a hard dependency will return NA and consequently the data will not be analysed
missing <- hard_dependencies[!hard_dependencies %in% names(columns_available)]
missing <- hard_dependencies[!hard_dependencies %in% names(columns_available[!is.na(columns_available)])]
generate_warning_abs_missing(missing, any = FALSE)
return(NA)
}
}
if (!is.null(soft_dependencies)) {
if (!all(soft_dependencies %in% names(columns_available))) {
if (!all(soft_dependencies %in% names(columns_available[!is.na(columns_available)]))) {
# missing a soft dependency may lower the reliability
missing <- soft_dependencies[!soft_dependencies %in% names(columns_available)]
missing <- soft_dependencies[!soft_dependencies %in% names(columns_available[!is.na(columns_available)])]
missing <- paste0("`", missing, "` (", ab_name(missing, tolower = TRUE), ")")
warning('Reliability might be improved if these antimicrobial results would be available too: ', paste(missing, collapse = ", "),
immediate. = TRUE,

32
R/mo.R
View File

@ -557,22 +557,22 @@ exec_as.mo <- function(x,
if (nchar(gsub("[^a-zA-Z]", "", x_trimmed[i])) < 3
& !x_backup_without_spp[i] %like% "O?(26|103|104|104|111|121|145|157)") {
# check if search term was like "A. species", then return first genus found with ^A
if (x_backup[i] %like% "[a-z]+ species" | x_backup[i] %like% "[a-z] spp[.]?") {
# get mo code of first hit
found <- microorganismsDT[fullname %like% x_withspaces_start_only[i], mo]
if (length(found) > 0) {
mo_code <- found[1L] %>% strsplit("_") %>% unlist() %>% .[1:2] %>% paste(collapse = "_")
found <- microorganismsDT[mo == mo_code, ..property][[1]]
# return first genus that begins with x_trimmed, e.g. when "E. spp."
if (length(found) > 0) {
x[i] <- found[1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
}
next
}
}
}
# if (x_backup[i] %like% "[a-z]+ species" | x_backup[i] %like% "[a-z] spp[.]?") {
# # get mo code of first hit
# found <- microorganismsDT[fullname %like% x_withspaces_start_only[i], mo]
# if (length(found) > 0) {
# mo_code <- found[1L] %>% strsplit("_") %>% unlist() %>% .[1:2] %>% paste(collapse = "_")
# found <- microorganismsDT[mo == mo_code, ..property][[1]]
# # return first genus that begins with x_trimmed, e.g. when "E. spp."
# if (length(found) > 0) {
# x[i] <- found[1L]
# if (initial_search == TRUE) {
# set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
# }
# next
# }
# }
# }
# fewer than 3 chars and not looked for species, add as failure
x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]]
if (initial_search == TRUE) {

View File

@ -64,7 +64,8 @@
#' mo_subspecies("E. coli") # ""
#'
#' ## colloquial properties
#' mo_fullname("E. coli") # "Escherichia coli"
#' mo_name("E. coli") # "Escherichia coli"
#' mo_fullname("E. coli") # "Escherichia coli", same as mo_name()
#' mo_shortname("E. coli") # "E. coli"
#'
#' ## other properties
@ -131,6 +132,12 @@
#'
#' # get a list with the complete taxonomy (from kingdom to subspecies)
#' mo_taxonomy("E. coli")
mo_name <- function(x, language = get_locale(), ...) {
mo_fullname(x = x, language = language, ... = ...)
}
#' @rdname mo_property
#' @export
mo_fullname <- function(x, language = get_locale(), ...) {
x <- mo_validate(x = x, property = "fullname", ...)
t(x, language = language)

View File

@ -31,7 +31,8 @@
#' @param data a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}})
#' @param translate_ab a column name of the \code{\link{antibiotics}} data set to translate the antibiotic abbreviations to, using \code{\link{ab_property}}
#' @inheritParams ab_property
#' @param combine_SI a logical to indicate whether all values of I and S must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter \code{combine_IR}, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now \code{TRUE}.
#' @param combine_SI a logical to indicate whether all values of S and I must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter \code{combine_IR}, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now \code{TRUE}.
#' @param combine_IR a logical to indicate whether all values of I and R must be merged into one, so the output only consists of S vs. I+R (susceptible vs. non-susceptible). This is outdated, see parameter \code{combine_SI}.
#' @inheritSection as.rsi Interpretation of S, I and R
#' @details \strong{Remember that you should filter your table to let it contain only first isolates!} Use \code{\link{first_isolate}} to determine them in your data set.
#'

View File

@ -242,6 +242,8 @@
<a href="#new" class="anchor"></a>New</h4>
<ul>
<li>Support for translation of disk diffusion and MIC values to RSI values (i.e. antimicrobial interpretations). Supported guidelines are EUCAST (2011 to 2019) and CLSI (2011 to 2019). Use <code><a href="../reference/as.rsi.html">as.rsi()</a></code> on an MIC value (created with <code><a href="../reference/as.mic.html">as.mic()</a></code>), a disk diffusion value (created with the new <code><a href="../reference/as.disk.html">as.disk()</a></code>) or on a complete date set containing columns with MIC or disk diffusion values.</li>
<li>Function <code><a href="../reference/mo_property.html">mo_name()</a></code> as alias of <code><a href="../reference/mo_property.html">mo_fullname()</a></code>
</li>
</ul>
</div>
<div id="changed" class="section level4">

View File

@ -285,7 +285,11 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
</tr>
<tr>
<th>combine_SI</th>
<td><p>a logical to indicate whether all values of I and S must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter <code>combine_IR</code>, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now <code>TRUE</code>.</p></td>
<td><p>a logical to indicate whether all values of S and I must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter <code>combine_IR</code>, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now <code>TRUE</code>.</p></td>
</tr>
<tr>
<th>combine_IR</th>
<td><p>a logical to indicate whether all values of I and R must be merged into one, so the output only consists of S vs. I+R (susceptible vs. non-susceptible). This is outdated, see parameter <code>combine_SI</code>.</p></td>
</tr>
</table>

View File

@ -301,7 +301,11 @@
</tr>
<tr>
<th>combine_SI</th>
<td><p>a logical to indicate whether all values of I and S must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter <code>combine_IR</code>, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now <code>TRUE</code>.</p></td>
<td><p>a logical to indicate whether all values of S and I must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter <code>combine_IR</code>, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now <code>TRUE</code>.</p></td>
</tr>
<tr>
<th>combine_IR</th>
<td><p>a logical to indicate whether all values of I and R must be merged into one, so the output only consists of S vs. I+R (susceptible vs. non-susceptible). This is outdated, see parameter <code>combine_SI</code>.</p></td>
</tr>
<tr>
<th>language</th>

View File

@ -373,7 +373,7 @@
</tr><tr>
<td>
<p><code><a href="mo_property.html">mo_fullname()</a></code> <code><a href="mo_property.html">mo_shortname()</a></code> <code><a href="mo_property.html">mo_subspecies()</a></code> <code><a href="mo_property.html">mo_species()</a></code> <code><a href="mo_property.html">mo_genus()</a></code> <code><a href="mo_property.html">mo_family()</a></code> <code><a href="mo_property.html">mo_order()</a></code> <code><a href="mo_property.html">mo_class()</a></code> <code><a href="mo_property.html">mo_phylum()</a></code> <code><a href="mo_property.html">mo_kingdom()</a></code> <code><a href="mo_property.html">mo_type()</a></code> <code><a href="mo_property.html">mo_gramstain()</a></code> <code><a href="mo_property.html">mo_ref()</a></code> <code><a href="mo_property.html">mo_authors()</a></code> <code><a href="mo_property.html">mo_year()</a></code> <code><a href="mo_property.html">mo_rank()</a></code> <code><a href="mo_property.html">mo_taxonomy()</a></code> <code><a href="mo_property.html">mo_url()</a></code> <code><a href="mo_property.html">mo_property()</a></code> </p>
<p><code><a href="mo_property.html">mo_name()</a></code> <code><a href="mo_property.html">mo_fullname()</a></code> <code><a href="mo_property.html">mo_shortname()</a></code> <code><a href="mo_property.html">mo_subspecies()</a></code> <code><a href="mo_property.html">mo_species()</a></code> <code><a href="mo_property.html">mo_genus()</a></code> <code><a href="mo_property.html">mo_family()</a></code> <code><a href="mo_property.html">mo_order()</a></code> <code><a href="mo_property.html">mo_class()</a></code> <code><a href="mo_property.html">mo_phylum()</a></code> <code><a href="mo_property.html">mo_kingdom()</a></code> <code><a href="mo_property.html">mo_type()</a></code> <code><a href="mo_property.html">mo_gramstain()</a></code> <code><a href="mo_property.html">mo_ref()</a></code> <code><a href="mo_property.html">mo_authors()</a></code> <code><a href="mo_property.html">mo_year()</a></code> <code><a href="mo_property.html">mo_rank()</a></code> <code><a href="mo_property.html">mo_taxonomy()</a></code> <code><a href="mo_property.html">mo_url()</a></code> <code><a href="mo_property.html">mo_property()</a></code> </p>
</td>
<td><p>Property of a microorganism</p></td>
</tr><tr>

View File

@ -241,7 +241,9 @@
</div>
<pre class="usage"><span class='fu'>mo_fullname</span>(<span class='no'>x</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='no'>...</span>)
<pre class="usage"><span class='fu'>mo_name</span>(<span class='no'>x</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='no'>...</span>)
<span class='fu'>mo_fullname</span>(<span class='no'>x</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='no'>...</span>)
<span class='fu'>mo_shortname</span>(<span class='no'>x</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='no'>...</span>)
@ -364,7 +366,8 @@ This package contains the complete taxonomic tree of almost all microorganisms (
<span class='fu'>mo_subspecies</span>(<span class='st'>"E. coli"</span>) <span class='co'># ""</span>
<span class='co'>## colloquial properties</span>
<span class='fu'>mo_fullname</span>(<span class='st'>"E. coli"</span>) <span class='co'># "Escherichia coli"</span>
<span class='fu'>mo_name</span>(<span class='st'>"E. coli"</span>) <span class='co'># "Escherichia coli"</span>
<span class='fu'>mo_fullname</span>(<span class='st'>"E. coli"</span>) <span class='co'># "Escherichia coli", same as mo_name()</span>
<span class='fu'>mo_shortname</span>(<span class='st'>"E. coli"</span>) <span class='co'># "E. coli"</span>
<span class='co'>## other properties</span>

View File

@ -295,7 +295,11 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
</tr>
<tr>
<th>combine_SI</th>
<td><p>a logical to indicate whether all values of I and S must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter <code>combine_IR</code>, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now <code>TRUE</code>.</p></td>
<td><p>a logical to indicate whether all values of S and I must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter <code>combine_IR</code>, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now <code>TRUE</code>.</p></td>
</tr>
<tr>
<th>combine_IR</th>
<td><p>a logical to indicate whether all values of I and R must be merged into one, so the output only consists of S vs. I+R (susceptible vs. non-susceptible). This is outdated, see parameter <code>combine_SI</code>.</p></td>
</tr>
</table>

View File

@ -43,7 +43,9 @@ count_df(data, translate_ab = "name", language = get_locale(),
\item{language}{language of the returned text, defaults to system language (see \code{\link{get_locale}}) and can also be set with \code{\link{getOption}("AMR_locale")}. Use \code{language = NULL} or \code{language = ""} to prevent translation.}
\item{combine_SI}{a logical to indicate whether all values of I and S must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter \code{combine_IR}, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now \code{TRUE}.}
\item{combine_SI}{a logical to indicate whether all values of S and I must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter \code{combine_IR}, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now \code{TRUE}.}
\item{combine_IR}{a logical to indicate whether all values of I and R must be merged into one, so the output only consists of S vs. I+R (susceptible vs. non-susceptible). This is outdated, see parameter \code{combine_SI}.}
}
\value{
Integer

View File

@ -50,7 +50,9 @@ labels_rsi_count(position = NULL, x = "Antibiotic",
\item{translate_ab}{a column name of the \code{\link{antibiotics}} data set to translate the antibiotic abbreviations to, using \code{\link{ab_property}}}
\item{combine_SI}{a logical to indicate whether all values of I and S must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter \code{combine_IR}, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now \code{TRUE}.}
\item{combine_SI}{a logical to indicate whether all values of S and I must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter \code{combine_IR}, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now \code{TRUE}.}
\item{combine_IR}{a logical to indicate whether all values of I and R must be merged into one, so the output only consists of S vs. I+R (susceptible vs. non-susceptible). This is outdated, see parameter \code{combine_SI}.}
\item{language}{language of the returned text, defaults to system language (see \code{\link{get_locale}}) and can also be set with \code{\link{getOption}("AMR_locale")}. Use \code{language = NULL} or \code{language = ""} to prevent translation.}

View File

@ -2,6 +2,7 @@
% Please edit documentation in R/mo_property.R
\name{mo_property}
\alias{mo_property}
\alias{mo_name}
\alias{mo_fullname}
\alias{mo_shortname}
\alias{mo_subspecies}
@ -22,6 +23,8 @@
\alias{mo_url}
\title{Property of a microorganism}
\usage{
mo_name(x, language = get_locale(), ...)
mo_fullname(x, language = get_locale(), ...)
mo_shortname(x, language = get_locale(), ...)
@ -132,7 +135,8 @@ mo_species("E. coli") # "coli"
mo_subspecies("E. coli") # ""
## colloquial properties
mo_fullname("E. coli") # "Escherichia coli"
mo_name("E. coli") # "Escherichia coli"
mo_fullname("E. coli") # "Escherichia coli", same as mo_name()
mo_shortname("E. coli") # "E. coli"
## other properties

View File

@ -49,7 +49,9 @@ portion_df(data, translate_ab = "name", language = get_locale(),
\item{language}{language of the returned text, defaults to system language (see \code{\link{get_locale}}) and can also be set with \code{\link{getOption}("AMR_locale")}. Use \code{language = NULL} or \code{language = ""} to prevent translation.}
\item{combine_SI}{a logical to indicate whether all values of I and S must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter \code{combine_IR}, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now \code{TRUE}.}
\item{combine_SI}{a logical to indicate whether all values of S and I must be merged into one, so the output only consists of S+I vs. R (susceptible vs. resistant). This used to be the parameter \code{combine_IR}, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now \code{TRUE}.}
\item{combine_IR}{a logical to indicate whether all values of I and R must be merged into one, so the output only consists of S vs. I+R (susceptible vs. non-susceptible). This is outdated, see parameter \code{combine_SI}.}
}
\value{
Double or, when \code{as_percent = TRUE}, a character.

View File

@ -33,6 +33,9 @@ test_that("EUCAST rules work", {
"reference.rule", "reference.rule_group"))
expect_error(suppressWarnings(eucast_rules(septic_patients, col_mo = "Non-existing")))
expect_error(eucast_rules(x = "text"))
expect_error(eucast_rules(data.frame(a = "test")))
expect_error(eucast_rules(data.frame(mo = "test"), rules = "invalid rules set"))
expect_identical(colnames(septic_patients),
colnames(suppressWarnings(eucast_rules(septic_patients))))

View File

@ -42,3 +42,10 @@ test_that("functions missing in older R versions work", {
expect_equal(trimws(" test ", "l"), "test ")
expect_equal(trimws(" test ", "r"), " test")
})
test_that("looking up ab columns works", {
expect_warning(generate_warning_abs_missing(c("AMP", "AMX")))
expect_warning(generate_warning_abs_missing(c("AMP", "AMX"), any = TRUE))
expect_warning(get_column_abx(septic_patients, hard_dependencies = "FUS"))
expect_warning(get_column_abx(septic_patients, soft_dependencies = "FUS"))
})

View File

@ -200,6 +200,9 @@ test_that("as.mo works", {
expect_equal(suppressWarnings(as.character(as.mo("esco extra_text", allow_uncertain = FALSE))), "UNKNOWN")
expect_equal(suppressWarnings(as.character(as.mo("esco extra_text", allow_uncertain = TRUE))), "B_ESCHR_COL")
expect_warning(as.mo("esco extra_text", allow_uncertain = TRUE))
expect_equal(suppressWarnings(as.character(as.mo("unexisting aureus", allow_uncertain = 3))), "B_STPHY_AUR")
expect_equal(suppressWarnings(as.character(as.mo("unexisting staphy", allow_uncertain = 3))), "B_STPHY")
expect_equal(suppressWarnings(as.character(as.mo("Staphylococcus aureus unexisting", allow_uncertain = 3))), "B_STPHY")
# predefined reference_df
expect_equal(as.character(as.mo("TestingOwnID",
@ -244,4 +247,20 @@ test_that("as.mo works", {
# summary
expect_equal(length(summary(septic_patients$mo)), 6)
# other
expect_equal(as.character(as.mo(c("xxx", "con", "na", "nan"), debug = TRUE)),
rep(NA_character_, 4))
expect_equal(as.character(as.mo(c("other", "none", "unknown"))),
rep("UNKNOWN", 3))
expect_null(mo_failures())
expect_true(septic_patients %>% pull(mo) %>% is.mo())
expect_equal(get_mo_code("test", "mo"), "test")
expect_equal(length(get_mo_code("Escherichia", "genus")),
nrow(AMR::microorganisms[base::which(AMR::microorganisms[, "genus"] %in% "Escherichia"),]))
expect_error(translate_allow_uncertain(5))
})

View File

@ -31,6 +31,7 @@ test_that("mo_property works", {
expect_equal(mo_species("E. coli"), "coli")
expect_equal(mo_subspecies("E. coli"), "")
expect_equal(mo_fullname("E. coli"), "Escherichia coli")
expect_equal(mo_name("E. coli"), "Escherichia coli")
expect_equal(mo_type("E. coli", language = "en"), "Bacteria")
expect_equal(mo_gramstain("E. coli", language = "en"), "Gram negative")
expect_equal(class(mo_taxonomy("E. coli")), "list")
@ -47,6 +48,8 @@ test_that("mo_property works", {
expect_equal(mo_shortname("S. agalac"), "S. agalactiae")
expect_equal(mo_shortname("S. agalac", Lancefield = TRUE), "GBS")
expect_true(mo_url("Escherichia coli") %like% "www.catalogueoflife.org")
# test integrity
MOs <- AMR::microorganisms
expect_identical(MOs$fullname, mo_fullname(MOs$fullname, language = "en"))