mirror of
https://github.com/msberends/AMR.git
synced 2025-07-12 23:41:57 +02:00
(v1.4.0.9003) CoNS update
This commit is contained in:
@ -89,7 +89,7 @@
|
||||
#' ab_atc("cephthriaxone")
|
||||
#' ab_atc("seephthriaaksone")
|
||||
ab_name <- function(x, language = get_locale(), tolower = FALSE, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
meet_criteria(tolower, allow_class = "logical", has_length = 1)
|
||||
|
||||
@ -106,21 +106,21 @@ ab_name <- function(x, language = get_locale(), tolower = FALSE, ...) {
|
||||
#' @aliases ATC
|
||||
#' @export
|
||||
ab_atc <- function(x, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
ab_validate(x = x, property = "atc", ...)
|
||||
}
|
||||
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_cid <- function(x, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
ab_validate(x = x, property = "cid", ...)
|
||||
}
|
||||
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_synonyms <- function(x, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
syns <- ab_validate(x = x, property = "synonyms", ...)
|
||||
names(syns) <- x
|
||||
if (length(syns) == 1) {
|
||||
@ -133,14 +133,14 @@ ab_synonyms <- function(x, ...) {
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_tradenames <- function(x, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
ab_synonyms(x, ...)
|
||||
}
|
||||
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_group <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
translate_AMR(ab_validate(x = x, property = "group", ...), language = language)
|
||||
}
|
||||
@ -148,7 +148,7 @@ ab_group <- function(x, language = get_locale(), ...) {
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_atc_group1 <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
translate_AMR(ab_validate(x = x, property = "atc_group1", ...), language = language)
|
||||
}
|
||||
@ -156,7 +156,7 @@ ab_atc_group1 <- function(x, language = get_locale(), ...) {
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_atc_group2 <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
translate_AMR(ab_validate(x = x, property = "atc_group2", ...), language = language)
|
||||
}
|
||||
@ -164,7 +164,7 @@ ab_atc_group2 <- function(x, language = get_locale(), ...) {
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_loinc <- function(x, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
loincs <- ab_validate(x = x, property = "loinc", ...)
|
||||
names(loincs) <- x
|
||||
if (length(loincs) == 1) {
|
||||
@ -177,7 +177,7 @@ ab_loinc <- function(x, ...) {
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_ddd <- function(x, administration = "oral", units = FALSE, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
meet_criteria(administration, is_in = c("oral", "iv"), has_length = 1)
|
||||
meet_criteria(units, allow_class = "logical", has_length = 1)
|
||||
|
||||
@ -193,7 +193,7 @@ ab_ddd <- function(x, administration = "oral", units = FALSE, ...) {
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_info <- function(x, language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
|
||||
|
||||
x <- as.ab(x, ...)
|
||||
@ -215,7 +215,7 @@ ab_info <- function(x, language = get_locale(), ...) {
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_url <- function(x, open = FALSE, ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
meet_criteria(open, allow_class = "logical", has_length = 1)
|
||||
|
||||
ab <- as.ab(x = x, ... = ...)
|
||||
@ -242,7 +242,7 @@ ab_url <- function(x, open = FALSE, ...) {
|
||||
#' @rdname ab_property
|
||||
#' @export
|
||||
ab_property <- function(x, property = "name", language = get_locale(), ...) {
|
||||
meet_criteria(x, allow_class = c("character", "numeric", "integer"))
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
meet_criteria(property, is_in = colnames(antibiotics), has_length = 1)
|
||||
meet_criteria(language, is_in = c(LANGUAGES_SUPPORTED, ""), has_length = 1, allow_NULL = TRUE, allow_NA = TRUE)
|
||||
translate_AMR(ab_validate(x = x, property = property, ...), language = language)
|
||||
|
@ -32,7 +32,7 @@
|
||||
#' @name AMR-deprecated
|
||||
#' @export
|
||||
p_symbol <- function(p, emptychar = " ") {
|
||||
.Deprecated(package = "AMR")
|
||||
.Deprecated(package = "AMR", new = "cleaner::p_symbol")
|
||||
|
||||
p <- as.double(p)
|
||||
s <- rep(NA_character_, length(p))
|
||||
|
2
R/mic.R
2
R/mic.R
@ -323,7 +323,7 @@ get_skimmers.mic <- function(column) {
|
||||
inline_hist <- import_fn("inline_hist", "skimr", error_on_fail = FALSE)
|
||||
sfl(
|
||||
skim_type = "mic",
|
||||
min = ~as.character(sort(na.omit(.))[1]),
|
||||
min = ~as.character(sort(stats::na.omit(.))[1]),
|
||||
max = ~as.character(sort(stats::na.omit(.))[length(stats::na.omit(.))]),
|
||||
median = ~as.character(stats::na.omit(.)[as.double(stats::na.omit(.)) == median(as.double(stats::na.omit(.)))])[1],
|
||||
n_unique = ~pm_n_distinct(., na.rm = TRUE),
|
||||
|
24
R/mo.R
24
R/mo.R
@ -28,10 +28,10 @@
|
||||
#' Use this function to determine a valid microorganism ID ([`mo`]). Determination is done using intelligent rules and the complete taxonomic kingdoms Bacteria, Chromista, Protozoa, Archaea and most microbial species from the kingdom Fungi (see Source). The input can be almost anything: a full name (like `"Staphylococcus aureus"`), an abbreviated name (like `"S. aureus"`), an abbreviation known in the field (like `"MRSA"`), or just a genus. Please see *Examples*.
|
||||
#' @inheritSection lifecycle Stable lifecycle
|
||||
#' @param x a character vector or a [data.frame] with one or two columns
|
||||
#' @param Becker a logical to indicate whether *Staphylococci* should be categorised into coagulase-negative *Staphylococci* ("CoNS") and coagulase-positive *Staphylococci* ("CoPS") instead of their own species, according to Karsten Becker *et al.* (1,2). Note that this does not include species that were newly named after these publications, like *S. caeli*.
|
||||
#' @param Becker a logical to indicate whether *Staphylococci* should be categorised into coagulase-negative *Staphylococci* ("CoNS") and coagulase-positive *Staphylococci* ("CoPS") instead of their own species, according to Karsten Becker *et al.* (1,2,3).
|
||||
#'
|
||||
#' This excludes *Staphylococcus aureus* at default, use `Becker = "all"` to also categorise *S. aureus* as "CoPS".
|
||||
#' @param Lancefield a logical to indicate whether beta-haemolytic *Streptococci* should be categorised into Lancefield groups instead of their own species, according to Rebecca C. Lancefield (3). These *Streptococci* will be categorised in their first group, e.g. *Streptococcus dysgalactiae* will be group C, although officially it was also categorised into groups G and L.
|
||||
#' @param Lancefield a logical to indicate whether beta-haemolytic *Streptococci* should be categorised into Lancefield groups instead of their own species, according to Rebecca C. Lancefield (4). These *Streptococci* will be categorised in their first group, e.g. *Streptococcus dysgalactiae* will be group C, although officially it was also categorised into groups G and L.
|
||||
#'
|
||||
#' This excludes *Enterococci* at default (who are in group D), use `Lancefield = "all"` to also categorise all *Enterococci* as group D.
|
||||
#' @param allow_uncertain a number between `0` (or `"none"`) and `3` (or `"all"`), or `TRUE` (= `2`) or `FALSE` (= `0`) to indicate whether the input should be checked for less probable results, please see *Details*
|
||||
@ -104,8 +104,9 @@
|
||||
#' @section Source:
|
||||
#' 1. Becker K *et al.* **Coagulase-Negative Staphylococci**. 2014. Clin Microbiol Rev. 27(4): 870–926. <https://dx.doi.org/10.1128/CMR.00109-13>
|
||||
#' 2. Becker K *et al.* **Implications of identifying the recently defined members of the *S. aureus* complex, *S. argenteus* and *S. schweitzeri*: A position paper of members of the ESCMID Study Group for staphylococci and Staphylococcal Diseases (ESGS).** 2019. Clin Microbiol Infect. <https://doi.org/10.1016/j.cmi.2019.02.028>
|
||||
#' 3. Lancefield RC **A serological differentiation of human and other groups of hemolytic streptococci**. 1933. J Exp Med. 57(4): 571–95. <https://dx.doi.org/10.1084/jem.57.4.571>
|
||||
#' 4. Catalogue of Life: Annual Checklist (public online taxonomic database), <http://www.catalogueoflife.org> (check included annual version with [catalogue_of_life_version()]).
|
||||
#' 3. Becker K *et al.* **Emergence of coagulase-negative staphylococci** 2020. Expert Rev Anti Infect Ther. 18(4):349-366. <https://dx.doi.org/10.1080/14787210.2020.1730813>
|
||||
#' 4. Lancefield RC **A serological differentiation of human and other groups of hemolytic streptococci**. 1933. J Exp Med. 57(4): 571–95. <https://dx.doi.org/10.1084/jem.57.4.571>
|
||||
#' 5. Catalogue of Life: Annual Checklist (public online taxonomic database), <http://www.catalogueoflife.org> (check included annual version with [catalogue_of_life_version()]).
|
||||
#' @export
|
||||
#' @return A [character] [vector] with additional class [`mo`]
|
||||
#' @seealso [microorganisms] for the [data.frame] that is being used to determine ID's.
|
||||
@ -158,7 +159,7 @@ as.mo <- function(x,
|
||||
ignore_pattern = getOption("AMR_ignore_pattern"),
|
||||
language = get_locale(),
|
||||
...) {
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
meet_criteria(x, allow_class = c("mo", "data.frame", "list", "character", "numeric", "integer", "factor"), allow_NA = TRUE)
|
||||
meet_criteria(Becker, allow_class = c("logical", "character"), has_length = 1)
|
||||
meet_criteria(Lancefield, allow_class = c("logical", "character"), has_length = 1)
|
||||
meet_criteria(allow_uncertain, allow_class = c("logical", "numeric", "integer"), has_length = 1)
|
||||
@ -275,7 +276,7 @@ exec_as.mo <- function(x,
|
||||
actual_uncertainty = 1,
|
||||
actual_input = NULL,
|
||||
language = get_locale()) {
|
||||
meet_criteria(x, allow_NA = TRUE)
|
||||
meet_criteria(x, allow_class = c("mo", "data.frame", "list", "character", "numeric", "integer", "factor"), allow_NA = TRUE)
|
||||
meet_criteria(Becker, allow_class = c("logical", "character"), has_length = 1)
|
||||
meet_criteria(Lancefield, allow_class = c("logical", "character"), has_length = 1)
|
||||
meet_criteria(allow_uncertain, allow_class = c("logical", "numeric", "integer"), has_length = 1)
|
||||
@ -1431,15 +1432,18 @@ exec_as.mo <- function(x,
|
||||
if (length(uncertainties$input) > 1) {
|
||||
plural <- c("s", "them", "were")
|
||||
}
|
||||
msg <- paste0("Result", plural[1], " of ", nr2char(length(uncertainties$input)), " value", plural[1],
|
||||
msg <- paste0("Translation to ", nr2char(length(uncertainties$input)), " microorganism", plural[1],
|
||||
" ", plural[3], " guessed with uncertainty. Use mo_uncertainties() to review ", plural[2], ".")
|
||||
message(font_blue(msg))
|
||||
message(font_red(msg))
|
||||
}
|
||||
|
||||
# Becker ----
|
||||
if (Becker == TRUE | Becker == "all") {
|
||||
# warn when species found that are not in Becker (2014, PMID 25278577) and Becker (2019, PMID 30872103)
|
||||
post_Becker <- c("argensis", "caeli", "cornubiensis", "edaphicus")
|
||||
# warn when species found that are not in:
|
||||
# - Becker et al. 2014, PMID 25278577
|
||||
# - Becker et al. 2019, PMID 30872103
|
||||
# - Becker et al. 2020, PMID 32056452
|
||||
post_Becker <- c("") # 2020-10-20 currently all are mentioned in above papers
|
||||
if (any(x %in% MO_lookup[which(MO_lookup$species %in% post_Becker), property])) {
|
||||
|
||||
warning("Becker ", font_italic("et al."), " (2014, 2019) does not contain these species named after their publication: ",
|
||||
|
62
R/rsi.R
62
R/rsi.R
@ -461,6 +461,12 @@ as.rsi.data.frame <- function(x,
|
||||
meet_criteria(conserve_capped_values, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(add_intrinsic_resistance, allow_class = "logical", has_length = 1)
|
||||
|
||||
# -- MO
|
||||
col_mo.bak <- col_mo
|
||||
if (is.null(col_mo)) {
|
||||
col_mo <- search_type_in_df(x = x, type = "mo", info = FALSE)
|
||||
}
|
||||
|
||||
# -- UTIs
|
||||
col_uti <- uti
|
||||
if (is.null(col_uti)) {
|
||||
@ -501,29 +507,25 @@ as.rsi.data.frame <- function(x,
|
||||
|
||||
i <- 0
|
||||
sel <- colnames(pm_select(x, ...))
|
||||
if (!is.null(col_mo)) {
|
||||
sel <- sel[sel != col_mo]
|
||||
}
|
||||
ab_cols <- colnames(x)[sapply(x, function(y) {
|
||||
i <<- i + 1
|
||||
check <- is.mic(y) | is.disk(y)
|
||||
ab <- colnames(x)[i]
|
||||
if (!is.null(col_mo) && ab == col_mo) {
|
||||
return(FALSE)
|
||||
}
|
||||
if (!is.null(col_uti) && ab == col_uti) {
|
||||
return(FALSE)
|
||||
}
|
||||
if (length(sel) == 0 || (length(sel) > 0 && ab %in% sel)) {
|
||||
ab_coerced <- suppressWarnings(as.ab(ab))
|
||||
if (is.na(ab_coerced) || (length(sel) > 0 & !ab %in% sel)) {
|
||||
# not even a valid AB code
|
||||
return(FALSE)
|
||||
} else {
|
||||
if (!check & all_valid_mics(y)) {
|
||||
message(font_blue(paste0("NOTE: Assuming column `", ab, "` (",
|
||||
ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""),
|
||||
ab_name(ab_coerced, tolower = TRUE), ") contains MIC values.")))
|
||||
} else if (!check & all_valid_disks(y)) {
|
||||
message(font_blue(paste0("NOTE: Assuming column `", ab, "` (",
|
||||
ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""),
|
||||
ab_name(ab_coerced, tolower = TRUE), ") contains disk zones.")))
|
||||
} else if (!check & !is.rsi(y)) {
|
||||
message(font_blue(paste0("NOTE: Assuming column `", ab, "` (",
|
||||
ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""),
|
||||
ab_name(ab_coerced, tolower = TRUE), ") must be cleaned to valid R/SI values.")))
|
||||
}
|
||||
return(TRUE)
|
||||
}
|
||||
} else {
|
||||
@ -535,36 +537,46 @@ as.rsi.data.frame <- function(x,
|
||||
"no columns with MIC values, disk zones or antibiotic column names found in this data set. Use as.mic() or as.disk() to transform antimicrobial columns.")
|
||||
# set type per column
|
||||
types <- character(length(ab_cols))
|
||||
types[sapply(x[, ab_cols], is.mic)] <- "mic"
|
||||
types[types == "" & sapply(x[, ab_cols], all_valid_mics)] <- "mic"
|
||||
types[sapply(x[, ab_cols], is.disk)] <- "disk"
|
||||
types[types == "" & sapply(x[, ab_cols], all_valid_disks)] <- "disk"
|
||||
types[sapply(x[, ab_cols], is.mic)] <- "mic"
|
||||
types[types == "" & sapply(x[, ab_cols], all_valid_mics)] <- "mic"
|
||||
types[types == "" & !sapply(x[, ab_cols], is.rsi)] <- "rsi"
|
||||
|
||||
if (any(types %in% c("mic", "disk"), na.rm = TRUE)) {
|
||||
# now we need an mo column - try to find columns based on type
|
||||
if (is.null(col_mo)) {
|
||||
# now we need an mo column
|
||||
stop_if(is.null(col_mo), "`col_mo` must be set")
|
||||
# if not null, we already found it, now find again so a message will show
|
||||
if (is.null(col_mo.bak)) {
|
||||
col_mo <- search_type_in_df(x = x, type = "mo")
|
||||
stop_if(is.null(col_mo), "`col_mo` must be set")
|
||||
}
|
||||
}
|
||||
|
||||
x_mo <- as.mo(x %pm>% pm_pull(col_mo))
|
||||
|
||||
for (i in seq_len(length(ab_cols))) {
|
||||
if (types[i] == "mic") {
|
||||
x[, ab_cols[i]] <- as.rsi.mic(x = x %pm>% pm_pull(ab_cols[i]),
|
||||
mo = x %pm>% pm_pull(col_mo),
|
||||
mo = x_mo,
|
||||
ab = ab_cols[i],
|
||||
guideline = guideline,
|
||||
uti = uti,
|
||||
conserve_capped_values = conserve_capped_values)
|
||||
} else if (types[i] == "disk") {
|
||||
x[, ab_cols[i]] <- as.rsi.disk(x = x %pm>% pm_pull(ab_cols[i]),
|
||||
mo = x %pm>% pm_pull(col_mo),
|
||||
mo = x_mo,
|
||||
ab = ab_cols[i],
|
||||
guideline = guideline,
|
||||
uti = uti)
|
||||
} else if (types[i] == "rsi") {
|
||||
ab <- ab_cols[i]
|
||||
ab_coerced <- suppressWarnings(as.ab(ab))
|
||||
message(font_blue(paste0("=> Cleaning values in column `", font_bold(ab), "` (",
|
||||
ifelse(ab_coerced != ab, paste0(ab_coerced, ", "), ""),
|
||||
ab_name(ab_coerced, tolower = TRUE), ")... ")),
|
||||
appendLF = FALSE)
|
||||
x[, ab_cols[i]] <- as.rsi.default(x = x %pm>% pm_pull(ab_cols[i]))
|
||||
message(font_green("OK."))
|
||||
}
|
||||
}
|
||||
|
||||
@ -760,11 +772,11 @@ freq.rsi <- function(x, ...) {
|
||||
x_name <- gsub(".*[$]", "", x_name)
|
||||
if (x_name %in% c("x", ".")) {
|
||||
# try again going through system calls
|
||||
x_name <- na.omit(sapply(sys.calls(),
|
||||
function(call) {
|
||||
call_txt <- as.character(call)
|
||||
ifelse(call_txt[1] %like% "freq$", call_txt[length(call_txt)], character(0))
|
||||
}))[1L]
|
||||
x_name <- stats::na.omit(sapply(sys.calls(),
|
||||
function(call) {
|
||||
call_txt <- as.character(call)
|
||||
ifelse(call_txt[1] %like% "freq$", call_txt[length(call_txt)], character(0))
|
||||
}))[1L]
|
||||
}
|
||||
ab <- suppressMessages(suppressWarnings(as.ab(x_name)))
|
||||
freq.default <- import_fn("freq.default", "cleaner", error_on_fail = FALSE)
|
||||
|
26
R/zzz.R
26
R/zzz.R
@ -84,23 +84,25 @@
|
||||
}
|
||||
|
||||
create_species_cons_cops <- function(type = c("CoNS", "CoPS")) {
|
||||
# Determination of which staphylococcal species are CoNS/CoPS according to Becker et al.:
|
||||
# https://cmr.asm.org/content/cmr/27/4/870/F6.large.jpg
|
||||
# Determination of which staphylococcal species are CoNS/CoPS according to:
|
||||
# - Becker et al. 2014, PMID 25278577
|
||||
# - Becker et al. 2019, PMID 30872103
|
||||
# - Becker et al. 2020, PMID 32056452
|
||||
# this function returns class <mo>
|
||||
MO_staph <- AMR::microorganisms
|
||||
MO_staph <- MO_staph[which(MO_staph$genus == "Staphylococcus"), , drop = FALSE]
|
||||
if (type == "CoNS") {
|
||||
MO_staph[which(MO_staph$species %in% c("coagulase-negative",
|
||||
"arlettae", "auricularis", "capitis",
|
||||
"caprae", "carnosus", "chromogenes", "cohnii", "condimenti",
|
||||
"devriesei", "epidermidis", "equorum", "felis",
|
||||
"fleurettii", "gallinarum", "haemolyticus",
|
||||
"hominis", "jettensis", "kloosii", "lentus",
|
||||
"lugdunensis", "massiliensis", "microti",
|
||||
MO_staph[which(MO_staph$species %in% c("coagulase-negative", "argensis", "arlettae",
|
||||
"auricularis", "caeli", "capitis", "caprae",
|
||||
"carnosus", "chromogenes", "cohnii", "condimenti",
|
||||
"debuckii", "devriesei", "edaphicus", "epidermidis",
|
||||
"equorum", "felis", "fleurettii", "gallinarum",
|
||||
"haemolyticus", "hominis", "jettensis", "kloosii",
|
||||
"lentus", "lugdunensis", "massiliensis", "microti",
|
||||
"muscae", "nepalensis", "pasteuri", "petrasii",
|
||||
"pettenkoferi", "piscifermentans", "rostri",
|
||||
"saccharolyticus", "saprophyticus", "sciuri",
|
||||
"stepanovicii", "simulans", "succinus",
|
||||
"pettenkoferi", "piscifermentans", "pseudoxylosus",
|
||||
"rostri", "saccharolyticus", "saprophyticus",
|
||||
"sciuri", "simulans", "stepanovicii", "succinus",
|
||||
"vitulinus", "warneri", "xylosus")
|
||||
| (MO_staph$species == "schleiferi" & MO_staph$subspecies %in% c("schleiferi", ""))),
|
||||
"mo", drop = TRUE]
|
||||
|
Reference in New Issue
Block a user