mirror of
https://github.com/msberends/AMR.git
synced 2024-12-26 18:46:13 +01:00
more unit tests
This commit is contained in:
parent
95c9fdc552
commit
67521394f6
2
R/mo.R
2
R/mo.R
@ -182,7 +182,7 @@ exec_as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, allow_uncertain =
|
|||||||
# defined df to check for
|
# defined df to check for
|
||||||
if (!is.null(reference_df)) {
|
if (!is.null(reference_df)) {
|
||||||
if (!is.data.frame(reference_df) | NCOL(reference_df) < 2) {
|
if (!is.data.frame(reference_df) | NCOL(reference_df) < 2) {
|
||||||
stop('`reference_df` must be a data.frame with at least two columns.')
|
stop('`reference_df` must be a data.frame with at least two columns.', call. = FALSE)
|
||||||
}
|
}
|
||||||
# remove factors, just keep characters
|
# remove factors, just keep characters
|
||||||
suppressWarnings(
|
suppressWarnings(
|
||||||
|
@ -231,16 +231,7 @@ mo_property <- function(x, property = 'fullname', language = NULL, ...) {
|
|||||||
stop("invalid property: '", property, "' - use a column name of the `microorganisms` data set")
|
stop("invalid property: '", property, "' - use a column name of the `microorganisms` data set")
|
||||||
}
|
}
|
||||||
|
|
||||||
# this will give a warning if x cannot be coerced
|
mo_translate(mo_validate(x = x, property = property, ...), language = language)
|
||||||
res <- exec_as.mo(x = x, Becker = Becker, Lancefield = Lancefield, property = property)
|
|
||||||
|
|
||||||
if (property != "tsn") {
|
|
||||||
res[x %in% c("", NA) | res %in% c("", NA, "(no MO)")] <- ""
|
|
||||||
if (property %in% c("fullname", "shortname", "genus", "species", "subspecies", "type", "gramstain")) {
|
|
||||||
res <- mo_translate(res, language = language)
|
|
||||||
}
|
|
||||||
}
|
|
||||||
res
|
|
||||||
}
|
}
|
||||||
|
|
||||||
#' @rdname mo_property
|
#' @rdname mo_property
|
||||||
|
@ -165,7 +165,15 @@ test_that("as.mo works", {
|
|||||||
expect_equal(as.character(as.mo(c("TestingOwnID", "E. coli"),
|
expect_equal(as.character(as.mo(c("TestingOwnID", "E. coli"),
|
||||||
reference_df = data.frame(a = "TestingOwnID", b = "B_ESCHR_COL"))),
|
reference_df = data.frame(a = "TestingOwnID", b = "B_ESCHR_COL"))),
|
||||||
c("B_ESCHR_COL", "B_ESCHR_COL"))
|
c("B_ESCHR_COL", "B_ESCHR_COL"))
|
||||||
expect_warning(as.character(as.mo("TestingOwnID",
|
expect_warning(as.mo("TestingOwnID", reference_df = NULL))
|
||||||
reference_df = NULL)))
|
expect_error(as.mo("E. coli", reference_df = data.frame(a = "TestingOwnID")))
|
||||||
|
|
||||||
|
# combination of existing mo and certe
|
||||||
|
expect_identical(as.character(as.mo(c("B_ESCHR_COL", "ESCCOL"))),
|
||||||
|
c("B_ESCHR_COL", "B_ESCHR_COL"))
|
||||||
|
|
||||||
|
# TSN of prevalent and non prevalent ones
|
||||||
|
expect_equal(mo_TSN(c("Gomphosphaeria aponina delicatula", "Escherichia coli")),
|
||||||
|
c(717, 285))
|
||||||
|
|
||||||
})
|
})
|
||||||
|
@ -12,6 +12,7 @@ test_that("mo_property works", {
|
|||||||
expect_equal(mo_fullname("E. coli"), "Escherichia coli")
|
expect_equal(mo_fullname("E. coli"), "Escherichia coli")
|
||||||
expect_equal(mo_type("E. coli", language = "en"), "Bacteria")
|
expect_equal(mo_type("E. coli", language = "en"), "Bacteria")
|
||||||
expect_equal(mo_gramstain("E. coli", language = "en"), "Gram negative")
|
expect_equal(mo_gramstain("E. coli", language = "en"), "Gram negative")
|
||||||
|
expect_equal(mo_TSN("E. coli"), 285)
|
||||||
expect_equal(class(mo_taxonomy("E. coli")), "list")
|
expect_equal(class(mo_taxonomy("E. coli")), "list")
|
||||||
expect_equal(names(mo_taxonomy("E. coli")), c("subkingdom", "phylum", "class", "order",
|
expect_equal(names(mo_taxonomy("E. coli")), c("subkingdom", "phylum", "class", "order",
|
||||||
"family", "genus", "species", "subspecies"))
|
"family", "genus", "species", "subspecies"))
|
||||||
@ -42,4 +43,14 @@ test_that("mo_property works", {
|
|||||||
|
|
||||||
expect_error(mo_gramstain("E. coli", language = "UNKNOWN"))
|
expect_error(mo_gramstain("E. coli", language = "UNKNOWN"))
|
||||||
|
|
||||||
|
# manual property function
|
||||||
|
expect_error(mo_property("E. coli", property = c("tsn", "fullname")))
|
||||||
|
expect_error(mo_property("E. coli", property = "UNKNOWN"))
|
||||||
|
expect_identical(mo_property("E. coli", property = "fullname"),
|
||||||
|
mo_fullname("E. coli"))
|
||||||
|
expect_identical(mo_property("E. coli", property = "genus"),
|
||||||
|
mo_genus("E. coli"))
|
||||||
|
expect_identical(mo_property("E. coli", property = "species"),
|
||||||
|
mo_species("E. coli"))
|
||||||
|
|
||||||
})
|
})
|
||||||
|
Loading…
Reference in New Issue
Block a user