From 0dc0715dc661b616c089e7c68b83fd0f0067888e Mon Sep 17 00:00:00 2001 From: "Matthijs S. Berends" Date: Mon, 13 May 2019 12:21:57 +0200 Subject: [PATCH] CI tests --- NAMESPACE | 1 + NEWS.md | 1 + R/mdro.R | 72 +++++++++++++++--------------- R/misc.R | 8 ++-- R/mo.R | 32 ++++++------- R/mo_property.R | 9 +++- R/portion.R | 3 +- docs/news/index.html | 2 + docs/reference/count.html | 6 ++- docs/reference/ggplot_rsi.html | 6 ++- docs/reference/index.html | 2 +- docs/reference/mo_property.html | 7 ++- docs/reference/portion.html | 6 ++- man/count.Rd | 4 +- man/ggplot_rsi.Rd | 4 +- man/mo_property.Rd | 6 ++- man/portion.Rd | 4 +- tests/testthat/test-eucast_rules.R | 3 ++ tests/testthat/test-misc.R | 7 +++ tests/testthat/test-mo.R | 19 ++++++++ tests/testthat/test-mo_property.R | 3 ++ 21 files changed, 137 insertions(+), 68 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index 7363cf91..0ae3547b 100755 --- a/NAMESPACE +++ b/NAMESPACE @@ -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) diff --git a/NEWS.md b/NEWS.md index e794ec0c..74907e41 100755 --- a/NEWS.md +++ b/NEWS.md @@ -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: diff --git a/R/mdro.R b/R/mdro.R index bf6b009e..ad6908cd 100755 --- a/R/mdro.R +++ b/R/mdro.R @@ -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 diff --git a/R/misc.R b/R/misc.R index a20d2e82..de04afc8 100755 --- a/R/misc.R +++ b/R/misc.R @@ -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, diff --git a/R/mo.R b/R/mo.R index 41af877a..05c5203d 100755 --- a/R/mo.R +++ b/R/mo.R @@ -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) { diff --git a/R/mo_property.R b/R/mo_property.R index 29af76be..46d188f1 100755 --- a/R/mo_property.R +++ b/R/mo_property.R @@ -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) diff --git a/R/portion.R b/R/portion.R index 0896b3bd..9d94f80f 100755 --- a/R/portion.R +++ b/R/portion.R @@ -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. #' diff --git a/docs/news/index.html b/docs/news/index.html index accffc4c..96b552a4 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -242,6 +242,8 @@ New
diff --git a/docs/reference/count.html b/docs/reference/count.html index 1f1b64ee..2bdd01e1 100644 --- a/docs/reference/count.html +++ b/docs/reference/count.html @@ -285,7 +285,11 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_ 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 combine_IR, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now TRUE.

+

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 combine_IR, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now TRUE.

+ + + 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 combine_SI.

diff --git a/docs/reference/ggplot_rsi.html b/docs/reference/ggplot_rsi.html index 6a85bad8..0e4ac000 100644 --- a/docs/reference/ggplot_rsi.html +++ b/docs/reference/ggplot_rsi.html @@ -301,7 +301,11 @@ 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 combine_IR, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now TRUE.

+

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 combine_IR, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now TRUE.

+ + + 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 combine_SI.

language diff --git a/docs/reference/index.html b/docs/reference/index.html index 0e7d4aeb..53b3ad07 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -373,7 +373,7 @@ -

mo_fullname() mo_shortname() mo_subspecies() mo_species() mo_genus() mo_family() mo_order() mo_class() mo_phylum() mo_kingdom() mo_type() mo_gramstain() mo_ref() mo_authors() mo_year() mo_rank() mo_taxonomy() mo_url() mo_property()

+

mo_name() mo_fullname() mo_shortname() mo_subspecies() mo_species() mo_genus() mo_family() mo_order() mo_class() mo_phylum() mo_kingdom() mo_type() mo_gramstain() mo_ref() mo_authors() mo_year() mo_rank() mo_taxonomy() mo_url() mo_property()

Property of a microorganism

diff --git a/docs/reference/mo_property.html b/docs/reference/mo_property.html index 4c9f333a..eb549154 100644 --- a/docs/reference/mo_property.html +++ b/docs/reference/mo_property.html @@ -241,7 +241,9 @@
-
mo_fullname(x, language = get_locale(), ...)
+    
mo_name(x, language = get_locale(), ...)
+
+mo_fullname(x, language = get_locale(), ...)
 
 mo_shortname(x, language = get_locale(), ...)
 
@@ -364,7 +366,8 @@ This package contains the complete taxonomic tree of almost all microorganisms (
 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
diff --git a/docs/reference/portion.html b/docs/reference/portion.html
index 8fbdaacf..46251b39 100644
--- a/docs/reference/portion.html
+++ b/docs/reference/portion.html
@@ -295,7 +295,11 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
     
     
       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 combine_IR, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now TRUE.

+

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 combine_IR, but this now follows the redefinition by EUCAST about the interpretion of I (increased exposure) in 2019, see below. Default is now TRUE.

+ + + 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 combine_SI.

diff --git a/man/count.Rd b/man/count.Rd index e2accb73..9c9c4737 100644 --- a/man/count.Rd +++ b/man/count.Rd @@ -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 diff --git a/man/ggplot_rsi.Rd b/man/ggplot_rsi.Rd index edc51a51..a49484e3 100644 --- a/man/ggplot_rsi.Rd +++ b/man/ggplot_rsi.Rd @@ -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.} diff --git a/man/mo_property.Rd b/man/mo_property.Rd index 6fccb9cd..a5a70a78 100644 --- a/man/mo_property.Rd +++ b/man/mo_property.Rd @@ -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 diff --git a/man/portion.Rd b/man/portion.Rd index 574e6f36..befc3bf3 100644 --- a/man/portion.Rd +++ b/man/portion.Rd @@ -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. diff --git a/tests/testthat/test-eucast_rules.R b/tests/testthat/test-eucast_rules.R index 286bcd81..f853eb8b 100755 --- a/tests/testthat/test-eucast_rules.R +++ b/tests/testthat/test-eucast_rules.R @@ -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)))) diff --git a/tests/testthat/test-misc.R b/tests/testthat/test-misc.R index 2c7f24c2..1403da12 100755 --- a/tests/testthat/test-misc.R +++ b/tests/testthat/test-misc.R @@ -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")) +}) diff --git a/tests/testthat/test-mo.R b/tests/testthat/test-mo.R index c92ef1dd..44f62095 100644 --- a/tests/testthat/test-mo.R +++ b/tests/testthat/test-mo.R @@ -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)) + }) diff --git a/tests/testthat/test-mo_property.R b/tests/testthat/test-mo_property.R index 68307088..cbb86007 100644 --- a/tests/testthat/test-mo_property.R +++ b/tests/testthat/test-mo_property.R @@ -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"))