diff --git a/DESCRIPTION b/DESCRIPTION index 89e7b702..055df164 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 0.8.0.9006 -Date: 2019-10-27 +Version: 0.8.0.9007 +Date: 2019-10-30 Title: Antimicrobial Resistance Analysis Authors@R: c( person(role = c("aut", "cre"), diff --git a/NEWS.md b/NEWS.md index b7d95eab..21e2cd94 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,5 @@ -# AMR 0.8.0.9006 -Last updated: 27-Oct-2019 +# AMR 0.8.0.9007 +Last updated: 30-Oct-2019 ### New * Support for a new MDRO guideline: Magiorakos AP, Srinivasan A *et al.* "Multidrug-resistant, extensively drug-resistant and pandrug-resistant bacteria: an international expert proposal for interim standard definitions for acquired resistance." Clinical Microbiology and Infection (2012). **This is now the new default guideline for the `mdro()` function.** @@ -7,7 +7,7 @@ ### Changes * When running `as.rsi()` over a data set, it will now print the guideline that will be used if it is not specified by the user * Fix for `eucast_rules()`: *Stenotrophomonas maltophilia* not interpreted "R" to ceftazidime anymore (following EUCAST v3.1) -* Fix in taxonomic info for genera that are in multiple kingdoms, like *Proteus* +* Adopted Adeolu *et al.* (2016), [PMID 27620848](https://www.ncbi.nlm.nih.gov/pubmed/27620848) for the `microorganisms` data set, which means that the new order Enterobacterales now consists of a part of the existing family *Enterobacteriaceae*, but that this family has been split into other families as well (like *Morganellaceae* and *Yersiniaceae*). Although published in 2016, this information is not yet in the Catalogue of Life version of 2019. All MDRO determinations with `mdro()` will now use the Enterobacterales order for all guidelines before 2016. * Fix for interpreting MIC values with `as.rsi()` where the input is `NA` * Added "imi" as allowed abbreviation for Imipenem * Fix for automatically determining columns with antibiotic results in `mdro()` and `eucast_rules()` diff --git a/R/data.R b/R/data.R index 77f1b794..4244bc6a 100755 --- a/R/data.R +++ b/R/data.R @@ -55,7 +55,7 @@ #' #' A data set containing the microbial taxonomy of six kingdoms from the Catalogue of Life. MO codes can be looked up using \code{\link{as.mo}}. #' @inheritSection catalogue_of_life Catalogue of Life -#' @format A \code{\link{data.frame}} with 69,465 observations and 16 variables: +#' @format A \code{\link{data.frame}} with 69,447 observations and 16 variables: #' \describe{ #' \item{\code{mo}}{ID of microorganism as used by this package} #' \item{\code{col_id}}{Catalogue of Life ID} @@ -72,9 +72,10 @@ #' \item{11 entries of \emph{Streptococcus} (beta-haemolytic: groups A, B, C, D, F, G, H, K and unspecified; other: viridans, milleri)} #' \item{2 entries of \emph{Staphylococcus} (coagulase-negative [CoNS] and coagulase-positive [CoPS])} #' \item{3 entries of \emph{Trichomonas} (\emph{Trichomonas vaginalis}, and its family and genus)} -#' \item{1 entry of \emph{Blastocystis} (\emph{Blastocystis hominis}), although it officially does not exist (Noel et al. 2005, PMID 15634993)} +#' \item{1 entry of \emph{Blastocystis} (\emph{Blastocystis hominis}), although it officially does not exist (Noel \emph{et al.} 2005, PMID 15634993)} #' \item{5 other 'undefined' entries (unknown, unknown Gram negatives, unknown Gram positives, unknown yeast and unknown fungus)} -#' \item{9,460 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) since the DSMZ contain the latest taxonomic information based on recent publications} +#' \item{6 families under the Enterobacterales order, according to Adeolu \emph{et al.} (2016, PMID 27620848), that are not in the Catalogue of Life} +#' \item{12,600 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) since the DSMZ contain the latest taxonomic information based on recent publications} #' } #' @section About the records from DSMZ (see source): #' Names of prokaryotes are defined as being validly published by the International Code of Nomenclature of Bacteria. Validly published are all names which are included in the Approved Lists of Bacterial Names and the names subsequently published in the International Journal of Systematic Bacteriology (IJSB) and, from January 2000, in the International Journal of Systematic and Evolutionary Microbiology (IJSEM) as original articles or in the validation lists. diff --git a/R/mdro.R b/R/mdro.R index 206de2b9..d9bef3e5 100755 --- a/R/mdro.R +++ b/R/mdro.R @@ -424,6 +424,9 @@ mdro <- function(x, } } trans_tbl2 <- function(txt, rows, lst) { + if (info == TRUE) { + message(blue(txt, "..."), appendLF = FALSE) + } # function specific for the CMI paper of 2012 (Magiorakos et al.) lst_vector <- unlist(lst)[!is.na(unlist(lst))] x$total_groups <- NA_integer_ @@ -447,12 +450,15 @@ mdro <- function(x, # MDR (=2): >=3 groups affected x[which(x$row_number %in% rows & x$affected_groups >= 3), "MDRO"] <<- 2 # XDR (=3): all but <=2 groups affected - x[which(x$row_number %in% rows & x$total_groups - x$affected_groups <= 2), "MDRO"] <<- 3 + x[which(x$row_number %in% rows & (x$total_groups - x$affected_groups) <= 2), "MDRO"] <<- 3 # PDR (=4): all agents are R x[filter_at(x[rows, ], vars(lst_vector), all_vars(. %in% c("R", "I")))$row_number, "MDRO"] <<- 4 + if (info == TRUE) { + message(blue(" OK")) + } } x <- x %>% @@ -461,7 +467,7 @@ mdro <- function(x, left_join_microorganisms(by = col_mo) %>% # add unconfirmed to where genus is available mutate(MDRO = ifelse(!is.na(genus), 1, NA_integer_), - row_number = seq_len(nrow(x))) %>% + row_number = seq_len(nrow(.))) %>% # transform to data.frame so subsetting is possible with x[y, z] (might not be the case with tibble/data.table/...) as.data.frame(stringsAsFactors = FALSE) @@ -572,7 +578,7 @@ mdro <- function(x, FOS, QDA, c(TCY, DOX, MNO))) - trans_tbl2(paste("Table 2 -", italic("Enterococcus"), "spp"), + trans_tbl2(paste("Table 2 -", italic("Enterococcus"), "spp."), which(x$genus == "Enterococcus"), list(GEH, STH, @@ -585,8 +591,10 @@ mdro <- function(x, AMP, QDA, c(DOX, MNO))) - trans_tbl2(paste("Table 3 -", italic("Enterobacteriaceae")), - which(x$family == "Enterobacteriaceae"), + trans_tbl2(paste0("Table 3 - ", italic("Enterobacteriaceae"), + " (before the taxonomic reclassification by Adeolu ", italic("et al."), ", 2016)"), + # this new order was previously 'Enterobacteriales' and contained only the family 'Enterobacteriaceae': + which(x$order == "Enterobacterales"), list(c(GEN, TOB, AMK, NET), CPT, c(TCC, TZP), @@ -615,7 +623,7 @@ mdro <- function(x, ATM, FOS, c(COL, PLB))) - trans_tbl2(paste("Table 5 -", italic("Acinetobacter"), "spp"), + trans_tbl2(paste("Table 5 -", italic("Acinetobacter"), "spp."), which(x$genus == "Acinetobacter"), list(c(GEN, TOB, AMK, NET), c(IPM, MEM, DOR), @@ -632,7 +640,7 @@ mdro <- function(x, # EUCAST ------------------------------------------------------------------ # Table 5 trans_tbl(3, - which(x$family == "Enterobacteriaceae" + which(x$order == "Enterobacterales" | x$fullname %like% "^Pseudomonas aeruginosa" | x$genus == "Acinetobacter"), COL, @@ -706,7 +714,7 @@ mdro <- function(x, if (is.na(CIP)) CIP <- "missing" # Table 1 - x[which((x$family == "Enterobacteriaceae" | + x[which((x$order == "Enterobacterales" | # following in fact the old Enterobacteriaceae classification x$fullname %like% "^Acinetobacter baumannii") & x[, PIP] == "R" & x[, CTX_or_CAZ] == "R" & @@ -714,7 +722,7 @@ mdro <- function(x, x[, CIP] == "R"), "MDRO"] <- 2 # 2 = 3MRGN - x[which((x$family == "Enterobacteriaceae" | + x[which((x$order == "Enterobacterales" | # following in fact the old Enterobacteriaceae classification x$fullname %like% "^Acinetobacter baumannii") & x[, PIP] == "R" & x[, CTX_or_CAZ] == "R" & @@ -722,7 +730,7 @@ mdro <- function(x, x[, CIP] == "R"), "MDRO"] <- 3 # 3 = 4MRGN, overwrites 3MRGN if applicable - x[which((x$family == "Enterobacteriaceae" | + x[which((x$order == "Enterobacterales" | # following in fact the old Enterobacteriaceae classification x$fullname %like% "^Acinetobacter baumannii") & x[, IPM] == "R" | x[, MEM] == "R"), "MDRO"] <- 3 # 3 = 4MRGN, always when imipenem or meropenem is R @@ -757,17 +765,17 @@ mdro <- function(x, # Table 1 trans_tbl(3, - which(x$family == "Enterobacteriaceae"), + which(x$order == "Enterobacterales"), # following in fact the old Enterobacteriaceae classification c(aminoglycosides, fluoroquinolones), "all") trans_tbl(2, - which(x$family == "Enterobacteriaceae"), + which(x$order == "Enterobacterales"), # following in fact the old Enterobacteriaceae classification carbapenems, "any") trans_tbl(2, - which(x$family == "Enterobacteriaceae"), + which(x$order == "Enterobacterales"), # following in fact the old Enterobacteriaceae classification ESBLs, "all") diff --git a/R/mo_property.R b/R/mo_property.R index c88b75eb..eb9083b2 100755 --- a/R/mo_property.R +++ b/R/mo_property.R @@ -57,7 +57,7 @@ #' mo_kingdom("E. coli") # "Bacteria" #' mo_phylum("E. coli") # "Proteobacteria" #' mo_class("E. coli") # "Gammaproteobacteria" -#' mo_order("E. coli") # "Enterobacteriales" +#' mo_order("E. coli") # "Enterobacterales" () #' mo_family("E. coli") # "Enterobacteriaceae" #' mo_genus("E. coli") # "Escherichia" #' mo_species("E. coli") # "coli" diff --git a/R/sysdata.rda b/R/sysdata.rda index dba065b0..c658d3ee 100644 Binary files a/R/sysdata.rda and b/R/sysdata.rda differ diff --git a/data-raw/eucast_rules.tsv b/data-raw/eucast_rules.tsv index 4bf7db34..cac99db2 100644 --- a/data-raw/eucast_rules.tsv +++ b/data-raw/eucast_rules.tsv @@ -5,13 +5,13 @@ # and all separate EARS-Net letter codes like 'AMC'. They can be separated by comma: 'AMC, fluoroquinolones'. # The 'if_mo_property' column can be any column name from the AMR::microorganisms data set, or "genus_species" or "gramstain". # The like.is.one_of column must be 'like' or 'is' or 'one_of' ('like' will read the 'this_value' column as regular expression) -# The EUCAST guideline contains references to the 'Burkholderia cepacia complex'. All species in this group can be found in: LiPuma J, Curr Opin Pulm Med. 2005 Nov;11(6):528-33. (PMID 16217180). +# The EUCAST guideline contains references to the 'Burkholderia cepacia complex'. All species in this group can be found in: LiPuma J (2005, PMID 16217180). # >>>>> IF YOU WANT TO IMPORT THIS FILE INTO YOUR OWN SOFTWARE, HAVE THE FIRST 10 LINES SKIPPED <<<<< # ------------------------------------------------------------------------------------------------------------------------------- if_mo_property like.is.one_of this_value and_these_antibiotics have_these_values then_change_these_antibiotics to_value reference.rule reference.rule_group -order is Enterobacteriales AMP S AMX S Enterobacteriales (Order) Breakpoints -order is Enterobacteriales AMP I AMX I Enterobacteriales (Order) Breakpoints -order is Enterobacteriales AMP R AMX R Enterobacteriales (Order) Breakpoints +order is Enterobacterales AMP S AMX S Enterobacterales (Order) Breakpoints +order is Enterobacterales AMP I AMX I Enterobacterales (Order) Breakpoints +order is Enterobacterales AMP R AMX R Enterobacterales (Order) Breakpoints genus is Staphylococcus PEN, FOX S AMP, AMX, PIP, TIC S Staphylococcus Breakpoints genus is Staphylococcus PEN, FOX R, S OXA, FLC S Staphylococcus Breakpoints genus is Staphylococcus FOX R all_betalactams R Staphylococcus Breakpoints @@ -109,7 +109,7 @@ genus_species is Kingella kingae ERY S AZM, CLR S Kingella kingae Breakpoints genus_species is Kingella kingae ERY I AZM, CLR I Kingella kingae Breakpoints genus_species is Kingella kingae ERY R AZM, CLR R Kingella kingae Breakpoints genus_species is Kingella kingae TCY S DOX S Kingella kingae Breakpoints -family is Enterobacteriaceae PEN, glycopeptides, FUS, macrolides, LIN, streptogramins, RIF, DAP, LNZ R Table 01: Intrinsic resistance in Enterobacteriaceae Expert Rules +order is Enterobacterales PEN, glycopeptides, FUS, macrolides, LIN, streptogramins, RIF, DAP, LNZ R Table 01: Intrinsic resistance in Enterobacteriaceae Expert Rules fullname like ^Citrobacter (koseri|amalonaticus|sedlakii|farmeri|rodentium) aminopenicillins, TIC R Table 01: Intrinsic resistance in Enterobacteriaceae Expert Rules fullname like ^Citrobacter (freundii|braakii|murliniae|werkmanii|youngae) aminopenicillins, AMC, CZO, FOX R Table 01: Intrinsic resistance in Enterobacteriaceae Expert Rules genus_species is Enterobacter cloacae aminopenicillins, AMC, CZO, FOX R Table 01: Intrinsic resistance in Enterobacteriaceae Expert Rules @@ -177,11 +177,11 @@ genus is .* ERY I AZM, CLR I Table 11: Interpretive rules for macrolides, lincos genus is .* ERY R AZM, CLR R Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins Expert Rules genus is Staphylococcus TOB R KAN, AMK R Table 12: Interpretive rules for aminoglycosides Expert Rules genus is Staphylococcus GEN R aminoglycosides R Table 12: Interpretive rules for aminoglycosides Expert Rules -family is Enterobacteriaceae GEN, TOB I, S GEN R Table 12: Interpretive rules for aminoglycosides Expert Rules -family is Enterobacteriaceae GEN, TOB R, I TOB R Table 12: Interpretive rules for aminoglycosides Expert Rules +order is Enterobacterales GEN, TOB I, S GEN R Table 12: Interpretive rules for aminoglycosides Expert Rules +order is Enterobacterales GEN, TOB R, I TOB R Table 12: Interpretive rules for aminoglycosides Expert Rules genus is Staphylococcus MFX R fluoroquinolones R Table 13: Interpretive rules for quinolones Expert Rules genus_species is Streptococcus pneumoniae MFX R fluoroquinolones R Table 13: Interpretive rules for quinolones Expert Rules -family is Enterobacteriaceae CIP R fluoroquinolones R Table 13: Interpretive rules for quinolones Expert Rules +order is Enterobacterales CIP R fluoroquinolones R Table 13: Interpretive rules for quinolones Expert Rules genus_species is Neisseria gonorrhoeae CIP R fluoroquinolones R Table 13: Interpretive rules for quinolones Expert Rules genus is .* AMC R AMP, AMX R Non-EUCAST: ampicillin = R where amoxicillin/clav acid = R Other rules genus is .* TZP R PIP R Non-EUCAST: piperacillin = R where piperacillin/tazobactam = R Other rules diff --git a/data-raw/reproduction_of_microorganisms.R b/data-raw/reproduction_of_microorganisms.R index ae244a78..8205ba76 100644 --- a/data-raw/reproduction_of_microorganisms.R +++ b/data-raw/reproduction_of_microorganisms.R @@ -663,6 +663,97 @@ MOs <- MOs %>% species_id = ""), ) +# Incorporate new microbial order for Gammaproteobacteria - Adeolu et al. (2016), PMID 27620848 +MOs[which(MOs$family == "Enterobacteriaceae"), "family"] <- "" +MOs[which(MOs$genus %in% c("Escherichia", + "Atlantibacter", + "Biostraticola", + "Buttiauxella", + "Cedecea", + "Citrobacter", + "Cronobacter", + "Enterobacillus", + "Enterobacter", + "Franconibacter", + "Gibbsiella", + "Izhakiella", + "Klebsiella", + "Kluyvera", + "Kosakonia", + "Leclercia", + "Lelliottia", + "Mangrovibacter", + "Pluralibacter", + "Pseudocitrobacter", + "Raoultella", + "Rosenbergiella", + "Saccharobacter", + "Salmonella", + "Shigella", + "Shimwellia", + "Siccibacter", + "Trabulsiella", + "Yokenella")), "family"] <- "Enterobacteriaceae" +MOs[which(MOs$genus %in% c("Erwinia", + "Buchnera", + "Pantoea", + "Phaseolibacter", + "Tatumella", + "Wigglesworthia")), "family"] <- "Erwiniaceae" +MOs[which(MOs$genus %in% c("Pectobacterium", + "Brenneria", + "Dickeya", + "Lonsdalea", + "Sodalis")), "family"] <- "Pectobacteriaceae" +MOs[which(MOs$genus %in% c("Yersinia", + "Chania", + "Ewingella", + "Rahnella", + "Rouxiella", + "Samsonia", + "Serratia")), "family"] <- "Yersiniaceae" +MOs[which(MOs$genus %in% c("Hafnia", + "Edwardsiella", + "Obesumbacterium")), "family"] <- "Hafniaceae" +MOs[which(MOs$genus %in% c("Morganella", + "Arsenophonus", + "Cosenzaea", + "Moellerella", + "Photorhabdus", + "Proteus", + "Providencia", + "Xenorhabdus")), "family"] <- "Morganellaceae" +MOs[which(MOs$genus %in% c("Budvicia", + "Leminorella", + "Pragia")), "family"] <- "Budviciaceae" +MOs[which(MOs$family %in% c("Enterobacteriaceae", + "Erwiniaceae", + "Pectobacteriaceae", + "Yersiniaceae", + "Hafniaceae", + "Morganellaceae", + "Budviciaceae")), "order"] <- "Enterobacterales" +new_families <- MOs %>% + filter(order == "Enterobacterales") %>% + pull(family) %>% + unique() +class(MOs$mo) <- "character" +MOs <- rbind(MOs %>% filter(!(rank == "family" & fullname %in% new_families)), + AMR::microorganisms %>% + filter(family == "Enterobacteriaceae" & rank == "family") %>% + rbind(., ., ., ., ., ., .) %>% + mutate(fullname = new_families, + source = "manually added", + ref = "Adeolu et al., 2016", + family = fullname, mo = paste0("B_[FAM]_", + toupper(abbreviate(new_families, + minlength = 8, + use.classes = TRUE, + method = "both.sides", + strict = FALSE))))) +MOs[which(MOs$order == "Enterobacteriales"), "order"] <- "Enterobacterales" +MOs[which(MOs$fullname == "Enterobacteriales"), "fullname"] <- "Enterobacterales" + MOs <- MOs %>% group_by(kingdom) %>% distinct(fullname, .keep_all = TRUE) %>% diff --git a/data/microorganisms.rda b/data/microorganisms.rda index 281bba24..164d85a0 100644 Binary files a/data/microorganisms.rda and b/data/microorganisms.rda differ diff --git a/docs/404.html b/docs/404.html index 9dd49105..a9c81c96 100644 --- a/docs/404.html +++ b/docs/404.html @@ -84,7 +84,7 @@ AMR (for R) - 0.8.0.9006 + 0.8.0.9007 diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index 7120f5ba..235bfeb6 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -84,7 +84,7 @@ AMR (for R) - 0.8.0.9006 + 0.8.0.9007 diff --git a/docs/articles/index.html b/docs/articles/index.html index 59df090e..1e29a142 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -84,7 +84,7 @@ AMR (for R) - 0.8.0.9006 + 0.8.0.9007 diff --git a/docs/authors.html b/docs/authors.html index 6d9f5b0c..f90b0c5f 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -84,7 +84,7 @@ AMR (for R) - 0.8.0.9006 + 0.8.0.9007 diff --git a/docs/index.html b/docs/index.html index c699cf16..12572cdd 100644 --- a/docs/index.html +++ b/docs/index.html @@ -45,7 +45,7 @@ AMR (for R) - 0.8.0.9006 + 0.8.0.9007 diff --git a/docs/news/index.html b/docs/news/index.html index b648810d..98c6ec10 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -84,7 +84,7 @@ AMR (for R) - 0.8.0.9006 + 0.8.0.9007 @@ -231,11 +231,11 @@ -
+

-AMR 0.8.0.9006 Unreleased +AMR 0.8.0.9007 Unreleased

-

Last updated: 27-Oct-2019

+

Last updated: 30-Oct-2019

New

@@ -250,8 +250,7 @@
  • When running as.rsi() over a data set, it will now print the guideline that will be used if it is not specified by the user
  • Fix for eucast_rules(): Stenotrophomonas maltophilia not interpreted “R” to ceftazidime anymore (following EUCAST v3.1)
  • -
  • Fix in taxonomic info for genera that are in multiple kingdoms, like Proteus -
  • +
  • Adopted Adeolu et al. (2016), PMID 27620848 for the microorganisms data set, which means that the new order Enterobacterales now consists of a part of the existing family Enterobacteriaceae, but that this family has been split into other families as well (like Morganellaceae and Yersiniaceae). Although published in 2016, this information is not yet in the Catalogue of Life version of 2019. All MDRO determinations with mdro() will now use the Enterobacterales order for all guidelines before 2016.
  • Fix for interpreting MIC values with as.rsi() where the input is NA
  • Added “imi” as allowed abbreviation for Imipenem
  • @@ -1321,7 +1320,7 @@ Using as.mo(..., allow_uncertain = 3)

    Contents

diff --git a/docs/reference/microorganisms.html b/docs/reference/microorganisms.html index 34640120..12ce4af1 100644 --- a/docs/reference/microorganisms.html +++ b/docs/reference/microorganisms.html @@ -85,7 +85,7 @@ AMR (for R) - 0.8.0 + 0.8.0.9007
@@ -242,7 +242,7 @@

Format

-

A data.frame with 69,465 observations and 16 variables:

+

A data.frame with 69,447 observations and 16 variables:

mo

ID of microorganism as used by this package

col_id

Catalogue of Life ID

fullname

Full name, like "Escherichia coli"

@@ -264,9 +264,10 @@
  • 11 entries of Streptococcus (beta-haemolytic: groups A, B, C, D, F, G, H, K and unspecified; other: viridans, milleri)

  • 2 entries of Staphylococcus (coagulase-negative [CoNS] and coagulase-positive [CoPS])

  • 3 entries of Trichomonas (Trichomonas vaginalis, and its family and genus)

  • -
  • 1 entry of Blastocystis (Blastocystis hominis), although it officially does not exist (Noel et al. 2005, PMID 15634993)

  • +
  • 1 entry of Blastocystis (Blastocystis hominis), although it officially does not exist (Noel et al. 2005, PMID 15634993)

  • 5 other 'undefined' entries (unknown, unknown Gram negatives, unknown Gram positives, unknown yeast and unknown fungus)

  • -
  • 9,460 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) since the DSMZ contain the latest taxonomic information based on recent publications

  • +
  • 6 families under the Enterobacterales order, according to Adeolu et al. (2016, PMID 27620848), that are not in the Catalogue of Life

  • +
  • 12,600 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) since the DSMZ contain the latest taxonomic information based on recent publications

  • About the records from DSMZ (see source)

    diff --git a/docs/reference/mo_property.html b/docs/reference/mo_property.html index 54645d49..97deaab8 100644 --- a/docs/reference/mo_property.html +++ b/docs/reference/mo_property.html @@ -85,7 +85,7 @@ AMR (for R) - 0.8.0 + 0.8.0.9007
    @@ -356,7 +356,7 @@ This package contains the complete taxonomic tree of almost all microorganisms ( mo_kingdom("E. coli") # "Bacteria" mo_phylum("E. coli") # "Proteobacteria" mo_class("E. coli") # "Gammaproteobacteria" -mo_order("E. coli") # "Enterobacteriales" +mo_order("E. coli") # "Enterobacterales" () mo_family("E. coli") # "Enterobacteriaceae" mo_genus("E. coli") # "Escherichia" mo_species("E. coli") # "coli" diff --git a/man/microorganisms.Rd b/man/microorganisms.Rd index 0f12ecc5..f8f1fbb1 100755 --- a/man/microorganisms.Rd +++ b/man/microorganisms.Rd @@ -4,7 +4,7 @@ \name{microorganisms} \alias{microorganisms} \title{Data set with ~70,000 microorganisms} -\format{A \code{\link{data.frame}} with 69,465 observations and 16 variables: +\format{A \code{\link{data.frame}} with 69,447 observations and 16 variables: \describe{ \item{\code{mo}}{ID of microorganism as used by this package} \item{\code{col_id}}{Catalogue of Life ID} @@ -33,9 +33,10 @@ Manually added were: \item{11 entries of \emph{Streptococcus} (beta-haemolytic: groups A, B, C, D, F, G, H, K and unspecified; other: viridans, milleri)} \item{2 entries of \emph{Staphylococcus} (coagulase-negative [CoNS] and coagulase-positive [CoPS])} \item{3 entries of \emph{Trichomonas} (\emph{Trichomonas vaginalis}, and its family and genus)} - \item{1 entry of \emph{Blastocystis} (\emph{Blastocystis hominis}), although it officially does not exist (Noel et al. 2005, PMID 15634993)} + \item{1 entry of \emph{Blastocystis} (\emph{Blastocystis hominis}), although it officially does not exist (Noel \emph{et al.} 2005, PMID 15634993)} \item{5 other 'undefined' entries (unknown, unknown Gram negatives, unknown Gram positives, unknown yeast and unknown fungus)} - \item{9,460 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) since the DSMZ contain the latest taxonomic information based on recent publications} + \item{6 families under the Enterobacterales order, according to Adeolu \emph{et al.} (2016, PMID 27620848), that are not in the Catalogue of Life} + \item{12,600 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) since the DSMZ contain the latest taxonomic information based on recent publications} } } \section{About the records from DSMZ (see source)}{ diff --git a/man/mo_property.Rd b/man/mo_property.Rd index 208656c3..6ba13943 100644 --- a/man/mo_property.Rd +++ b/man/mo_property.Rd @@ -134,7 +134,7 @@ On our website \url{https://msberends.gitlab.io/AMR} you can find \href{https:// mo_kingdom("E. coli") # "Bacteria" mo_phylum("E. coli") # "Proteobacteria" mo_class("E. coli") # "Gammaproteobacteria" -mo_order("E. coli") # "Enterobacteriales" +mo_order("E. coli") # "Enterobacterales" () mo_family("E. coli") # "Enterobacteriaceae" mo_genus("E. coli") # "Escherichia" mo_species("E. coli") # "coli" diff --git a/tests/testthat/test-misc.R b/tests/testthat/test-misc.R index 9eeec400..af460940 100755 --- a/tests/testthat/test-misc.R +++ b/tests/testthat/test-misc.R @@ -44,6 +44,6 @@ test_that("looking up ab columns works", { expect_warning(generate_warning_abs_missing(c("AMP", "AMX"), any = TRUE)) expect_warning(get_column_abx(example_isolates, hard_dependencies = "FUS")) expect_message(get_column_abx(example_isolates, soft_dependencies = "FUS")) - expect_message(get_column_abx(dplyr::rename(example_isolates, thisone = AMX), amox = "thisone", tmp = "thisone", verbose = TRUE)) + expect_warning(get_column_abx(dplyr::rename(example_isolates, thisone = AMX), amox = "thisone", tmp = "thisone", verbose = TRUE)) expect_warning(get_column_abx(dplyr::rename(example_isolates, thisone = AMX), amox = "thisone", tmp = "thisone", verbose = FALSE)) }) diff --git a/tests/testthat/test-mo_property.R b/tests/testthat/test-mo_property.R index a4a9511b..93b4f3e2 100644 --- a/tests/testthat/test-mo_property.R +++ b/tests/testthat/test-mo_property.R @@ -28,7 +28,7 @@ test_that("mo_property works", { expect_equal(mo_kingdom("Escherichia coli"), "Bacteria") expect_equal(mo_phylum("Escherichia coli"), "Proteobacteria") expect_equal(mo_class("Escherichia coli"), "Gammaproteobacteria") - expect_equal(mo_order("Escherichia coli"), "Enterobacteriales") + expect_equal(mo_order("Escherichia coli"), "Enterobacterales") expect_equal(mo_family("Escherichia coli"), "Enterobacteriaceae") expect_equal(mo_genus("Escherichia coli"), "Escherichia") expect_equal(mo_species("Escherichia coli"), "coli")