1
0
mirror of https://github.com/msberends/AMR.git synced 2025-07-08 11:51:59 +02:00

(v1.4.0.9013) is_gram_negative/positive update

This commit is contained in:
2020-11-09 13:07:02 +01:00
parent 423879c034
commit d3b1d33210
22 changed files with 149 additions and 82 deletions

View File

@ -54,7 +54,7 @@
#'
#' # get bug/drug combinations for only macrolides in Gram-positives:
#' example_isolates %>%
#' filter(mo %>% is_gram_positive()) %>%
#' filter(is_gram_positive()) %>%
#' select(mo, macrolides()) %>%
#' bug_drug_combinations() %>%
#' format()

View File

@ -773,7 +773,7 @@ eucast_rules <- function(x,
like_is_one_of <- trimws(eucast_rules_df[i, "like.is.one_of", drop = TRUE])
mo_value <- trimws(eucast_rules_df[i, "this_value", drop = TRUE])
# be sure to comprise all coagulase-negative/-positive Staphylococci when they are mentioned
# be sure to comprise all coagulase-negative/-positive staphylococci when they are mentioned
if (mo_value %like% "coagulase" && any(x$genus == "Staphylococcus", na.rm = TRUE)) {
if (mo_value %like% "negative") {
eucast_rules_df[i, "this_value"] <- paste0("^(", paste0(all_staph[which(all_staph$CNS_CPS %like% "negative"),

2
R/mo.R
View File

@ -28,7 +28,7 @@
#' 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,3).
#' @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 (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.

View File

@ -41,7 +41,7 @@
#'
#' Since the top-level of the taxonomy is sometimes referred to as 'kingdom' and sometimes as 'domain', the functions [mo_kingdom()] and [mo_domain()] return the exact same results.
#'
#' The Gram stain - [mo_gramstain()] - will be determined based on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002, [PMID 11837318](https://pubmed.ncbi.nlm.nih.gov/11837318)), who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value `NA`. Functions [is_gram_negative()] and [is_gram_positive()] always return `TRUE` or `FALSE`, even for species outside the kingdom of Bacteria.
#' The Gram stain - [mo_gramstain()] - will be determined based on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002, [PMID 11837318](https://pubmed.ncbi.nlm.nih.gov/11837318)), who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value `NA`. Functions [is_gram_negative()] and [is_gram_positive()] always return `TRUE` or `FALSE` (except when the input is `NA` or the MO code is `UNKNOWN`), thus always return `FALSE` for species outside the taxonomic kingdom of Bacteria.
#'
#' All output will be [translate]d where possible.
#'
@ -122,7 +122,7 @@
#' mo_shortname("S. pyo", Lancefield = TRUE) # "GAS" (='Group A Streptococci')
#'
#'
#' # language support for German, Dutch, Spanish, Portuguese, Italian and French
#' # language support --------------------------------------------------------
#' mo_gramstain("E. coli", language = "de") # "Gramnegativ"
#' mo_gramstain("E. coli", language = "nl") # "Gram-negatief"
#' mo_gramstain("E. coli", language = "es") # "Gram negativo"
@ -139,7 +139,11 @@
#' Lancefield = TRUE,
#' language = "nl") # "Streptococcus groep A"
#'
#' # gram stains can be used as a filter
#' example_isolates %>%
#' filter(is_gram_positive())
#'
#' # other --------------------------------------------------------------------
#' # get a list with the complete taxonomy (from kingdom to subspecies)
#' mo_taxonomy("E. coli")
#' # get a list with the taxonomy, the authors, Gram-stain and URL to the online database
@ -177,10 +181,10 @@ mo_shortname <- function(x, language = get_locale(), ...) {
# exceptions for where no species is known
shortnames[shortnames %like% ".[.] spp[.]"] <- genera[shortnames %like% ".[.] spp[.]"]
# exceptions for Staphylococci
# exceptions for staphylococci
shortnames[shortnames == "S. coagulase-negative"] <- "CoNS"
shortnames[shortnames == "S. coagulase-positive"] <- "CoPS"
# exceptions for Streptococci: Streptococcus Group A -> GAS
# exceptions for streptococci: Group A Streptococcus -> GAS
shortnames[shortnames %like% "S. group [ABCDFGHK]"] <- paste0("G", gsub("S. group ([ABCDFGHK])", "\\1", shortnames[shortnames %like% "S. group [ABCDFGHK]"]), "S")
# unknown species etc.
shortnames[shortnames %like% "unknown"] <- paste0("(", trimws(gsub("[^a-zA-Z -]", "", shortnames[shortnames %like% "unknown"])), ")")
@ -311,6 +315,23 @@ mo_gramstain <- function(x, language = get_locale(), ...) {
#' @rdname mo_property
#' @export
is_gram_negative <- function(x, language = get_locale(), ...) {
if (missing(x)) {
peek_mask_dplyr <- import_fn("peek_mask", "dplyr", error_on_fail = FALSE)
if (!is.null(peek_mask_dplyr)) {
try({
df <- as.data.frame(peek_mask_dplyr()$across_cols(), stringsAsFactors = FALSE)
mo <- suppressMessages(search_type_in_df(df, "mo"))
if (!is.null(mo)) {
message_("Using column `", font_bold(mo), "` as input for 'x'")
x <- df[, mo, drop = TRUE]
} else {
stop_("Argument 'x' is missing")
}
}, silent = TRUE)
} else {
stop_("Argument 'x' is missing")
}
}
meet_criteria(x, allow_NA = TRUE)
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
@ -318,12 +339,31 @@ is_gram_negative <- function(x, language = get_locale(), ...) {
metadata <- get_mo_failures_uncertainties_renamed()
grams <- mo_gramstain(x.mo, language = NULL)
load_mo_failures_uncertainties_renamed(metadata)
grams == "Gram-negative" & !is.na(grams)
out <- grams == "Gram-negative" & !is.na(grams)
out[x.mo %in% c(NA, "UNKNOWN")] <- NA
out
}
#' @rdname mo_property
#' @export
is_gram_positive <- function(x, language = get_locale(), ...) {
if (missing(x)) {
peek_mask_dplyr <- import_fn("peek_mask", "dplyr", error_on_fail = FALSE)
if (!is.null(peek_mask_dplyr)) {
try({
df <- as.data.frame(peek_mask_dplyr()$across_cols(), stringsAsFactors = FALSE)
mo <- suppressMessages(search_type_in_df(df, "mo"))
if (!is.null(mo)) {
message_("Using column `", font_bold(mo), "` as input for 'x'")
x <- df[, mo, drop = TRUE]
} else {
stop_("Argument 'x' is missing")
}
}, silent = TRUE)
} else {
stop_("Argument 'x' is missing")
}
}
meet_criteria(x, allow_NA = TRUE)
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
@ -331,7 +371,9 @@ is_gram_positive <- function(x, language = get_locale(), ...) {
metadata <- get_mo_failures_uncertainties_renamed()
grams <- mo_gramstain(x.mo, language = NULL)
load_mo_failures_uncertainties_renamed(metadata)
grams == "Gram-positive" & !is.na(grams)
out <- grams == "Gram-positive" & !is.na(grams)
out[x.mo %in% c(NA, "UNKNOWN")] <- NA
out
}
#' @rdname mo_property