(v0.9.0.9005) as.mo for G. species

This commit is contained in:
dr. M.S. (Matthijs) Berends 2019-12-21 10:56:06 +01:00
parent cc8cd043e1
commit ba3ce77f02
21 changed files with 501 additions and 361 deletions

View File

@ -1,6 +1,6 @@
Package: AMR
Version: 0.9.0.9004
Date: 2019-12-20
Version: 0.9.0.9005
Date: 2019-12-21
Title: Antimicrobial Resistance Analysis
Authors@R: c(
person(role = c("aut", "cre"),

View File

@ -1,8 +1,9 @@
# AMR 0.9.0.9004
## <small>Last updated: 20-Dec-2019</small>
# AMR 0.9.0.9005
## <small>Last updated: 21-Dec-2019</small>
### Changes
* Speed improvement for `as.mo()` (and consequently all `mo_*` functions that use `as.mo()` internally)
* Speed improvement for `as.mo()` (and consequently all `mo_*` functions that use `as.mo()` internally), especially for the *G. species* format (G for genus), like *E. coli* and *K penumoniae*
* Input values for `as.disk()` limited to a maximum of 50 millimeters
# AMR 0.9.0

View File

@ -21,12 +21,12 @@
#' Class 'disk'
#'
#' This transforms a vector to a new class [`disk`], which is a growth zone size (around an antibiotic disk) in millimeters between 6 and 99.
#' This transforms a vector to a new class [`disk`], which is a growth zone size (around an antibiotic disk) in millimeters between 6 and 50.
#' @rdname as.disk
#' @param x vector
#' @param na.rm a logical indicating whether missing values should be removed
#' @details Interpret disk values as RSI values with [as.rsi()]. It supports guidelines from EUCAST and CLSI.
#' @return Ordered integer factor with new class [`disk`]
#' @return An [`integer`] with additional new class [`disk`]
#' @aliases disk
#' @export
#' @seealso [as.rsi()]
@ -56,8 +56,8 @@ as.disk <- function(x, na.rm = FALSE) {
# force it to be integer
x <- suppressWarnings(as.integer(x))
# disks can never be less than 9 mm (size of a disk) or more than 50 mm
x[x < 6 | x > 99] <- NA_integer_
# disks can never be less than 6 mm (size of smallest disk) or more than 50 mm
x[x < 6 | x > 50] <- NA_integer_
na_after <- length(x[is.na(x)])
if (na_before != na_after) {

274
R/mo.R
View File

@ -228,7 +228,7 @@ as.mo <- function(x,
& isFALSE(Lancefield)) {
# check previously found results
y <- mo_hist
} else {
# will be checked for mo class in validation and uses exec_as.mo internally if necessary
y <- mo_validate(x = x, property = "mo",
@ -273,7 +273,7 @@ exec_as.mo <- function(x,
disable_mo_history = getOption("AMR_disable_mo_history", FALSE),
debug = FALSE,
reference_data_to_use = microorganismsDT) {
load_AMR_package()
# WHONET: xxx = no growth
@ -391,7 +391,9 @@ exec_as.mo <- function(x,
} else if (all(x %in% reference_data_to_use$mo)) {
# existing mo codes when not looking for property "mo", like mo_genus("B_ESCHR_COL")
y <- reference_data_to_use[prevalence == 1][data.table(mo = x), on = "mo", ..property][[1]]
y <- reference_data_to_use[prevalence == 1][data.table(mo = x),
on = "mo",
..property][[1]]
if (any(is.na(y))) {
y[is.na(y)] <- reference_data_to_use[prevalence == 2][data.table(mo = x[is.na(y)]),
on = "mo",
@ -420,21 +422,29 @@ exec_as.mo <- function(x,
} else if (all(tolower(x) %in% reference_data_to_use$fullname_lower)) {
# we need special treatment for very prevalent full names, they are likely!
# e.g. as.mo("Staphylococcus aureus")
x <- reference_data_to_use[data.table(fullname_lower = tolower(x)), on = "fullname_lower", ..property][[1]]
x <- reference_data_to_use[data.table(fullname_lower = tolower(x)),
on = "fullname_lower",
..property][[1]]
} else if (all(toupper(x) %in% AMR::microorganisms.codes$code)) {
# commonly used MO codes
y <- as.data.table(AMR::microorganisms.codes)[data.table(code = toupper(x)), on = "code", ]
y <- as.data.table(AMR::microorganisms.codes)[data.table(code = toupper(x)),
on = "code", ]
# save them to history
set_mo_history(x, y$mo, 0, force = force_mo_history, disable = disable_mo_history)
x <- reference_data_to_use[data.table(mo = y[["mo"]]), on = "mo", ..property][[1]]
x <- reference_data_to_use[data.table(mo = y[["mo"]]),
on = "mo",
..property][[1]]
} else if (all(x %in% microorganisms.translation$mo_old)) {
# is an old mo code, used in previous versions of this package
old_mo_warning <- TRUE
y <- as.data.table(microorganisms.translation)[data.table(mo_old = x), on = "mo_old", "mo_new"][[1]]
y <- reference_data_to_use[data.table(mo = y), on = "mo", ..property][[1]]
y <- as.data.table(microorganisms.translation)[data.table(mo_old = x),
on = "mo_old", "mo_new"][[1]]
y <- reference_data_to_use[data.table(mo = y),
on = "mo",
..property][[1]]
# don't save to history, as all items are already in microorganisms.translation
x <- y
@ -557,7 +567,7 @@ exec_as.mo <- function(x,
}
progress <- progress_estimated(n = length(x), min_time = 3)
for (i in seq_len(length(x))) {
progress$tick()$print()
@ -580,7 +590,8 @@ exec_as.mo <- function(x,
next
}
found <- reference_data_to_use[mo == toupper(x_backup[i]), ..property][[1]]
found <- reference_data_to_use[mo == toupper(x_backup[i]),
..property][[1]]
# is a valid MO code
if (length(found) > 0) {
x[i] <- found[1L]
@ -590,17 +601,19 @@ exec_as.mo <- function(x,
if (x_backup[i] %in% microorganisms.translation$mo_old) {
# is an old mo code, used in previous versions of this package
old_mo_warning <- TRUE
found <- reference_data_to_use[mo == microorganisms.translation[which(microorganisms.translation$mo_old == x_backup[i]), "mo_new"], ..property][[1]]
found <- reference_data_to_use[mo == microorganisms.translation[which(microorganisms.translation$mo_old == x_backup[i]), "mo_new"],
..property][[1]]
if (length(found) > 0) {
x[i] <- found[1L]
# don't save to history, as all items are already in microorganisms.translation
next
}
}
if (toupper(x_backup_untouched[i]) %in% microorganisms.codes$code) {
# is a WHONET code, like "HA-"
found <- microorganismsDT[mo == microorganisms.codes[which(microorganisms.codes$code == toupper(x_backup_untouched[i])), "mo"][1L], ..property][[1]]
found <- microorganismsDT[mo == microorganisms.codes[which(microorganisms.codes$code == toupper(x_backup_untouched[i])), "mo"][1L],
..property][[1]]
if (length(found) > 0) {
x[i] <- found[1L]
# don't save to history, as all items are already in microorganisms.codes
@ -608,7 +621,8 @@ exec_as.mo <- function(x,
}
}
found <- reference_data_to_use[fullname_lower %in% tolower(c(x_backup[i], x_backup_without_spp[i])), ..property][[1]]
found <- reference_data_to_use[fullname_lower %in% tolower(c(x_backup[i], x_backup_without_spp[i])),
..property][[1]]
# most probable: is exact match in fullname
if (length(found) > 0) {
x[i] <- found[1L]
@ -618,7 +632,20 @@ exec_as.mo <- function(x,
next
}
found <- reference_data_to_use[col_id == x_backup[i], ..property][[1]]
found <- reference_data_to_use[g_species %in% gsub("[^a-z0-9/ \\-]+", "",
tolower(c(x_backup[i], x_backup_without_spp[i]))),
..property][[1]]
# very probable: is G. species
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, disable = disable_mo_history)
}
next
}
found <- reference_data_to_use[col_id == x_backup[i],
..property][[1]]
# is a valid Catalogue of Life ID
if (NROW(found) > 0) {
x[i] <- found[1L]
@ -632,19 +659,22 @@ exec_as.mo <- function(x,
if (any(toupper(c(x_backup[i], x_backup_without_spp[i])) %in% AMR::microorganisms.codes$code)) {
mo_found <- AMR::microorganisms.codes[which(AMR::microorganisms.codes$code %in% toupper(c(x_backup[i], x_backup_without_spp[i]))), "mo"][1L]
if (length(mo_found) > 0) {
x[i] <- microorganismsDT[mo == mo_found, ..property][[1]][1L]
x[i] <- microorganismsDT[mo == mo_found,
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
next
}
}
if (!is.null(reference_df)) {
# self-defined reference
if (x_backup[i] %in% reference_df[, 1]) {
ref_mo <- reference_df[reference_df[, 1] == x_backup[i], "mo"][[1L]]
if (ref_mo %in% microorganismsDT[, mo]) {
x[i] <- microorganismsDT[mo == ref_mo, ..property][[1]][1L]
x[i] <- microorganismsDT[mo == ref_mo,
..property][[1]][1L]
next
} else {
warning("Value '", x_backup[i], "' was found in reference_df, but '", ref_mo, "' is not a valid MO code.", call. = FALSE)
@ -660,7 +690,8 @@ exec_as.mo <- function(x,
if (tolower(x_backup_without_spp[i]) %in% c("other", "none", "unknown")) {
# empty and nonsense values, ignore without warning
x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]]
x[i] <- microorganismsDT[mo == "UNKNOWN",
..property][[1]]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -671,7 +702,8 @@ exec_as.mo <- function(x,
if (nchar(gsub("[^a-zA-Z]", "", x_trimmed[i])) < 3
& !x_backup_without_spp[i] %like_case% "[Oo]?(26|103|104|104|111|121|145|157)") {
# fewer than 3 chars and not looked for species, add as failure
x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]]
x[i] <- microorganismsDT[mo == "UNKNOWN",
..property][[1]]
if (initial_search == TRUE) {
failures <- c(failures, x_backup[i])
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
@ -689,7 +721,8 @@ exec_as.mo <- function(x,
if (!is.na(x_trimmed[i])) {
if (toupper(x_backup_without_spp[i]) %in% c("MRSA", "MSSA", "VISA", "VRSA")
| x_backup_without_spp[i] %like_case% " (mrsa|mssa|visa|vrsa) ") {
x[i] <- microorganismsDT[mo == "B_STPHY_AURS", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_STPHY_AURS",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -697,7 +730,8 @@ exec_as.mo <- function(x,
}
if (toupper(x_backup_without_spp[i]) %in% c("MRSE", "MSSE")
| x_backup_without_spp[i] %like_case% " (mrse|msse) ") {
x[i] <- microorganismsDT[mo == "B_STPHY_EPDR", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_STPHY_EPDR",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -706,7 +740,8 @@ exec_as.mo <- function(x,
if (toupper(x_backup_without_spp[i]) == "VRE"
| x_backup_without_spp[i] %like_case% " vre "
| x_backup_without_spp[i] %like_case% "(enterococci|enterokok|enterococo)[a-z]*?$") {
x[i] <- microorganismsDT[mo == "B_ENTRC", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_ENTRC",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -727,7 +762,8 @@ exec_as.mo <- function(x,
if (toupper(x_backup_without_spp[i]) %in% c("AIEC", "ATEC", "DAEC", "EAEC", "EHEC", "EIEC", "EPEC", "ETEC", "NMEC", "STEC", "UPEC")
# also support O-antigens of E. coli: O26, O103, O104, O111, O121, O145, O157
| x_backup_without_spp[i] %like_case% "o?(26|103|104|111|121|145|157)") {
x[i] <- microorganismsDT[mo == "B_ESCHR_COLI", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_ESCHR_COLI",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -736,7 +772,8 @@ exec_as.mo <- function(x,
if (toupper(x_backup_without_spp[i]) == "MRPA"
| x_backup_without_spp[i] %like_case% " mrpa ") {
# multi resistant P. aeruginosa
x[i] <- microorganismsDT[mo == "B_PSDMN_ARGN", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_PSDMN_ARGN",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -744,7 +781,8 @@ exec_as.mo <- function(x,
}
if (toupper(x_backup_without_spp[i]) == "CRSM") {
# co-trim resistant S. maltophilia
x[i] <- microorganismsDT[mo == "B_STNTR_MLTP", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_STNTR_MLTP",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -753,7 +791,8 @@ exec_as.mo <- function(x,
if (toupper(x_backup_without_spp[i]) %in% c("PISP", "PRSP", "VISP", "VRSP")
| x_backup_without_spp[i] %like_case% " (pisp|prsp|visp|vrsp) ") {
# peni I, peni R, vanco I, vanco R: S. pneumoniae
x[i] <- microorganismsDT[mo == "B_STRPT_PNMN", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_STRPT_PNMN",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -761,7 +800,8 @@ exec_as.mo <- function(x,
}
if (x_backup_without_spp[i] %like_case% "^g[abcdfghk]s$") {
# Streptococci, like GBS = Group B Streptococci (B_STRPT_GRPB)
x[i] <- microorganismsDT[mo == toupper(gsub("g([abcdfghk])s", "B_STRPT_GRP\\1", x_backup_without_spp[i])), ..property][[1]][1L]
x[i] <- microorganismsDT[mo == toupper(gsub("g([abcdfghk])s", "B_STRPT_GRP\\1", x_backup_without_spp[i])),
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -769,7 +809,8 @@ exec_as.mo <- function(x,
}
if (x_backup_without_spp[i] %like_case% "(streptococ|streptokok).* [abcdfghk]$") {
# Streptococci in different languages, like "estreptococos grupo B"
x[i] <- microorganismsDT[mo == toupper(gsub(".*(streptococ|streptokok|estreptococ).* ([abcdfghk])$", "B_STRPT_GRP\\2", x_backup_without_spp[i])), ..property][[1]][1L]
x[i] <- microorganismsDT[mo == toupper(gsub(".*(streptococ|streptokok|estreptococ).* ([abcdfghk])$", "B_STRPT_GRP\\2", x_backup_without_spp[i])),
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -777,7 +818,8 @@ exec_as.mo <- function(x,
}
if (x_backup_without_spp[i] %like_case% "group [abcdfghk] (streptococ|streptokok|estreptococ)") {
# Streptococci in different languages, like "Group A Streptococci"
x[i] <- microorganismsDT[mo == toupper(gsub(".*group ([abcdfghk]) (streptococ|streptokok|estreptococ).*", "B_STRPT_GRP\\1", x_backup_without_spp[i])), ..property][[1]][1L]
x[i] <- microorganismsDT[mo == toupper(gsub(".*group ([abcdfghk]) (streptococ|streptokok|estreptococ).*", "B_STRPT_GRP\\1", x_backup_without_spp[i])),
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -785,7 +827,8 @@ exec_as.mo <- function(x,
}
if (x_backup_without_spp[i] %like_case% "haemoly.*strept") {
# Haemolytic streptococci in different languages
x[i] <- microorganismsDT[mo == "B_STRPT_HAEM", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_STRPT_HAEM",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -796,7 +839,8 @@ exec_as.mo <- function(x,
| x_trimmed[i] %like_case% "[ck]oagulas[ea] negatie?[vf]"
| x_backup_without_spp[i] %like_case% "[ck]o?ns[^a-z]?$") {
# coerce S. coagulase negative
x[i] <- microorganismsDT[mo == "B_STPHY_CONS", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_STPHY_CONS",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -806,7 +850,8 @@ exec_as.mo <- function(x,
| x_trimmed[i] %like_case% "[ck]oagulas[ea] positie?[vf]"
| x_backup_without_spp[i] %like_case% "[ck]o?ps[^a-z]?$") {
# coerce S. coagulase positive
x[i] <- microorganismsDT[mo == "B_STPHY_COPS", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_STPHY_COPS",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -817,7 +862,8 @@ exec_as.mo <- function(x,
| x_backup_without_spp[i] %like_case% "strepto.* mil+er+i"
| x_backup_without_spp[i] %like_case% "mgs[^a-z]?$") {
# Milleri Group Streptococcus (MGS)
x[i] <- microorganismsDT[mo == "B_STRPT_MILL", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_STRPT_MILL",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -827,7 +873,8 @@ exec_as.mo <- function(x,
| x_backup_without_spp[i] %like_case% "strepto.* viridans"
| x_backup_without_spp[i] %like_case% "vgs[^a-z]?$") {
# Viridans Group Streptococcus (VGS)
x[i] <- microorganismsDT[mo == "B_STRPT_VIRI", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_STRPT_VIRI",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -837,7 +884,8 @@ exec_as.mo <- function(x,
| x_backup_without_spp[i] %like_case% "negatie?[vf]"
| x_trimmed[i] %like_case% "gram[ -]?neg.*") {
# coerce Gram negatives
x[i] <- microorganismsDT[mo == "B_GRAMN", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_GRAMN",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -847,7 +895,8 @@ exec_as.mo <- function(x,
| x_backup_without_spp[i] %like_case% "positie?[vf]"
| x_trimmed[i] %like_case% "gram[ -]?pos.*") {
# coerce Gram positives
x[i] <- microorganismsDT[mo == "B_GRAMP", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_GRAMP",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -855,7 +904,8 @@ exec_as.mo <- function(x,
}
if (x_backup_without_spp[i] %like_case% "mycoba[ck]teri.[nm]?$") {
# coerce Gram positives
x[i] <- microorganismsDT[mo == "B_MYCBC", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_MYCBC",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -865,14 +915,16 @@ exec_as.mo <- function(x,
if (x_backup_without_spp[i] %like_case% "salmonella [a-z]+ ?.*") {
if (x_backup_without_spp[i] %like_case% "salmonella group") {
# Salmonella Group A to Z, just return S. species for now
x[i] <- microorganismsDT[mo == "B_SLMNL", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_SLMNL",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
next
} else if (grepl("[sS]almonella [A-Z][a-z]+ ?.*", x_backup[i], ignore.case = FALSE)) {
# Salmonella with capital letter species like "Salmonella Goettingen" - they're all S. enterica
x[i] <- microorganismsDT[mo == "B_SLMNL_ENTR", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_SLMNL_ENTR",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -887,7 +939,8 @@ exec_as.mo <- function(x,
# trivial names known to the field:
if ("meningococcus" %like_case% x_trimmed[i]) {
# coerce Neisseria meningitidis
x[i] <- microorganismsDT[mo == "B_NESSR_MNNG", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_NESSR_MNNG",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -895,7 +948,8 @@ exec_as.mo <- function(x,
}
if ("gonococcus" %like_case% x_trimmed[i]) {
# coerce Neisseria gonorrhoeae
x[i] <- microorganismsDT[mo == "B_NESSR_GNRR", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_NESSR_GNRR",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -903,7 +957,8 @@ exec_as.mo <- function(x,
}
if ("pneumococcus" %like_case% x_trimmed[i]) {
# coerce Streptococcus penumoniae
x[i] <- microorganismsDT[mo == "B_STRPT_PNMN", ..property][[1]][1L]
x[i] <- microorganismsDT[mo == "B_STRPT_PNMN",
..property][[1]][1L]
if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
}
@ -928,7 +983,8 @@ exec_as.mo <- function(x,
# if only genus is available, return only genus
if (all(!c(x[i], b.x_trimmed) %like_case% " ")) {
found <- data_to_check[fullname_lower %in% c(h.x_species, i.x_trimmed_species), ..property][[1]]
found <- data_to_check[fullname_lower %in% c(h.x_species, i.x_trimmed_species),
..property][[1]]
if (length(found) > 0) {
x[i] <- found[1L]
if (initial_search == TRUE) {
@ -937,7 +993,8 @@ exec_as.mo <- function(x,
return(x[i])
}
if (nchar(g.x_backup_without_spp) >= 6) {
found <- data_to_check[fullname_lower %like_case% paste0("^", unregex(g.x_backup_without_spp), "[a-z]+"), ..property][[1]]
found <- data_to_check[fullname_lower %like_case% paste0("^", unregex(g.x_backup_without_spp), "[a-z]+"),
..property][[1]]
if (length(found) > 0) {
x[i] <- found[1L]
if (initial_search == TRUE) {
@ -951,7 +1008,8 @@ exec_as.mo <- function(x,
# allow no codes less than 4 characters long, was already checked for WHONET earlier
if (nchar(g.x_backup_without_spp) < 4) {
x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]]
x[i] <- microorganismsDT[mo == "UNKNOWN",
..property][[1]]
if (initial_search == TRUE) {
failures <- c(failures, a.x_backup)
set_mo_history(a.x_backup, get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
@ -960,36 +1018,42 @@ exec_as.mo <- function(x,
}
# try probable: trimmed version of fullname ----
found <- data_to_check[fullname_lower %in% tolower(g.x_backup_without_spp), ..property][[1]]
found <- data_to_check[fullname_lower %in% tolower(g.x_backup_without_spp),
..property][[1]]
if (length(found) > 0) {
return(found[1L])
}
# try any match keeping spaces ----
found <- data_to_check[fullname_lower %like_case% d.x_withspaces_start_end, ..property][[1]]
found <- data_to_check[fullname_lower %like_case% d.x_withspaces_start_end,
..property][[1]]
if (length(found) > 0 & nchar(g.x_backup_without_spp) >= 6) {
return(found[1L])
}
# try any match keeping spaces, not ending with $ ----
found <- data_to_check[fullname_lower %like_case% paste0(trimws(e.x_withspaces_start_only), " "), ..property][[1]]
found <- data_to_check[fullname_lower %like_case% paste0(trimws(e.x_withspaces_start_only), " "),
..property][[1]]
if (length(found) > 0) {
return(found[1L])
}
found <- data_to_check[fullname_lower %like_case% e.x_withspaces_start_only, ..property][[1]]
found <- data_to_check[fullname_lower %like_case% e.x_withspaces_start_only,
..property][[1]]
if (length(found) > 0 & nchar(g.x_backup_without_spp) >= 6) {
return(found[1L])
}
# try any match keeping spaces, not start with ^ ----
found <- data_to_check[fullname_lower %like_case% paste0(" ", trimws(f.x_withspaces_end_only)), ..property][[1]]
found <- data_to_check[fullname_lower %like_case% paste0(" ", trimws(f.x_withspaces_end_only)),
..property][[1]]
if (length(found) > 0) {
return(found[1L])
}
# try a trimmed version
found <- data_to_check[fullname_lower %like_case% b.x_trimmed
| fullname_lower %like_case% c.x_trimmed_without_group, ..property][[1]]
| fullname_lower %like_case% c.x_trimmed_without_group,
..property][[1]]
if (length(found) > 0 & nchar(g.x_backup_without_spp) >= 6) {
return(found[1L])
}
@ -1004,7 +1068,8 @@ exec_as.mo <- function(x,
g.x_backup_without_spp %>% substr(1, x_length / 2),
".* ",
g.x_backup_without_spp %>% substr((x_length / 2) + 1, x_length))
found <- data_to_check[fullname_lower %like_case% x_split, ..property][[1]]
found <- data_to_check[fullname_lower %like_case% x_split,
..property][[1]]
if (length(found) > 0) {
return(found[1L])
}
@ -1012,7 +1077,8 @@ exec_as.mo <- function(x,
# try fullname without start and without nchar limit of >= 6 ----
# like "K. pneu rhino" >> "Klebsiella pneumoniae (rhinoscleromatis)" = KLEPNERH
found <- data_to_check[fullname_lower %like_case% e.x_withspaces_start_only, ..property][[1]]
found <- data_to_check[fullname_lower %like_case% e.x_withspaces_start_only,
..property][[1]]
if (length(found) > 0) {
return(found[1L])
}
@ -1031,7 +1097,8 @@ exec_as.mo <- function(x,
if (property == "ref") {
x[i] <- found[1, ref]
} else {
x[i] <- microorganismsDT[col_id == found[1, col_id_new], ..property][[1]]
x[i] <- microorganismsDT[col_id == found[1, col_id_new],
..property][[1]]
}
options(mo_renamed_last_run = found[1, fullname])
was_renamed(name_old = found[1, fullname],
@ -1077,7 +1144,8 @@ exec_as.mo <- function(x,
# mo_ref("Chlamydophila psittaci) = "Everett et al., 1999"
x <- found[1, ref]
} else {
x <- microorganismsDT[col_id == found[1, col_id_new], ..property][[1]]
x <- microorganismsDT[col_id == found[1, col_id_new],
..property][[1]]
}
was_renamed(name_old = found[1, fullname],
name_new = microorganismsDT[col_id == found[1, col_id_new], fullname],
@ -1109,7 +1177,8 @@ exec_as.mo <- function(x,
}
if (!empty_result(found)) {
found_result <- found
found <- reference_data_to_use[mo == found, ..property][[1]]
found <- reference_data_to_use[mo == found,
..property][[1]]
uncertainties <<- rbind(uncertainties,
format_uncertainty_as_df(uncertainty_level = now_checks_for_uncertainty_level,
input = a.x_backup,
@ -1135,7 +1204,8 @@ exec_as.mo <- function(x,
message("Running '", paste(b.x_trimmed, "species"), "'")
}
# not when input is like Genustext, because then Neospora would lead to Actinokineospora
found <- uncertain.reference_data_to_use[fullname_lower %like_case% paste(b.x_trimmed, "species"), ..property][[1]]
found <- uncertain.reference_data_to_use[fullname_lower %like_case% paste(b.x_trimmed, "species"),
..property][[1]]
if (length(found) > 0) {
x[i] <- found[1L]
uncertainties <<- rbind(uncertainties,
@ -1167,7 +1237,8 @@ exec_as.mo <- function(x,
}
if (!empty_result(found) & nchar(g.x_backup_without_spp) >= 6) {
found_result <- found
found <- reference_data_to_use[mo == found, ..property][[1]]
found <- reference_data_to_use[mo == found,
..property][[1]]
uncertainties <<- rbind(uncertainties,
format_uncertainty_as_df(uncertainty_level = now_checks_for_uncertainty_level,
input = a.x_backup,
@ -1194,7 +1265,8 @@ exec_as.mo <- function(x,
}
if (!empty_result(found) & nchar(g.x_backup_without_spp) >= 6) {
found_result <- found
found <- reference_data_to_use[mo == found, ..property][[1]]
found <- reference_data_to_use[mo == found,
..property][[1]]
uncertainties <<- rbind(uncertainties,
format_uncertainty_as_df(uncertainty_level = now_checks_for_uncertainty_level,
input = a.x_backup,
@ -1228,7 +1300,8 @@ exec_as.mo <- function(x,
}
if (!empty_result(found)) {
found_result <- found
found <- reference_data_to_use[mo == found, ..property][[1]]
found <- reference_data_to_use[mo == found,
..property][[1]]
uncertainties <<- rbind(uncertainties,
format_uncertainty_as_df(uncertainty_level = now_checks_for_uncertainty_level,
input = a.x_backup,
@ -1260,7 +1333,8 @@ exec_as.mo <- function(x,
}
if (!empty_result(found)) {
found_result <- found
found <- reference_data_to_use[mo == found, ..property][[1]]
found <- reference_data_to_use[mo == found,
..property][[1]]
uncertainties <<- rbind(uncertainties,
format_uncertainty_as_df(uncertainty_level = now_checks_for_uncertainty_level,
input = a.x_backup,
@ -1280,7 +1354,8 @@ exec_as.mo <- function(x,
if (b.x_trimmed %like_case% "yeast") {
found <- "F_YEAST"
found_result <- found
found <- microorganismsDT[mo == found, ..property][[1]]
found <- microorganismsDT[mo == found,
..property][[1]]
uncertainties <<- rbind(uncertainties,
format_uncertainty_as_df(uncertainty_level = now_checks_for_uncertainty_level,
input = a.x_backup,
@ -1293,7 +1368,8 @@ exec_as.mo <- function(x,
if (b.x_trimmed %like_case% "(fungus|fungi)" & !b.x_trimmed %like_case% "fungiphrya") {
found <- "F_FUNGUS"
found_result <- found
found <- microorganismsDT[mo == found, ..property][[1]]
found <- microorganismsDT[mo == found,
..property][[1]]
uncertainties <<- rbind(uncertainties,
format_uncertainty_as_df(uncertainty_level = now_checks_for_uncertainty_level,
input = a.x_backup,
@ -1322,7 +1398,8 @@ exec_as.mo <- function(x,
}
if (!empty_result(found)) {
found_result <- found
found <- reference_data_to_use[mo == found_result[1L], ..property][[1]]
found <- reference_data_to_use[mo == found_result[1L],
..property][[1]]
# uncertainty level 2 only if searched part contains a space (otherwise it will be found with lvl 3)
if (x_strip_collapsed %like_case% " ") {
uncertainties <<- rbind(uncertainties,
@ -1362,7 +1439,8 @@ exec_as.mo <- function(x,
}
if (!empty_result(found)) {
found_result <- found
found <- reference_data_to_use[mo == found, ..property][[1]]
found <- reference_data_to_use[mo == found,
..property][[1]]
uncertainties <<- rbind(uncertainties,
format_uncertainty_as_df(uncertainty_level = now_checks_for_uncertainty_level,
input = a.x_backup,
@ -1393,7 +1471,8 @@ exec_as.mo <- function(x,
}
if (!empty_result(found)) {
found_result <- found
found <- reference_data_to_use[mo == found, ..property][[1]]
found <- reference_data_to_use[mo == found,
..property][[1]]
uncertainties <<- rbind(uncertainties,
format_uncertainty_as_df(uncertainty_level = now_checks_for_uncertainty_level,
input = a.x_backup,
@ -1417,7 +1496,8 @@ exec_as.mo <- function(x,
if (nrow(found) > 0) {
found_result <- found[["mo"]]
if (!empty_result(found_result) & nchar(g.x_backup_without_spp) >= 6) {
found <- reference_data_to_use[mo == found_result[1L], ..property][[1]]
found <- reference_data_to_use[mo == found_result[1L],
..property][[1]]
uncertainties <<- rbind(uncertainties,
format_uncertainty_as_df(uncertainty_level = now_checks_for_uncertainty_level,
input = a.x_backup,
@ -1525,7 +1605,8 @@ exec_as.mo <- function(x,
}
# no results found: make them UNKNOWN ----
x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]]
x[i] <- microorganismsDT[mo == "UNKNOWN",
..property][[1]]
if (initial_search == TRUE) {
failures <- c(failures, x_backup[i])
set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history, disable = disable_mo_history)
@ -1586,56 +1667,76 @@ exec_as.mo <- function(x,
"saccharolyticus", "saprophyticus", "sciuri",
"stepanovicii", "simulans", "succinus",
"vitulinus", "warneri", "xylosus")
| (species == "schleiferi" & subspecies %in% c("schleiferi", "")), ..property][[1]]
| (species == "schleiferi" & subspecies %in% c("schleiferi", "")),
..property][[1]]
CoPS <- MOs_staph[species %in% c("simiae", "agnetis",
"delphini", "lutrae",
"hyicus", "intermedius",
"pseudintermedius", "pseudointermedius",
"schweitzeri", "argenteus")
| (species == "schleiferi" & subspecies == "coagulans"), ..property][[1]]
| (species == "schleiferi" & subspecies == "coagulans"),
..property][[1]]
# warn when species found that are not in Becker (2014, PMID 25278577) and Becker (2019, PMID 30872103)
post_Becker <- c("argensis", "caeli", "cornubiensis", "edaphicus")
if (any(x %in% MOs_staph[species %in% post_Becker, ..property][[1]])) {
if (any(x %in% MOs_staph[species %in% post_Becker,
..property][[1]])) {
warning("Becker ", italic("et al."), " (2014, 2019) does not contain these species named after their publication: ",
italic(paste("S.",
sort(mo_species(unique(x[x %in% MOs_staph[species %in% post_Becker, ..property][[1]]]))),
sort(mo_species(unique(x[x %in% MOs_staph[species %in% post_Becker,
..property][[1]]]))),
collapse = ", ")),
".",
call. = FALSE,
immediate. = TRUE)
}
x[x %in% CoNS] <- microorganismsDT[mo == "B_STPHY_CONS", ..property][[1]][1L]
x[x %in% CoPS] <- microorganismsDT[mo == "B_STPHY_COPS", ..property][[1]][1L]
x[x %in% CoNS] <- microorganismsDT[mo == "B_STPHY_CONS",
..property][[1]][1L]
x[x %in% CoPS] <- microorganismsDT[mo == "B_STPHY_COPS",
..property][[1]][1L]
if (Becker == "all") {
x[x %in% microorganismsDT[mo %like_case% "^B_STPHY_AURS", ..property][[1]]] <- microorganismsDT[mo == "B_STPHY_COPS", ..property][[1]][1L]
x[x %in% microorganismsDT[mo %like_case% "^B_STPHY_AURS",
..property][[1]]] <- microorganismsDT[mo == "B_STPHY_COPS",
..property][[1]][1L]
}
}
# Lancefield ----
if (Lancefield == TRUE | Lancefield == "all") {
# group A - S. pyogenes
x[x == microorganismsDT[mo == "B_STRPT_PYGN", ..property][[1]][1L]] <- microorganismsDT[mo == "B_STRPT_GRPA", ..property][[1]][1L]
x[x == microorganismsDT[mo == "B_STRPT_PYGN",
..property][[1]][1L]] <- microorganismsDT[mo == "B_STRPT_GRPA",
..property][[1]][1L]
# group B - S. agalactiae
x[x == microorganismsDT[mo == "B_STRPT_AGLC", ..property][[1]][1L]] <- microorganismsDT[mo == "B_STRPT_GRPB", ..property][[1]][1L]
x[x == microorganismsDT[mo == "B_STRPT_AGLC",
..property][[1]][1L]] <- microorganismsDT[mo == "B_STRPT_GRPB",
..property][[1]][1L]
# group C
S_groupC <- microorganismsDT %>% filter(genus == "Streptococcus",
species %in% c("equisimilis", "equi",
"zooepidemicus", "dysgalactiae")) %>%
pull(property)
x[x %in% S_groupC] <- microorganismsDT[mo == "B_STRPT_GRPC", ..property][[1]][1L]
x[x %in% S_groupC] <- microorganismsDT[mo == "B_STRPT_GRPC",
..property][[1]][1L]
if (Lancefield == "all") {
# all Enterococci
x[x %like% "^(Enterococcus|B_ENTRC)"] <- microorganismsDT[mo == "B_STRPT_GRPD", ..property][[1]][1L]
x[x %like% "^(Enterococcus|B_ENTRC)"] <- microorganismsDT[mo == "B_STRPT_GRPD",
..property][[1]][1L]
}
# group F - S. anginosus
x[x == microorganismsDT[mo == "B_STRPT_ANGN", ..property][[1]][1L]] <- microorganismsDT[mo == "B_STRPT_GRPF", ..property][[1]][1L]
x[x == microorganismsDT[mo == "B_STRPT_ANGN",
..property][[1]][1L]] <- microorganismsDT[mo == "B_STRPT_GRPF",
..property][[1]][1L]
# group H - S. sanguinis
x[x == microorganismsDT[mo == "B_STRPT_SNGN", ..property][[1]][1L]] <- microorganismsDT[mo == "B_STRPT_GRPH", ..property][[1]][1L]
x[x == microorganismsDT[mo == "B_STRPT_SNGN",
..property][[1]][1L]] <- microorganismsDT[mo == "B_STRPT_GRPH",
..property][[1]][1L]
# group K - S. salivarius
x[x == microorganismsDT[mo == "B_STRPT_SLVR", ..property][[1]][1L]] <- microorganismsDT[mo == "B_STRPT_GRPK", ..property][[1]][1L]
x[x == microorganismsDT[mo == "B_STRPT_SLVR",
..property][[1]][1L]] <- microorganismsDT[mo == "B_STRPT_GRPK",
..property][[1]][1L]
}
# Wrap up ----------------------------------------------------------------
@ -1805,7 +1906,8 @@ as.data.frame.mo <- function(x, ...) {
"[<-.mo" <- function(i, j, ..., value) {
y <- NextMethod()
attributes(y) <- attributes(i)
class_integrity_check(y, "microorganism code", c(as.character(AMR::microorganisms$mo), as.character(microorganisms.translation$mo_old)))
class_integrity_check(y, "microorganism code", c(as.character(AMR::microorganisms$mo),
as.character(microorganisms.translation$mo_old)))
}
#' @exportMethod [[<-.mo
#' @export
@ -1813,7 +1915,8 @@ as.data.frame.mo <- function(x, ...) {
"[[<-.mo" <- function(i, j, ..., value) {
y <- NextMethod()
attributes(y) <- attributes(i)
class_integrity_check(y, "microorganism code", c(as.character(AMR::microorganisms$mo), as.character(microorganisms.translation$mo_old)))
class_integrity_check(y, "microorganism code", c(as.character(AMR::microorganisms$mo),
as.character(microorganisms.translation$mo_old)))
}
#' @exportMethod c.mo
#' @export
@ -1821,7 +1924,8 @@ as.data.frame.mo <- function(x, ...) {
c.mo <- function(x, ...) {
y <- NextMethod()
attributes(y) <- attributes(x)
class_integrity_check(y, "microorganism code", c(as.character(AMR::microorganisms$mo), as.character(microorganisms.translation$mo_old)))
class_integrity_check(y, "microorganism code", c(as.character(AMR::microorganisms$mo),
as.character(microorganisms.translation$mo_old)))
}
#' @rdname as.mo

34
R/zzz.R
View File

@ -21,21 +21,18 @@
#' @importFrom data.table as.data.table setkey
.onLoad <- function(libname, pkgname) {
# packageStartupMessage("Loading taxonomic reference data")
# get new functions not available in older versions of R
backports::import(pkgname)
# register data
microorganisms.oldDT <- as.data.table(AMR::microorganisms.old)
# for fullname_lower: keep only dots, letters, numbers, slashes, spaces and dashes
microorganisms.oldDT$fullname_lower <- gsub("[^.a-z0-9/ \\-]+", "", tolower(microorganisms.oldDT$fullname))
setkey(microorganisms.oldDT, prevalence, fullname)
assign(x = "microorganismsDT",
value = make_DT(),
envir = asNamespace("AMR"))
assign(x = "microorganisms.oldDT",
value = microorganisms.oldDT,
value = make_oldDT(),
envir = asNamespace("AMR"))
assign(x = "mo_codes_v0.5.0",
@ -62,7 +59,9 @@ make_DT <- function() {
# work with Viridans Group Streptococci, etc.
tolower(trimws(ifelse(genus == "",
fullname,
paste(genus, species, subspecies)))))) %>%
paste(genus, species, subspecies))))),
# add a column with only "e coli" like combinations
g_species = gsub("^([a-z])[a-z]+ ([a-z]+) ?.*", "\\1 \\2", fullname_lower)) %>%
as.data.table()
# so arrange data on prevalence first, then kingdom, then full name
@ -73,6 +72,25 @@ make_DT <- function() {
microorganismsDT
}
#' @importFrom data.table as.data.table setkey
#' @importFrom dplyr %>% mutate
make_oldDT <- function() {
microorganisms.oldDT <- AMR::microorganisms.old %>%
mutate(
# for fullname_lower: keep only dots, letters,
# numbers, slashes, spaces and dashes
fullname_lower = gsub("[^.a-z0-9/ \\-]+", "", tolower(fullname)),
# add a column with only "e coli" like combinations
g_species = gsub("^([a-z])[a-z]+ ([a-z]+) ?.*", "\\1 \\2", fullname_lower)) %>%
as.data.table()
# so arrange data on prevalence first, then full name
setkey(microorganisms.oldDT,
prevalence,
fullname)
microorganisms.oldDT
}
make_trans_tbl <- function() {
# conversion of old MO codes from v0.5.0 (ITIS) to later versions (Catalogue of Life)
c(B_ACHRMB = "B_ACHRM", B_ANNMA = "B_ACTNS", B_ACLLS = "B_ALCYC",

View File

@ -84,7 +84,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="https://msberends.gitlab.io/AMR/index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9004</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9005</span>
</span>
</div>

View File

@ -84,7 +84,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9004</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9005</span>
</span>
</div>

View File

@ -41,7 +41,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9004</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9005</span>
</span>
</div>
@ -187,7 +187,7 @@
<h1>How to conduct AMR analysis</h1>
<h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">20 December 2019</h4>
<h4 class="date">21 December 2019</h4>
<div class="hidden name"><code>AMR.Rmd</code></div>
@ -196,19 +196,21 @@
<p><strong>Note:</strong> values on this page will change with every website update since they are based on randomly created values and the page was written in <a href="https://rmarkdown.rstudio.com/">R Markdown</a>. However, the methodology remains unchanged. This page was generated on 20 December 2019.</p>
<p><strong>Note:</strong> values on this page will change with every website update since they are based on randomly created values and the page was written in <a href="https://rmarkdown.rstudio.com/">R Markdown</a>. However, the methodology remains unchanged. This page was generated on 21 December 2019.</p>
<div id="introduction" class="section level1">
<h1 class="hasAnchor">
<a href="#introduction" class="anchor"></a>Introduction</h1>
<p>Conducting antimicrobial resistance analysis unfortunately requires in-depth knowledge from different scientific fields, which makes it hard to do right. At least, it requires:</p>
<ul>
<li>Good questions (always start with these!)</li>
<li>A thorough understanding of both (clinical) epidemiology and (clinical) microbiology, to understand the clinical and epidemiological relevance of results and their pharmaceutical implications</li>
<li>Experience with data analysis with microbiological tests and their results (MIC/RSI values)</li>
<li>Availability of the biological taxonomy of microorganisms</li>
<li>Available (inter-)national guidelines and methods to apply them</li>
<li>A thorough understanding of (clinical) epidemiology, to understand the clinical and epidemiological relevance and possible bias of results</li>
<li>A thorough understanding of (clinical) microbiology/infectious diseases, to understand which microorganisms are causal to which infections and the implications of pharmaceutical treatment</li>
<li>Experience with data analysis with microbiological tests and their results, to understand the determination and limitations of MIC values and their interpretations to RSI values</li>
<li>Availability of the biological taxonomy of microorganisms and probably normalisation factors for pharmaceuticals, such as defined daily doses (DDD)</li>
<li>Available (inter-)national guidelines, and profound methods to apply them</li>
</ul>
<p>Of course, we cannot instantly provide you with knowledge and experience. But with this <code>AMR</code> pacakge, we aimed at providing (1) tools to simplify antimicrobial resistance data cleaning/analysis, (2) methods to easily incorporate international guidelines and (3) scientifically reliable reference data. The <code>AMR</code> package enables standardised and reproducible antimicrobial resistance analyses, including the application of evidence-based rules, determination of first isolates, translation of various codes for microorganisms and antimicrobial agents, determination of (multi-drug) resistant microorganisms, and calculation of antimicrobial resistance, prevalence and future trends.</p>
<p>Of course, we cannot instantly provide you with knowledge and experience. But with this <code>AMR</code> package, we aimed at providing (1) tools to simplify antimicrobial resistance data cleaning, transformation and analysis, (2) methods to easily incorporate international guidelines and (3) scientifically reliable reference data, including the requirements mentioned above.</p>
<p>The <code>AMR</code> package enables standardised and reproducible antimicrobial resistance analysis, with the application of evidence-based rules, determination of first isolates, translation of various codes for microorganisms and antimicrobial agents, determination of (multi-drug) resistant microorganisms, and calculation of antimicrobial resistance, prevalence and future trends.</p>
</div>
<div id="preparation" class="section level1">
<h1 class="hasAnchor">
@ -225,21 +227,21 @@
</tr></thead>
<tbody>
<tr class="odd">
<td align="center">2019-12-20</td>
<td align="center">2019-12-21</td>
<td align="center">abcd</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">S</td>
</tr>
<tr class="even">
<td align="center">2019-12-20</td>
<td align="center">2019-12-21</td>
<td align="center">abcd</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">R</td>
</tr>
<tr class="odd">
<td align="center">2019-12-20</td>
<td align="center">2019-12-21</td>
<td align="center">efgh</td>
<td align="center">Escherichia coli</td>
<td align="center">R</td>
@ -334,10 +336,10 @@
</tr></thead>
<tbody>
<tr class="odd">
<td align="center">2015-01-13</td>
<td align="center">Y8</td>
<td align="center">2011-10-17</td>
<td align="center">V10</td>
<td align="center">Hospital D</td>
<td align="center">Escherichia coli</td>
<td align="center">Staphylococcus aureus</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
@ -345,9 +347,31 @@
<td align="center">F</td>
</tr>
<tr class="even">
<td align="center">2010-04-08</td>
<td align="center">O8</td>
<td align="center">2017-05-17</td>
<td align="center">R1</td>
<td align="center">Hospital B</td>
<td align="center">Klebsiella pneumoniae</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="odd">
<td align="center">2015-07-05</td>
<td align="center">J5</td>
<td align="center">Hospital B</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td>
</tr>
<tr class="even">
<td align="center">2012-01-01</td>
<td align="center">R10</td>
<td align="center">Hospital C</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">S</td>
@ -356,49 +380,27 @@
<td align="center">F</td>
</tr>
<tr class="odd">
<td align="center">2010-05-11</td>
<td align="center">W2</td>
<td align="center">2014-07-18</td>
<td align="center">T6</td>
<td align="center">Hospital A</td>
<td align="center">Escherichia coli</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="even">
<td align="center">2011-11-23</td>
<td align="center">I9</td>
<td align="center">2016-07-17</td>
<td align="center">K1</td>
<td align="center">Hospital C</td>
<td align="center">Klebsiella pneumoniae</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td>
</tr>
<tr class="odd">
<td align="center">2011-03-28</td>
<td align="center">D3</td>
<td align="center">Hospital B</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">I</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td>
</tr>
<tr class="even">
<td align="center">2013-11-16</td>
<td align="center">P8</td>
<td align="center">Hospital D</td>
<td align="center">Streptococcus pneumoniae</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
</tbody>
</table>
<p>Now, lets start the cleaning and the analysis!</p>
@ -419,8 +421,8 @@
#
# Item Count Percent Cum. Count Cum. Percent
# --- ----- ------- -------- ----------- -------------
# 1 M 10,341 51.71% 10,341 51.71%
# 2 F 9,659 48.30% 20,000 100.00%</code></pre>
# 1 M 10,402 52.01% 10,402 52.01%
# 2 F 9,598 47.99% 20,000 100.00%</code></pre>
<p>So, we can draw at least two conclusions immediately. From a data scientists perspective, the data looks clean: only values <code>M</code> and <code>F</code>. From a researchers perspective: there are slightly more men. Nothing we didnt already know.</p>
<p>The data is already quite clean, but we still need to transform some variables. The <code>bacteria</code> column now consists of text, and we want to add more variables based on microbial IDs later on. So, we will transform this column to valid IDs. The <code><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate()</a></code> function of the <code>dplyr</code> package makes this really easy:</p>
<div class="sourceCode" id="cb12"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb12-1" data-line-number="1">data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span></a>
@ -435,8 +437,8 @@
<a class="sourceLine" id="cb14-3" data-line-number="3"><span class="co"># Other rules by this AMR package</span></a>
<a class="sourceLine" id="cb14-4" data-line-number="4"><span class="co"># Non-EUCAST: inherit amoxicillin results for unavailable ampicillin (no changes)</span></a>
<a class="sourceLine" id="cb14-5" data-line-number="5"><span class="co"># Non-EUCAST: inherit ampicillin results for unavailable amoxicillin (no changes)</span></a>
<a class="sourceLine" id="cb14-6" data-line-number="6"><span class="co"># Non-EUCAST: set amoxicillin/clav acid = S where ampicillin = S (2,942 values changed)</span></a>
<a class="sourceLine" id="cb14-7" data-line-number="7"><span class="co"># Non-EUCAST: set ampicillin = R where amoxicillin/clav acid = R (159 values changed)</span></a>
<a class="sourceLine" id="cb14-6" data-line-number="6"><span class="co"># Non-EUCAST: set amoxicillin/clav acid = S where ampicillin = S (2,972 values changed)</span></a>
<a class="sourceLine" id="cb14-7" data-line-number="7"><span class="co"># Non-EUCAST: set ampicillin = R where amoxicillin/clav acid = R (139 values changed)</span></a>
<a class="sourceLine" id="cb14-8" data-line-number="8"><span class="co"># Non-EUCAST: set piperacillin = R where piperacillin/tazobactam = R (no changes)</span></a>
<a class="sourceLine" id="cb14-9" data-line-number="9"><span class="co"># Non-EUCAST: set piperacillin/tazobactam = S where piperacillin = S (no changes)</span></a>
<a class="sourceLine" id="cb14-10" data-line-number="10"><span class="co"># Non-EUCAST: set trimethoprim = R where trimethoprim/sulfa = R (no changes)</span></a>
@ -461,14 +463,14 @@
<a class="sourceLine" id="cb14-29" data-line-number="29"><span class="co"># Pasteurella multocida (no changes)</span></a>
<a class="sourceLine" id="cb14-30" data-line-number="30"><span class="co"># Staphylococcus (no changes)</span></a>
<a class="sourceLine" id="cb14-31" data-line-number="31"><span class="co"># Streptococcus groups A, B, C, G (no changes)</span></a>
<a class="sourceLine" id="cb14-32" data-line-number="32"><span class="co"># Streptococcus pneumoniae (942 values changed)</span></a>
<a class="sourceLine" id="cb14-32" data-line-number="32"><span class="co"># Streptococcus pneumoniae (959 values changed)</span></a>
<a class="sourceLine" id="cb14-33" data-line-number="33"><span class="co"># Viridans group streptococci (no changes)</span></a>
<a class="sourceLine" id="cb14-34" data-line-number="34"><span class="co"># </span></a>
<a class="sourceLine" id="cb14-35" data-line-number="35"><span class="co"># EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)</span></a>
<a class="sourceLine" id="cb14-36" data-line-number="36"><span class="co"># Table 01: Intrinsic resistance in Enterobacteriaceae (1,222 values changed)</span></a>
<a class="sourceLine" id="cb14-36" data-line-number="36"><span class="co"># Table 01: Intrinsic resistance in Enterobacteriaceae (1,333 values changed)</span></a>
<a class="sourceLine" id="cb14-37" data-line-number="37"><span class="co"># Table 02: Intrinsic resistance in non-fermentative Gram-negative bacteria (no changes)</span></a>
<a class="sourceLine" id="cb14-38" data-line-number="38"><span class="co"># Table 03: Intrinsic resistance in other Gram-negative bacteria (no changes)</span></a>
<a class="sourceLine" id="cb14-39" data-line-number="39"><span class="co"># Table 04: Intrinsic resistance in Gram-positive bacteria (2,709 values changed)</span></a>
<a class="sourceLine" id="cb14-39" data-line-number="39"><span class="co"># Table 04: Intrinsic resistance in Gram-positive bacteria (2,723 values changed)</span></a>
<a class="sourceLine" id="cb14-40" data-line-number="40"><span class="co"># Table 08: Interpretive rules for B-lactam agents and Gram-positive cocci (no changes)</span></a>
<a class="sourceLine" id="cb14-41" data-line-number="41"><span class="co"># Table 09: Interpretive rules for B-lactam agents and Gram-negative rods (no changes)</span></a>
<a class="sourceLine" id="cb14-42" data-line-number="42"><span class="co"># Table 11: Interpretive rules for macrolides, lincosamides, and streptogramins (no changes)</span></a>
@ -476,15 +478,15 @@
<a class="sourceLine" id="cb14-44" data-line-number="44"><span class="co"># Table 13: Interpretive rules for quinolones (no changes)</span></a>
<a class="sourceLine" id="cb14-45" data-line-number="45"><span class="co"># </span></a>
<a class="sourceLine" id="cb14-46" data-line-number="46"><span class="co"># -------------------------------------------------------------------------------</span></a>
<a class="sourceLine" id="cb14-47" data-line-number="47"><span class="co"># EUCAST rules affected 6,398 out of 20,000 rows, making a total of 7,974 edits</span></a>
<a class="sourceLine" id="cb14-47" data-line-number="47"><span class="co"># EUCAST rules affected 6,551 out of 20,000 rows, making a total of 8,126 edits</span></a>
<a class="sourceLine" id="cb14-48" data-line-number="48"><span class="co"># =&gt; added 0 test results</span></a>
<a class="sourceLine" id="cb14-49" data-line-number="49"><span class="co"># </span></a>
<a class="sourceLine" id="cb14-50" data-line-number="50"><span class="co"># =&gt; changed 7,974 test results</span></a>
<a class="sourceLine" id="cb14-51" data-line-number="51"><span class="co"># - 95 test results changed from S to I</span></a>
<a class="sourceLine" id="cb14-52" data-line-number="52"><span class="co"># - 4,603 test results changed from S to R</span></a>
<a class="sourceLine" id="cb14-53" data-line-number="53"><span class="co"># - 1,165 test results changed from I to S</span></a>
<a class="sourceLine" id="cb14-54" data-line-number="54"><span class="co"># - 334 test results changed from I to R</span></a>
<a class="sourceLine" id="cb14-55" data-line-number="55"><span class="co"># - 1,777 test results changed from R to S</span></a>
<a class="sourceLine" id="cb14-50" data-line-number="50"><span class="co"># =&gt; changed 8,126 test results</span></a>
<a class="sourceLine" id="cb14-51" data-line-number="51"><span class="co"># - 115 test results changed from S to I</span></a>
<a class="sourceLine" id="cb14-52" data-line-number="52"><span class="co"># - 4,709 test results changed from S to R</span></a>
<a class="sourceLine" id="cb14-53" data-line-number="53"><span class="co"># - 1,179 test results changed from I to S</span></a>
<a class="sourceLine" id="cb14-54" data-line-number="54"><span class="co"># - 330 test results changed from I to R</span></a>
<a class="sourceLine" id="cb14-55" data-line-number="55"><span class="co"># - 1,793 test results changed from R to S</span></a>
<a class="sourceLine" id="cb14-56" data-line-number="56"><span class="co"># -------------------------------------------------------------------------------</span></a>
<a class="sourceLine" id="cb14-57" data-line-number="57"><span class="co"># </span></a>
<a class="sourceLine" id="cb14-58" data-line-number="58"><span class="co"># Use eucast_rules(..., verbose = TRUE) (on your original data) to get a data.frame with all specified edits instead.</span></a></code></pre></div>
@ -512,8 +514,8 @@
<a class="sourceLine" id="cb16-3" data-line-number="3"><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `bacteria` as input for `col_mo`.</span></a>
<a class="sourceLine" id="cb16-4" data-line-number="4"><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `date` as input for `col_date`.</span></a>
<a class="sourceLine" id="cb16-5" data-line-number="5"><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></a>
<a class="sourceLine" id="cb16-6" data-line-number="6"><span class="co"># =&gt; Found 5,647 first isolates (28.2% of total)</span></a></code></pre></div>
<p>So only 28.2% is suitable for resistance analysis! We can now filter on it with the <code><a href="https://dplyr.tidyverse.org/reference/filter.html">filter()</a></code> function, also from the <code>dplyr</code> package:</p>
<a class="sourceLine" id="cb16-6" data-line-number="6"><span class="co"># =&gt; Found 5,691 first isolates (28.5% of total)</span></a></code></pre></div>
<p>So only 28.5% is suitable for resistance analysis! We can now filter on it with the <code><a href="https://dplyr.tidyverse.org/reference/filter.html">filter()</a></code> function, also from the <code>dplyr</code> package:</p>
<div class="sourceCode" id="cb17"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb17-1" data-line-number="1">data_1st &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb17-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(first <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>)</a></code></pre></div>
<p>For future use, the above two syntaxes can be shortened with the <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> function:</p>
@ -523,7 +525,7 @@
<div id="first-weighted-isolates" class="section level2">
<h2 class="hasAnchor">
<a href="#first-weighted-isolates" class="anchor"></a>First <em>weighted</em> isolates</h2>
<p>We made a slight twist to the CLSI algorithm, to take into account the antimicrobial susceptibility profile. Have a look at all isolates of patient T5, sorted on date:</p>
<p>We made a slight twist to the CLSI algorithm, to take into account the antimicrobial susceptibility profile. Have a look at all isolates of patient Y10, sorted on date:</p>
<table class="table">
<thead><tr class="header">
<th align="center">isolate</th>
@ -539,54 +541,54 @@
<tbody>
<tr class="odd">
<td align="center">1</td>
<td align="center">2010-02-25</td>
<td align="center">T5</td>
<td align="center">2010-06-10</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">2</td>
<td align="center">2010-03-02</td>
<td align="center">T5</td>
<td align="center">2010-09-27</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
</tr>
<tr class="odd">
<td align="center">3</td>
<td align="center">2010-04-02</td>
<td align="center">T5</td>
<td align="center">2010-11-27</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">4</td>
<td align="center">2010-06-08</td>
<td align="center">T5</td>
<td align="center">2010-12-06</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">FALSE</td>
</tr>
<tr class="odd">
<td align="center">5</td>
<td align="center">2010-06-20</td>
<td align="center">T5</td>
<td align="center">2011-02-18</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
@ -594,30 +596,30 @@
</tr>
<tr class="even">
<td align="center">6</td>
<td align="center">2010-09-13</td>
<td align="center">T5</td>
<td align="center">2011-04-05</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">FALSE</td>
</tr>
<tr class="odd">
<td align="center">7</td>
<td align="center">2010-10-06</td>
<td align="center">T5</td>
<td align="center">2011-05-29</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">8</td>
<td align="center">2010-11-19</td>
<td align="center">T5</td>
<td align="center">2011-06-04</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
@ -627,29 +629,29 @@
</tr>
<tr class="odd">
<td align="center">9</td>
<td align="center">2010-12-06</td>
<td align="center">T5</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">10</td>
<td align="center">2010-12-07</td>
<td align="center">T5</td>
<td align="center">2011-06-14</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">10</td>
<td align="center">2011-11-02</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
</tr>
</tbody>
</table>
<p>Only 1 isolates are marked as first according to CLSI guideline. But when reviewing the antibiogram, it is obvious that some isolates are absolutely different strains and should be included too. This is why we weigh isolates, based on their antibiogram. The <code><a href="../reference/key_antibiotics.html">key_antibiotics()</a></code> function adds a vector with 18 key antibiotics: 6 broad spectrum ones, 6 small spectrum for Gram negatives and 6 small spectrum for Gram positives. These can be defined by the user.</p>
<p>Only 2 isolates are marked as first according to CLSI guideline. But when reviewing the antibiogram, it is obvious that some isolates are absolutely different strains and should be included too. This is why we weigh isolates, based on their antibiogram. The <code><a href="../reference/key_antibiotics.html">key_antibiotics()</a></code> function adds a vector with 18 key antibiotics: 6 broad spectrum ones, 6 small spectrum for Gram negatives and 6 small spectrum for Gram positives. These can be defined by the user.</p>
<p>If a column exists with a name like key(…)ab the <code><a href="../reference/first_isolate.html">first_isolate()</a></code> function will automatically use it and determine the first weighted isolates. Mind the NOTEs in below output:</p>
<div class="sourceCode" id="cb19"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb19-1" data-line-number="1">data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb19-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span>(<span class="dt">keyab =</span> <span class="kw"><a href="../reference/key_antibiotics.html">key_antibiotics</a></span>(.)) <span class="op">%&gt;%</span><span class="st"> </span></a>
@ -660,7 +662,7 @@
<a class="sourceLine" id="cb19-7" data-line-number="7"><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></a>
<a class="sourceLine" id="cb19-8" data-line-number="8"><span class="co"># </span><span class="al">NOTE</span><span class="co">: Using column `keyab` as input for `col_keyantibiotics`. Use col_keyantibiotics = FALSE to prevent this.</span></a>
<a class="sourceLine" id="cb19-9" data-line-number="9"><span class="co"># [Criterion] Inclusion based on key antibiotics, ignoring I</span></a>
<a class="sourceLine" id="cb19-10" data-line-number="10"><span class="co"># =&gt; Found 15,050 first weighted isolates (75.3% of total)</span></a></code></pre></div>
<a class="sourceLine" id="cb19-10" data-line-number="10"><span class="co"># =&gt; Found 15,020 first weighted isolates (75.1% of total)</span></a></code></pre></div>
<table class="table">
<thead><tr class="header">
<th align="center">isolate</th>
@ -677,23 +679,23 @@
<tbody>
<tr class="odd">
<td align="center">1</td>
<td align="center">2010-02-25</td>
<td align="center">T5</td>
<td align="center">2010-06-10</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">TRUE</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">2</td>
<td align="center">2010-03-02</td>
<td align="center">T5</td>
<td align="center">2010-09-27</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
@ -701,68 +703,68 @@
</tr>
<tr class="odd">
<td align="center">3</td>
<td align="center">2010-04-02</td>
<td align="center">T5</td>
<td align="center">2010-11-27</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">4</td>
<td align="center">2010-06-08</td>
<td align="center">T5</td>
<td align="center">2010-12-06</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td>
</tr>
<tr class="odd">
<td align="center">5</td>
<td align="center">2010-06-20</td>
<td align="center">T5</td>
<td align="center">2011-02-18</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">6</td>
<td align="center">2010-09-13</td>
<td align="center">T5</td>
<td align="center">2011-04-05</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">7</td>
<td align="center">2010-10-06</td>
<td align="center">T5</td>
<td align="center">2011-05-29</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">8</td>
<td align="center">2010-11-19</td>
<td align="center">T5</td>
<td align="center">2011-06-04</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
@ -773,35 +775,35 @@
</tr>
<tr class="odd">
<td align="center">9</td>
<td align="center">2010-12-06</td>
<td align="center">T5</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">10</td>
<td align="center">2010-12-07</td>
<td align="center">T5</td>
<td align="center">2011-06-14</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">TRUE</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">10</td>
<td align="center">2011-11-02</td>
<td align="center">Y10</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr>
</tbody>
</table>
<p>Instead of 1, now 7 isolates are flagged. In total, 75.3% of all isolates are marked first weighted - 47.0% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.</p>
<p>Instead of 2, now 9 isolates are flagged. In total, 75.1% of all isolates are marked first weighted - 46.6% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.</p>
<p>As with <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code>, theres a shortcut for this new algorithm too:</p>
<div class="sourceCode" id="cb20"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb20-1" data-line-number="1">data_1st &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb20-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_weighted_isolate</a></span>()</a></code></pre></div>
<p>So we end up with 15,050 isolates for analysis.</p>
<p>So we end up with 15,020 isolates for analysis.</p>
<p>We can remove unneeded columns:</p>
<div class="sourceCode" id="cb21"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb21-1" data-line-number="1">data_1st &lt;-<span class="st"> </span>data_1st <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb21-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(<span class="op">-</span><span class="kw"><a href="https://rdrr.io/r/base/c.html">c</a></span>(first, keyab))</a></code></pre></div>
@ -827,24 +829,24 @@
<tbody>
<tr class="odd">
<td>2</td>
<td align="center">2010-04-08</td>
<td align="center">O8</td>
<td align="center">2017-05-17</td>
<td align="center">R1</td>
<td align="center">Hospital B</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">B_KLBSL_PNMN</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
<td align="center">Gram-negative</td>
<td align="center">Escherichia</td>
<td align="center">coli</td>
<td align="center">Klebsiella</td>
<td align="center">pneumoniae</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td>3</td>
<td align="center">2010-05-11</td>
<td align="center">W2</td>
<td>9</td>
<td align="center">2016-05-07</td>
<td align="center">N8</td>
<td align="center">Hospital A</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">R</td>
@ -858,67 +860,67 @@
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td>4</td>
<td align="center">2011-11-23</td>
<td align="center">I9</td>
<td align="center">Hospital C</td>
<td align="center">B_KLBSL_PNMN</td>
<td align="center">R</td>
<td>11</td>
<td align="center">2015-11-13</td>
<td align="center">U7</td>
<td align="center">Hospital B</td>
<td align="center">B_STPHY_AURS</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td>
<td align="center">Gram-negative</td>
<td align="center">Klebsiella</td>
<td align="center">pneumoniae</td>
<td align="center">S</td>
<td align="center">F</td>
<td align="center">Gram-positive</td>
<td align="center">Staphylococcus</td>
<td align="center">aureus</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td>5</td>
<td align="center">2011-03-28</td>
<td align="center">D3</td>
<td align="center">Hospital B</td>
<td align="center">B_ESCHR_COLI</td>
<td align="center">S</td>
<td align="center">S</td>
<td>14</td>
<td align="center">2011-08-27</td>
<td align="center">C10</td>
<td align="center">Hospital C</td>
<td align="center">B_STPHY_AURS</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">M</td>
<td align="center">Gram-negative</td>
<td align="center">Escherichia</td>
<td align="center">coli</td>
<td align="center">Gram-positive</td>
<td align="center">Staphylococcus</td>
<td align="center">aureus</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td>6</td>
<td align="center">2013-11-16</td>
<td align="center">P8</td>
<td align="center">Hospital D</td>
<td align="center">B_STRPT_PNMN</td>
<td align="center">R</td>
<td>15</td>
<td align="center">2013-10-17</td>
<td align="center">R10</td>
<td align="center">Hospital B</td>
<td align="center">B_STPHY_AURS</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
<td align="center">Gram-positive</td>
<td align="center">Streptococcus</td>
<td align="center">pneumoniae</td>
<td align="center">Staphylococcus</td>
<td align="center">aureus</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td>7</td>
<td align="center">2014-12-19</td>
<td align="center">Q5</td>
<td align="center">Hospital B</td>
<td align="center">B_ESCHR_COLI</td>
<td>16</td>
<td align="center">2011-10-01</td>
<td align="center">I6</td>
<td align="center">Hospital A</td>
<td align="center">B_STRPT_PNMN</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
<td align="center">Gram-negative</td>
<td align="center">Escherichia</td>
<td align="center">coli</td>
<td align="center">R</td>
<td align="center">R</td>
<td align="center">M</td>
<td align="center">Gram-positive</td>
<td align="center">Streptococcus</td>
<td align="center">pneumoniae</td>
<td align="center">TRUE</td>
</tr>
</tbody>
@ -940,7 +942,7 @@
<div class="sourceCode" id="cb24"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb24-1" data-line-number="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>(genus, species)</a></code></pre></div>
<p><strong>Frequency table</strong></p>
<p>Class: character<br>
Length: 15,050 (of which NA: 0 = 0%)<br>
Length: 15,020 (of which NA: 0 = 0%)<br>
Unique: 4</p>
<p>Shortest: 16<br>
Longest: 24</p>
@ -957,33 +959,33 @@ Longest: 24</p>
<tr class="odd">
<td align="left">1</td>
<td align="left">Escherichia coli</td>
<td align="right">7,510</td>
<td align="right">49.90%</td>
<td align="right">7,510</td>
<td align="right">49.90%</td>
<td align="right">7,478</td>
<td align="right">49.79%</td>
<td align="right">7,478</td>
<td align="right">49.79%</td>
</tr>
<tr class="even">
<td align="left">2</td>
<td align="left">Staphylococcus aureus</td>
<td align="right">3,786</td>
<td align="right">25.16%</td>
<td align="right">11,296</td>
<td align="right">75.06%</td>
<td align="right">3,691</td>
<td align="right">24.57%</td>
<td align="right">11,169</td>
<td align="right">74.36%</td>
</tr>
<tr class="odd">
<td align="left">3</td>
<td align="left">Streptococcus pneumoniae</td>
<td align="right">2,294</td>
<td align="right">15.24%</td>
<td align="right">13,590</td>
<td align="right">90.30%</td>
<td align="right">2,306</td>
<td align="right">15.35%</td>
<td align="right">13,475</td>
<td align="right">89.71%</td>
</tr>
<tr class="even">
<td align="left">4</td>
<td align="left">Klebsiella pneumoniae</td>
<td align="right">1,460</td>
<td align="right">9.70%</td>
<td align="right">15,050</td>
<td align="right">1,545</td>
<td align="right">10.29%</td>
<td align="right">15,020</td>
<td align="right">100.00%</td>
</tr>
</tbody>
@ -995,7 +997,7 @@ Longest: 24</p>
<p>The functions <code><a href="../reference/proportion.html">resistance()</a></code> and <code><a href="../reference/proportion.html">susceptibility()</a></code> can be used to calculate antimicrobial resistance or susceptibility. For more specific analyses, the functions <code><a href="../reference/proportion.html">proportion_S()</a></code>, <code><a href="../reference/proportion.html">proportion_SI()</a></code>, <code><a href="../reference/proportion.html">proportion_I()</a></code>, <code><a href="../reference/proportion.html">proportion_IR()</a></code> and <code><a href="../reference/proportion.html">proportion_R()</a></code> can be used to determine the proportion of a specific antimicrobial outcome.</p>
<p>As per the EUCAST guideline of 2019, we calculate resistance as the proportion of R (<code><a href="../reference/proportion.html">proportion_R()</a></code>, equal to <code><a href="../reference/proportion.html">resistance()</a></code>) and susceptibility as the proportion of S and I (<code><a href="../reference/proportion.html">proportion_SI()</a></code>, equal to <code><a href="../reference/proportion.html">susceptibility()</a></code>). These functions can be used on their own:</p>
<div class="sourceCode" id="cb25"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb25-1" data-line-number="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/proportion.html">resistance</a></span>(AMX)</a>
<a class="sourceLine" id="cb25-2" data-line-number="2"><span class="co"># [1] 0.4623256</span></a></code></pre></div>
<a class="sourceLine" id="cb25-2" data-line-number="2"><span class="co"># [1] 0.4637816</span></a></code></pre></div>
<p>Or can be used in conjuction with <code><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by()</a></code> and <code><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise()</a></code>, both from the <code>dplyr</code> package:</p>
<div class="sourceCode" id="cb26"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb26-1" data-line-number="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb26-2" data-line-number="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(hospital) <span class="op">%&gt;%</span><span class="st"> </span></a>
@ -1008,19 +1010,19 @@ Longest: 24</p>
<tbody>
<tr class="odd">
<td align="center">Hospital A</td>
<td align="center">0.4637522</td>
<td align="center">0.4687360</td>
</tr>
<tr class="even">
<td align="center">Hospital B</td>
<td align="center">0.4602655</td>
<td align="center">0.4664905</td>
</tr>
<tr class="odd">
<td align="center">Hospital C</td>
<td align="center">0.4760000</td>
<td align="center">0.4576649</td>
</tr>
<tr class="even">
<td align="center">Hospital D</td>
<td align="center">0.4536218</td>
<td align="center">0.4561813</td>
</tr>
</tbody>
</table>
@ -1038,23 +1040,23 @@ Longest: 24</p>
<tbody>
<tr class="odd">
<td align="center">Hospital A</td>
<td align="center">0.4637522</td>
<td align="center">4552</td>
<td align="center">0.4687360</td>
<td align="center">4478</td>
</tr>
<tr class="even">
<td align="center">Hospital B</td>
<td align="center">0.4602655</td>
<td align="center">5197</td>
<td align="center">0.4664905</td>
<td align="center">5297</td>
</tr>
<tr class="odd">
<td align="center">Hospital C</td>
<td align="center">0.4760000</td>
<td align="center">2250</td>
<td align="center">0.4576649</td>
<td align="center">2244</td>
</tr>
<tr class="even">
<td align="center">Hospital D</td>
<td align="center">0.4536218</td>
<td align="center">3051</td>
<td align="center">0.4561813</td>
<td align="center">3001</td>
</tr>
</tbody>
</table>
@ -1074,27 +1076,27 @@ Longest: 24</p>
<tbody>
<tr class="odd">
<td align="center">Escherichia</td>
<td align="center">0.9227696</td>
<td align="center">0.8909454</td>
<td align="center">0.9920107</td>
<td align="center">0.9259160</td>
<td align="center">0.8915485</td>
<td align="center">0.9933137</td>
</tr>
<tr class="even">
<td align="center">Klebsiella</td>
<td align="center">0.9191781</td>
<td align="center">0.9061644</td>
<td align="center">0.9917808</td>
<td align="center">0.9177994</td>
<td align="center">0.8990291</td>
<td align="center">0.9967638</td>
</tr>
<tr class="odd">
<td align="center">Staphylococcus</td>
<td align="center">0.9186476</td>
<td align="center">0.9199683</td>
<td align="center">0.9915478</td>
<td align="center">0.9244107</td>
<td align="center">0.9260363</td>
<td align="center">0.9943105</td>
</tr>
<tr class="even">
<td align="center">Streptococcus</td>
<td align="center">0.6129032</td>
<td align="center">0.6183868</td>
<td align="center">0.0000000</td>
<td align="center">0.6129032</td>
<td align="center">0.6183868</td>
</tr>
</tbody>
</table>

Binary file not shown.

Before

Width:  |  Height:  |  Size: 64 KiB

After

Width:  |  Height:  |  Size: 64 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 51 KiB

After

Width:  |  Height:  |  Size: 51 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 102 KiB

After

Width:  |  Height:  |  Size: 102 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 83 KiB

After

Width:  |  Height:  |  Size: 83 KiB

View File

@ -84,7 +84,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9004</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9005</span>
</span>
</div>

View File

@ -84,7 +84,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9004</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9005</span>
</span>
</div>

View File

@ -45,7 +45,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9004</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9005</span>
</span>
</div>

View File

@ -84,7 +84,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9004</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9005</span>
</span>
</div>
@ -231,19 +231,21 @@
</div>
<div id="amr-0-9-0-9004" class="section level1">
<div id="amr-0-9-0-9005" class="section level1">
<h1 class="page-header">
<a href="#amr-0-9-0-9004" class="anchor"></a>AMR 0.9.0.9004<small> Unreleased </small>
<a href="#amr-0-9-0-9005" class="anchor"></a>AMR 0.9.0.9005<small> Unreleased </small>
</h1>
<div id="last-updated-20-dec-2019" class="section level2">
<div id="last-updated-21-dec-2019" class="section level2">
<h2 class="hasAnchor">
<a href="#last-updated-20-dec-2019" class="anchor"></a><small>Last updated: 20-Dec-2019</small>
<a href="#last-updated-21-dec-2019" class="anchor"></a><small>Last updated: 21-Dec-2019</small>
</h2>
<div id="changes" class="section level3">
<h3 class="hasAnchor">
<a href="#changes" class="anchor"></a>Changes</h3>
<ul>
<li>Speed improvement for <code><a href="../reference/as.mo.html">as.mo()</a></code> (and consequently all <code>mo_*</code> functions that use <code><a href="../reference/as.mo.html">as.mo()</a></code> internally)</li>
<li>Speed improvement for <code><a href="../reference/as.mo.html">as.mo()</a></code> (and consequently all <code>mo_*</code> functions that use <code><a href="../reference/as.mo.html">as.mo()</a></code> internally), especially for the <em>G. species</em> format (G for genus), like <em>E. coli</em> and <em>K penumoniae</em>
</li>
<li>Input values for <code><a href="../reference/as.disk.html">as.disk()</a></code> limited to a maximum of 50 millimeters</li>
</ul>
</div>
</div>
@ -1407,7 +1409,7 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<div id="tocnav">
<h2>Contents</h2>
<ul class="nav nav-pills nav-stacked">
<li><a href="#amr-0-9-0-9004">0.9.0.9004</a></li>
<li><a href="#amr-0-9-0-9005">0.9.0.9005</a></li>
<li><a href="#amr-0-9-0">0.9.0</a></li>
<li><a href="#amr-0-8-0">0.8.0</a></li>
<li><a href="#amr-0-7-1">0.7.1</a></li>

View File

@ -51,7 +51,7 @@
<script src="../extra.js"></script>
<meta property="og:title" content="Class 'disk' — as.disk" />
<meta property="og:description" content="This transforms a vector to a new class disk, which is a growth zone size (around an antibiotic disk) in millimeters between 6 and 99." />
<meta property="og:description" content="This transforms a vector to a new class disk, which is a growth zone size (around an antibiotic disk) in millimeters between 6 and 50." />
<meta property="og:image" content="https://msberends.gitlab.io/AMR/logo.png" />
<meta name="twitter:card" content="summary" />
@ -85,7 +85,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9005</span>
</span>
</div>
@ -234,7 +234,7 @@
</div>
<div class="ref-description">
<p>This transforms a vector to a new class <code>disk</code>, which is a growth zone size (around an antibiotic disk) in millimeters between 6 and 99.</p>
<p>This transforms a vector to a new class <code>disk</code>, which is a growth zone size (around an antibiotic disk) in millimeters between 6 and 50.</p>
</div>
<pre class="usage"><span class='fu'>as.disk</span>(<span class='no'>x</span>, <span class='kw'>na.rm</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
@ -256,7 +256,7 @@
<h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2>
<p>Ordered integer factor with new class <code>disk</code></p>
<p>An <code><a href='https://rdrr.io/r/base/integer.html'>integer</a></code> with additional new class <code>disk</code></p>
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p>Interpret disk values as RSI values with <code><a href='as.rsi.html'>as.rsi()</a></code>. It supports guidelines from EUCAST and CLSI.</p>
@ -297,7 +297,7 @@
<footer>
<div class="copyright">
<p>Developed by <a href='https://www.rug.nl/staff/m.s.berends/'>Matthijs S. Berends</a>, <a href='https://www.rug.nl/staff/c.f.luz/'>Christian F. Luz</a>, <a href='https://www.rug.nl/staff/a.w.friedrich/'>Alex W. Friedrich</a>, <a href='https://www.rug.nl/staff/b.sinha/'>Bhanu N. M. Sinha</a>, <a href='https://www.rug.nl/staff/c.j.albers/'>Casper J. Albers</a>, <a href='https://www.rug.nl/staff/c.glasner/'>Corinna Glasner</a>.</p>
<p>Developed by <a href='https://www.rug.nl/staff/m.s.berends/'>Matthijs S Berends</a>, <a href='https://www.rug.nl/staff/c.f.luz/'>Christian F Luz</a>, <a href='https://www.rug.nl/staff/a.w.friedrich/'>Alexander W Friedrich</a>, <a href='https://www.rug.nl/staff/b.sinha/'>Bhanu N M Sinha</a>, <a href='https://www.rug.nl/staff/c.j.albers/'>Casper J Albers</a>, <a href='https://www.rug.nl/staff/c.glasner/'>Corinna Glasner</a>.</p>
</div>
<div class="pkgdown">

View File

@ -84,7 +84,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9004</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.9.0.9005</span>
</span>
</div>

View File

@ -16,10 +16,10 @@ is.disk(x)
\item{na.rm}{a logical indicating whether missing values should be removed}
}
\value{
Ordered integer factor with new class \code{\link{disk}}
An \code{\link{integer}} with additional new class \code{\link{disk}}
}
\description{
This transforms a vector to a new class \code{\link{disk}}, which is a growth zone size (around an antibiotic disk) in millimeters between 6 and 99.
This transforms a vector to a new class \code{\link{disk}}, which is a growth zone size (around an antibiotic disk) in millimeters between 6 and 50.
}
\details{
Interpret disk values as RSI values with \code{\link[=as.rsi]{as.rsi()}}. It supports guidelines from EUCAST and CLSI.

View File

@ -51,8 +51,18 @@ test_that("creation of data sets is valid", {
DT <- make_DT()
expect_lt(nrow(DT[prevalence == 1]), nrow(DT[prevalence == 2]))
expect_lt(nrow(DT[prevalence == 2]), nrow(DT[prevalence == 3]))
expect_true(all(c("mo", "fullname",
"kingdom", "phylum", "class", "order", "family", "genus", "species", "subspecies",
"rank", "col_id", "species_id", "source", "ref", "prevalence",
"kingdom_index", "fullname_lower", "g_species") %in% colnames(DT)))
oldDT <- make_oldDT()
expect_true(all(c("col_id", "col_id_new", "fullname", "ref", "prevalence",
"fullname_lower", "g_species") %in% colnames(oldDT)))
old <- make_trans_tbl()
expect_gt(length(old), 0)
})
test_that("CoL version info works", {

View File

@ -31,12 +31,15 @@ knitr::opts_chunk$set(
Conducting antimicrobial resistance analysis unfortunately requires in-depth knowledge from different scientific fields, which makes it hard to do right. At least, it requires:
* Good questions (always start with these!)
* A thorough understanding of both (clinical) epidemiology and (clinical) microbiology, to understand the clinical and epidemiological relevance of results and their pharmaceutical implications
* Experience with data analysis with microbiological tests and their results (MIC/RSI values)
* Availability of the biological taxonomy of microorganisms
* Available (inter-)national guidelines and methods to apply them
* A thorough understanding of (clinical) epidemiology, to understand the clinical and epidemiological relevance and possible bias of results
* A thorough understanding of (clinical) microbiology/infectious diseases, to understand which microorganisms are causal to which infections and the implications of pharmaceutical treatment
* Experience with data analysis with microbiological tests and their results, to understand the determination and limitations of MIC values and their interpretations to RSI values
* Availability of the biological taxonomy of microorganisms and probably normalisation factors for pharmaceuticals, such as defined daily doses (DDD)
* Available (inter-)national guidelines, and profound methods to apply them
Of course, we cannot instantly provide you with knowledge and experience. But with this `AMR` pacakge, we aimed at providing (1) tools to simplify antimicrobial resistance data cleaning/analysis, (2) methods to easily incorporate international guidelines and (3) scientifically reliable reference data. The `AMR` package enables standardised and reproducible antimicrobial resistance analyses, including the application of evidence-based rules, determination of first isolates, translation of various codes for microorganisms and antimicrobial agents, determination of (multi-drug) resistant microorganisms, and calculation of antimicrobial resistance, prevalence and future trends.
Of course, we cannot instantly provide you with knowledge and experience. But with this `AMR` package, we aimed at providing (1) tools to simplify antimicrobial resistance data cleaning, transformation and analysis, (2) methods to easily incorporate international guidelines and (3) scientifically reliable reference data, including the requirements mentioned above.
The `AMR` package enables standardised and reproducible antimicrobial resistance analysis, with the application of evidence-based rules, determination of first isolates, translation of various codes for microorganisms and antimicrobial agents, determination of (multi-drug) resistant microorganisms, and calculation of antimicrobial resistance, prevalence and future trends.
# Preparation