(v1.3.0.9038) prefinal 1.4.0
| @@ -1,6 +1,6 @@ | |||||||
| Package: AMR | Package: AMR | ||||||
| Version: 1.3.0.9037 | Version: 1.3.0.9038 | ||||||
| Date: 2020-09-30 | Date: 2020-10-04 | ||||||
| Title: Antimicrobial Resistance Analysis | Title: Antimicrobial Resistance Analysis | ||||||
| Authors@R: c( | Authors@R: c( | ||||||
|     person(role = c("aut", "cre"),  |     person(role = c("aut", "cre"),  | ||||||
|   | |||||||
							
								
								
									
										4
									
								
								NEWS.md
									
									
									
									
									
								
							
							
						
						| @@ -1,5 +1,5 @@ | |||||||
| # AMR 1.3.0.9037 | # AMR 1.3.0.9038 | ||||||
| ## <small>Last updated: 30 September 2020</small> | ## <small>Last updated: 4 October 2020</small> | ||||||
|  |  | ||||||
| Note: some changes in this version were suggested by anonymous reviewers from the journal we submitted our manuscipt about this package to. We are those reviewers very grateful for going through our code so thoroughly! | Note: some changes in this version were suggested by anonymous reviewers from the journal we submitted our manuscipt about this package to. We are those reviewers very grateful for going through our code so thoroughly! | ||||||
|  |  | ||||||
|   | |||||||
| @@ -188,8 +188,9 @@ search_type_in_df <- function(x, type, info = TRUE) { | |||||||
| } | } | ||||||
|  |  | ||||||
| is_possibly_regex <- function(x) { | is_possibly_regex <- function(x) { | ||||||
|   sapply(strsplit(x, ""), |   tryCatch(sapply(strsplit(x, ""), | ||||||
|          function(y) any(y %in% c("$", "(", ")", "*", "+", "-", ".", "?", "[", "]", "^", "{", "|", "}", "\\"), na.rm = TRUE)) |                   function(y) any(y %in% c("$", "(", ")", "*", "+", "-", ".", "?", "[", "]", "^", "{", "|", "}", "\\"), na.rm = TRUE)), | ||||||
|  |            error = function(e) rep(TRUE, length(x))) | ||||||
| } | } | ||||||
|  |  | ||||||
| stop_ifnot_installed <- function(package) { | stop_ifnot_installed <- function(package) { | ||||||
|   | |||||||
| @@ -39,7 +39,7 @@ EUCAST_VERSION_EXPERT_RULES <- list("3.1" = list(version_txt = "v3.1", | |||||||
| #' To improve the interpretation of the antibiogram before EUCAST rules are applied, some non-EUCAST rules can applied at default, see Details. | #' To improve the interpretation of the antibiogram before EUCAST rules are applied, some non-EUCAST rules can applied at default, see Details. | ||||||
| #' @inheritSection lifecycle Stable lifecycle | #' @inheritSection lifecycle Stable lifecycle | ||||||
| #' @param x data with antibiotic columns, such as `amox`, `AMX` and `AMC` | #' @param x data with antibiotic columns, such as `amox`, `AMX` and `AMC` | ||||||
| #' @param info print progress | #' @param info a logical to indicate whether progress should be printed to the console, defaults to only print while in interactive sessions | ||||||
| #' @param rules a character vector that specifies which rules should be applied. Must be one or more of `"breakpoints"`, `"expert"`, `"other"`, `"all"`, and defaults to `c("breakpoints", "expert")`. The default value can be set to another value, e.g. using `options(AMR_eucastrules = "all")`. | #' @param rules a character vector that specifies which rules should be applied. Must be one or more of `"breakpoints"`, `"expert"`, `"other"`, `"all"`, and defaults to `c("breakpoints", "expert")`. The default value can be set to another value, e.g. using `options(AMR_eucastrules = "all")`. | ||||||
| #' @param verbose a [logical] to turn Verbose mode on and off (default is off). In Verbose mode, the function does not apply rules to the data, but instead returns a data set in logbook form with extensive info about which rows and columns would be effected and in which way. Using Verbose mode takes a lot more time. | #' @param verbose a [logical] to turn Verbose mode on and off (default is off). In Verbose mode, the function does not apply rules to the data, but instead returns a data set in logbook form with extensive info about which rows and columns would be effected and in which way. Using Verbose mode takes a lot more time. | ||||||
| #' @param version_breakpoints the version number to use for the EUCAST Clinical Breakpoints guideline. Currently supported: `r paste0(names(EUCAST_VERSION_BREAKPOINTS), collapse = ", ")`. | #' @param version_breakpoints the version number to use for the EUCAST Clinical Breakpoints guideline. Currently supported: `r paste0(names(EUCAST_VERSION_BREAKPOINTS), collapse = ", ")`. | ||||||
| @@ -132,7 +132,7 @@ eucast_rules <- function(x, | |||||||
|                          ...) { |                          ...) { | ||||||
|    |    | ||||||
|   x_deparsed <- deparse(substitute(x)) |   x_deparsed <- deparse(substitute(x)) | ||||||
|   if (length(x_deparsed) > 0 || !all(x_deparsed %like% "[a-z]")) { |   if (length(x_deparsed) > 1 || !all(x_deparsed %like% "[a-z]+")) { | ||||||
|     x_deparsed <- "your_data" |     x_deparsed <- "your_data" | ||||||
|   } |   } | ||||||
|    |    | ||||||
| @@ -188,7 +188,7 @@ eucast_rules <- function(x, | |||||||
|   } |   } | ||||||
|    |    | ||||||
|   warned <- FALSE |   warned <- FALSE | ||||||
|   warn_lacking_rsi_class <- FALSE |   warn_lacking_rsi_class <- character(0) | ||||||
|   txt_ok <- function(n_added, n_changed, warned = FALSE) { |   txt_ok <- function(n_added, n_changed, warned = FALSE) { | ||||||
|     if (warned == FALSE) { |     if (warned == FALSE) { | ||||||
|       if (n_added + n_changed == 0) { |       if (n_added + n_changed == 0) { | ||||||
| @@ -612,9 +612,7 @@ eucast_rules <- function(x, | |||||||
|         # Set base to R where base + enzyme inhibitor is R |         # Set base to R where base + enzyme inhibitor is R | ||||||
|         rule_current <- paste0("Set ", ab_name_base, " (", cols_ab[ab_enzyme[i, ]$base_ab], ") = R where ", |         rule_current <- paste0("Set ", ab_name_base, " (", cols_ab[ab_enzyme[i, ]$base_ab], ") = R where ", | ||||||
|                                ab_name_enzyme, " (", cols_ab[ab_enzyme[i, ]$ab], ") = R") |                                ab_name_enzyme, " (", cols_ab[ab_enzyme[i, ]$ab], ") = R") | ||||||
|         if (info == TRUE) { |         cat(rule_current) | ||||||
|           cat(rule_current) |  | ||||||
|         } |  | ||||||
|         run_changes <- edit_rsi(x = x, |         run_changes <- edit_rsi(x = x, | ||||||
|                                 col_mo = col_mo, |                                 col_mo = col_mo, | ||||||
|                                 to = "R", |                                 to = "R", | ||||||
| @@ -629,7 +627,7 @@ eucast_rules <- function(x, | |||||||
|         n_changed <- n_changed + run_changes$changed |         n_changed <- n_changed + run_changes$changed | ||||||
|         verbose_info <- run_changes$verbose_info |         verbose_info <- run_changes$verbose_info | ||||||
|         x <- run_changes$output |         x <- run_changes$output | ||||||
|         warn_lacking_rsi_class <- warn_lacking_rsi_class | run_changes$rsi_warn |         warn_lacking_rsi_class <- c(warn_lacking_rsi_class, run_changes$rsi_warn) | ||||||
|         # Print number of new changes |         # Print number of new changes | ||||||
|         if (info == TRUE) { |         if (info == TRUE) { | ||||||
|           # print only on last one of rules in this group |           # print only on last one of rules in this group | ||||||
| @@ -659,7 +657,7 @@ eucast_rules <- function(x, | |||||||
|         n_changed <- n_changed + run_changes$changed |         n_changed <- n_changed + run_changes$changed | ||||||
|         verbose_info <- run_changes$verbose_info |         verbose_info <- run_changes$verbose_info | ||||||
|         x <- run_changes$output |         x <- run_changes$output | ||||||
|         warn_lacking_rsi_class <- warn_lacking_rsi_class | run_changes$rsi_warn |         warn_lacking_rsi_class <- c(warn_lacking_rsi_class, run_changes$rsi_warn) | ||||||
|         # Print number of new changes |         # Print number of new changes | ||||||
|         if (info == TRUE) { |         if (info == TRUE) { | ||||||
|           # print only on last one of rules in this group |           # print only on last one of rules in this group | ||||||
| @@ -691,7 +689,7 @@ eucast_rules <- function(x, | |||||||
|   if (any(c("all", "breakpoints") %in% rules)) { |   if (any(c("all", "breakpoints") %in% rules)) { | ||||||
|     eucast_rules_df <- subset(eucast_rules_df, |     eucast_rules_df <- subset(eucast_rules_df, | ||||||
|                               !reference.rule_group %like% "breakpoint" | |                               !reference.rule_group %like% "breakpoint" | | ||||||
|                               (reference.rule_group %like% "breakpoint" & reference.version == version_breakpoints)) |                                 (reference.rule_group %like% "breakpoint" & reference.version == version_breakpoints)) | ||||||
|   } |   } | ||||||
|   if (any(c("all", "expert") %in% rules)) { |   if (any(c("all", "expert") %in% rules)) { | ||||||
|     eucast_rules_df <- subset(eucast_rules_df, |     eucast_rules_df <- subset(eucast_rules_df, | ||||||
| @@ -866,7 +864,7 @@ eucast_rules <- function(x, | |||||||
|     n_changed <- n_changed + run_changes$changed |     n_changed <- n_changed + run_changes$changed | ||||||
|     verbose_info <- run_changes$verbose_info |     verbose_info <- run_changes$verbose_info | ||||||
|     x <- run_changes$output |     x <- run_changes$output | ||||||
|     warn_lacking_rsi_class <- warn_lacking_rsi_class | run_changes$rsi_warn |     warn_lacking_rsi_class <- c(warn_lacking_rsi_class, run_changes$rsi_warn) | ||||||
|     # Print number of new changes --------------------------------------------- |     # Print number of new changes --------------------------------------------- | ||||||
|     if (info == TRUE & rule_next != rule_current) { |     if (info == TRUE & rule_next != rule_current) { | ||||||
|       # print only on last one of rules in this group |       # print only on last one of rules in this group | ||||||
| @@ -878,8 +876,7 @@ eucast_rules <- function(x, | |||||||
|   } |   } | ||||||
|    |    | ||||||
|   # Print overview ---------------------------------------------------------- |   # Print overview ---------------------------------------------------------- | ||||||
|   if (info == TRUE) { |   if (info == TRUE | verbose == TRUE) { | ||||||
|      |  | ||||||
|     verbose_info <- x.bak %pm>% |     verbose_info <- x.bak %pm>% | ||||||
|       pm_mutate(row = pm_row_number()) %pm>% |       pm_mutate(row = pm_row_number()) %pm>% | ||||||
|       pm_select(`.rowid`, row) %pm>% |       pm_select(`.rowid`, row) %pm>% | ||||||
| @@ -890,6 +887,9 @@ eucast_rules <- function(x, | |||||||
|       pm_filter(!is.na(new)) %pm>% |       pm_filter(!is.na(new)) %pm>% | ||||||
|       pm_arrange(row, rule_group, rule_name, col) |       pm_arrange(row, rule_group, rule_name, col) | ||||||
|     rownames(verbose_info) <- NULL |     rownames(verbose_info) <- NULL | ||||||
|  |   } | ||||||
|  |    | ||||||
|  |   if (info == TRUE) { | ||||||
|      |      | ||||||
|     if (verbose == TRUE) { |     if (verbose == TRUE) { | ||||||
|       wouldve <- "would have " |       wouldve <- "would have " | ||||||
| @@ -899,16 +899,16 @@ eucast_rules <- function(x, | |||||||
|      |      | ||||||
|     cat(paste0("\n", font_grey(strrep("-", 0.95 * options()$width)), "\n")) |     cat(paste0("\n", font_grey(strrep("-", 0.95 * options()$width)), "\n")) | ||||||
|     cat(paste0("The rules ", paste0(wouldve, "affected "), |     cat(paste0("The rules ", paste0(wouldve, "affected "), | ||||||
|               font_bold(formatnr(pm_n_distinct(verbose_info$row)), |                font_bold(formatnr(pm_n_distinct(verbose_info$row)), | ||||||
|                         "out of", formatnr(nrow(x.bak)), |                          "out of", formatnr(nrow(x.bak)), | ||||||
|                         "rows"),  |                          "rows"),  | ||||||
|               ", making a total of ", |                ", making a total of ", | ||||||
|               font_bold(formatnr(nrow(verbose_info)), "edits\n"))) |                font_bold(formatnr(nrow(verbose_info)), "edits\n"))) | ||||||
|      |      | ||||||
| total_n_added <- verbose_info %pm>% pm_filter(is.na(old)) %pm>% nrow() |     total_n_added <- verbose_info %pm>% pm_filter(is.na(old)) %pm>% nrow() | ||||||
| total_n_changed <- verbose_info %pm>% pm_filter(!is.na(old)) %pm>% nrow() |     total_n_changed <- verbose_info %pm>% pm_filter(!is.na(old)) %pm>% nrow() | ||||||
|      |      | ||||||
| # print added values |     # print added values | ||||||
|     if (total_n_added == 0) { |     if (total_n_added == 0) { | ||||||
|       colour <- cat # is function |       colour <- cat # is function | ||||||
|     } else { |     } else { | ||||||
| @@ -961,12 +961,14 @@ total_n_changed <- verbose_info %pm>% pm_filter(!is.na(old)) %pm>% nrow() | |||||||
|     } |     } | ||||||
|   } |   } | ||||||
|    |    | ||||||
|  |   if (length(warn_lacking_rsi_class) > 0) { | ||||||
|   if (isTRUE(warn_lacking_rsi_class)) { |     warn_lacking_rsi_class <- unique(warn_lacking_rsi_class) | ||||||
|     unique_cols <- colnames(x.bak)[colnames(x.bak) %in% verbose_info$col] |  | ||||||
|     warning("Not all columns with antimicrobial results are of class <rsi>. Transform them on beforehand, with e.g.:\n", |     warning("Not all columns with antimicrobial results are of class <rsi>. Transform them on beforehand, with e.g.:\n", | ||||||
|             "  ", x_deparsed, " %>% mutate_if(is.rsi.eligible, as.rsi)\n", |             "  ", x_deparsed, " %>% mutate_if(is.rsi.eligible, as.rsi)\n", | ||||||
|             "  ", x_deparsed, " %>% as.rsi(", unique_cols[1], ":", unique_cols[length(unique_cols)], ")", |             "  ", x_deparsed, " %>% as.rsi(", ifelse(length(warn_lacking_rsi_class) == 1,  | ||||||
|  |                                                      warn_lacking_rsi_class, | ||||||
|  |                                                      paste0(warn_lacking_rsi_class[1], ":", warn_lacking_rsi_class[length(warn_lacking_rsi_class)])),  | ||||||
|  |             ")", | ||||||
|             call. = FALSE) |             call. = FALSE) | ||||||
|   } |   } | ||||||
|    |    | ||||||
| @@ -1004,7 +1006,7 @@ edit_rsi <- function(x, | |||||||
|                         changed = 0, |                         changed = 0, | ||||||
|                         output = x, |                         output = x, | ||||||
|                         verbose_info = last_verbose_info, |                         verbose_info = last_verbose_info, | ||||||
|                         rsi_warn = FALSE) |                         rsi_warn = character(0)) | ||||||
|    |    | ||||||
|   txt_error <- function() { |   txt_error <- function() { | ||||||
|     if (info == TRUE) cat("", font_red_bg(font_white(" ERROR ")), "\n\n")  |     if (info == TRUE) cat("", font_red_bg(font_white(" ERROR ")), "\n\n")  | ||||||
| @@ -1019,7 +1021,7 @@ edit_rsi <- function(x, | |||||||
|   if (length(rows) > 0 & length(cols) > 0) { |   if (length(rows) > 0 & length(cols) > 0) { | ||||||
|     new_edits <- x |     new_edits <- x | ||||||
|     if (any(!sapply(x[, cols, drop = FALSE], is.rsi), na.rm = TRUE)) { |     if (any(!sapply(x[, cols, drop = FALSE], is.rsi), na.rm = TRUE)) { | ||||||
|       track_changes$rsi_warn <- TRUE |       track_changes$rsi_warn <- cols[!sapply(x[, cols, drop = FALSE], is.rsi)] | ||||||
|     } |     } | ||||||
|     tryCatch( |     tryCatch( | ||||||
|       # insert into original table |       # insert into original table | ||||||
|   | |||||||
							
								
								
									
										1
									
								
								R/mdro.R
									
									
									
									
									
								
							
							
						
						| @@ -24,7 +24,6 @@ | |||||||
| #' Determine which isolates are multidrug-resistant organisms (MDRO) according to international and national guidelines. | #' Determine which isolates are multidrug-resistant organisms (MDRO) according to international and national guidelines. | ||||||
| #' @inheritSection lifecycle Maturing lifecycle | #' @inheritSection lifecycle Maturing lifecycle | ||||||
| #' @param guideline a specific guideline to follow. When left empty, the publication by Magiorakos *et al.* (2012, Clinical Microbiology and Infection) will be followed, please see *Details*. | #' @param guideline a specific guideline to follow. When left empty, the publication by Magiorakos *et al.* (2012, Clinical Microbiology and Infection) will be followed, please see *Details*. | ||||||
| #' @param info a logical to indicate whether progress should be printed to the console |  | ||||||
| #' @inheritParams eucast_rules | #' @inheritParams eucast_rules | ||||||
| #' @param pct_required_classes minimal required percentage of antimicrobial classes that must be available per isolate, rounded down. For example, with the default guideline, 17 antimicrobial classes must be available for *S. aureus*. Setting this `pct_required_classes` argument to `0.5` (default) means that for every *S. aureus* isolate at least 8 different classes must be available. Any lower number of available classes will return `NA` for that isolate. | #' @param pct_required_classes minimal required percentage of antimicrobial classes that must be available per isolate, rounded down. For example, with the default guideline, 17 antimicrobial classes must be available for *S. aureus*. Setting this `pct_required_classes` argument to `0.5` (default) means that for every *S. aureus* isolate at least 8 different classes must be available. Any lower number of available classes will return `NA` for that isolate. | ||||||
| #' @param combine_SI a [logical] to indicate whether all values of S and I must be merged into one, so resistance is only considered when isolates are R, not I. As this is the default behaviour of the [mdro()] function, it follows the redefinition by EUCAST about the interpretation of I (increased exposure) in 2019, see section 'Interpretation of S, I and R' below. When using `combine_SI = FALSE`, resistance is considered when isolates are R or I. | #' @param combine_SI a [logical] to indicate whether all values of S and I must be merged into one, so resistance is only considered when isolates are R, not I. As this is the default behaviour of the [mdro()] function, it follows the redefinition by EUCAST about the interpretation of I (increased exposure) in 2019, see section 'Interpretation of S, I and R' below. When using `combine_SI = FALSE`, resistance is considered when isolates are R or I. | ||||||
|   | |||||||
							
								
								
									
										48
									
								
								R/mo.R
									
									
									
									
									
								
							
							
						
						| @@ -157,7 +157,7 @@ as.mo <- function(x, | |||||||
|    |    | ||||||
|   check_dataset_integrity() |   check_dataset_integrity() | ||||||
|    |    | ||||||
|   if (tryCatch(all(x %in% MO_lookup$mo, na.rm = TRUE) |   if (tryCatch(all(x[!is.na(x)] %in% MO_lookup$mo) | ||||||
|                & isFALSE(Becker) |                & isFALSE(Becker) | ||||||
|                & isFALSE(Lancefield), error = function(e) FALSE)) { |                & isFALSE(Lancefield), error = function(e) FALSE)) { | ||||||
|     # don't look into valid MO codes, just return them |     # don't look into valid MO codes, just return them | ||||||
| @@ -212,7 +212,7 @@ as.mo <- function(x, | |||||||
|         pm_pull("mo") |         pm_pull("mo") | ||||||
|     ) |     ) | ||||||
|      |      | ||||||
|   } else if (all(x %in% MO_lookup$mo) |   } else if (all(x[!is.na(x)] %in% MO_lookup$mo) | ||||||
|              & isFALSE(Becker) |              & isFALSE(Becker) | ||||||
|              & isFALSE(Lancefield)) { |              & isFALSE(Lancefield)) { | ||||||
|     y <- x |     y <- x | ||||||
| @@ -1733,7 +1733,9 @@ print.mo_uncertainties <- function(x, ...) { | |||||||
|   if (NROW(x) == 0) { |   if (NROW(x) == 0) { | ||||||
|     return(NULL) |     return(NULL) | ||||||
|   } |   } | ||||||
|   cat(font_blue(strwrap(c("Matching scores are based on human pathogenic prevalence and the resemblance between the input and the full taxonomic name. Please see ?mo_matching_score.")), collapse = "\n")) |   cat(font_blue(strwrap("Matching scores are based on human pathogenic prevalence and the resemblance between the input and the full taxonomic name. Please see ?mo_matching_score.",  | ||||||
|  |                         width = 0.98 * getOption("width")),  | ||||||
|  |                 collapse = "\n")) | ||||||
|   cat("\n") |   cat("\n") | ||||||
|    |    | ||||||
|   msg <- "" |   msg <- "" | ||||||
| @@ -1745,12 +1747,22 @@ print.mo_uncertainties <- function(x, ...) { | |||||||
|       candidates <- candidates[order(1 - scores)] |       candidates <- candidates[order(1 - scores)] | ||||||
|       scores_formatted <- trimws(formatC(round(scores, 3), format = "f", digits = 3)) |       scores_formatted <- trimws(formatC(round(scores, 3), format = "f", digits = 3)) | ||||||
|       n_candidates <- length(candidates) |       n_candidates <- length(candidates) | ||||||
|       candidates <- paste0(font_italic(candidates, collapse = NULL),  |       candidates <- paste0(candidates, " (", scores_formatted[order(1 - scores)], ")", collapse = ", ") | ||||||
|                            " (", scores_formatted[order(1 - scores)], ")") |  | ||||||
|       candidates <- paste(candidates, collapse = ", ") |  | ||||||
|       # align with input after arrow |       # align with input after arrow | ||||||
|       candidates <- paste0("\n", strrep(" ", nchar(x[i, ]$input) + 6),  |       candidates <- paste0("\n",  | ||||||
|                            "Also matched", ifelse(n_candidates == 25, " (max 25)", ""), ": ", candidates) |                            strwrap(paste0("Also matched", | ||||||
|  |                                           ifelse(n_candidates >= 25, " (max 25)", ""), ": ",  | ||||||
|  |                                           candidates), # this is already max 25 due to format_uncertainty_as_df() | ||||||
|  |                                    indent = nchar(x[i, ]$input) + 6, | ||||||
|  |                                    exdent = nchar(x[i, ]$input) + 6,  | ||||||
|  |                                    width = 0.98 * getOption("width")), | ||||||
|  |                            collapse = "") | ||||||
|  |       # after strwrap, make taxonomic names italic | ||||||
|  |       candidates <- gsub("([A-Za-z]+)", font_italic("\\1"), candidates) | ||||||
|  |       candidates <- gsub(paste(font_italic(c("Also", "matched"), collapse = NULL), collapse = " "),  | ||||||
|  |                          "Also matched", | ||||||
|  |                          candidates, fixed = TRUE) | ||||||
|  |       candidates <- gsub(font_italic("max"), "max", candidates, fixed = TRUE) | ||||||
|     } else { |     } else { | ||||||
|       candidates <- "" |       candidates <- "" | ||||||
|     } |     } | ||||||
| @@ -1759,14 +1771,20 @@ print.mo_uncertainties <- function(x, ...) { | |||||||
|                                   3), |                                   3), | ||||||
|                             format = "f", digits = 3)) |                             format = "f", digits = 3)) | ||||||
|     msg <- paste(msg, |     msg <- paste(msg, | ||||||
|                  paste0('"', x[i, ]$input, '" -> ', |                  paste0( | ||||||
|                         paste0(font_bold(font_italic(x[i, ]$fullname)), |                    strwrap( | ||||||
|                                ifelse(!is.na(x[i, ]$renamed_to), paste(", renamed to", font_italic(x[i, ]$renamed_to)), ""), |                      paste0('"', x[i, ]$input, '" -> ', | ||||||
|                                " (", x[i, ]$mo, |                             paste0(font_bold(font_italic(x[i, ]$fullname)), | ||||||
|                                ", matching score = ", score, |                                    ifelse(!is.na(x[i, ]$renamed_to), paste(", renamed to", font_italic(x[i, ]$renamed_to)), ""), | ||||||
|                                ") "), |                                    " (", x[i, ]$mo, | ||||||
|                         candidates), |                                    ", matching score = ", score, | ||||||
|  |                                    ") ")), | ||||||
|  |                      width = 0.98 * getOption("width"), | ||||||
|  |                      exdent = nchar(x[i, ]$input) + 6),  | ||||||
|  |                    collapse = "\n"), | ||||||
|  |                  candidates, | ||||||
|                  sep = "\n") |                  sep = "\n") | ||||||
|  |     msg <- paste0(gsub("\n\n", "\n", msg), "\n\n") | ||||||
|   } |   } | ||||||
|   cat(msg) |   cat(msg) | ||||||
| } | } | ||||||
|   | |||||||
| @@ -415,7 +415,7 @@ mo_validate <- function(x, property, language, ...) { | |||||||
|    |    | ||||||
|   check_dataset_integrity() |   check_dataset_integrity() | ||||||
|    |    | ||||||
|   if (tryCatch(all(x %in% MO_lookup$mo) & length(list(...)) == 0, error = function(e) FALSE)) { |   if (tryCatch(all(x[!is.na(x)] %in% MO_lookup$mo) & length(list(...)) == 0, error = function(e) FALSE)) { | ||||||
|     # special case for mo_* functions where class is already <mo> |     # special case for mo_* functions where class is already <mo> | ||||||
|     return(MO_lookup[match(x, MO_lookup$mo), property, drop = TRUE]) |     return(MO_lookup[match(x, MO_lookup$mo), property, drop = TRUE]) | ||||||
|   } |   } | ||||||
|   | |||||||
| @@ -31,7 +31,7 @@ | |||||||
| #' @aliases set_mo_source get_mo_source | #' @aliases set_mo_source get_mo_source | ||||||
| #' @details The reference file can be a text file separated with commas (CSV) or tabs or pipes, an Excel file (either 'xls' or 'xlsx' format) or an R object file (extension '.rds'). To use an Excel file, you will need to have the `readxl` package installed. | #' @details The reference file can be a text file separated with commas (CSV) or tabs or pipes, an Excel file (either 'xls' or 'xlsx' format) or an R object file (extension '.rds'). To use an Excel file, you will need to have the `readxl` package installed. | ||||||
| #' | #' | ||||||
| #' [set_mo_source()] will check the file for validity: it must be a [data.frame], must have a column named `"mo"` which contains values from [`microorganisms$mo`][microorganisms] and must have a reference column with your own defined values. If all tests pass, [set_mo_source()] will read the file into R and export it to `"~/.mo_source.rds"` after the user **specifically confirms and allows** that this file will be created. For this reason, this function only works in interactive sessions. | #' [set_mo_source()] will check the file for validity: it must be a [data.frame], must have a column named `"mo"` which contains values from [`microorganisms$mo`][microorganisms] and must have a reference column with your own defined values. If all tests pass, [set_mo_source()] will read the file into R and will ask to export it to `"~/.mo_source.rds"`. The CRAN policy disallows packages to write to the file system, although '*exceptions may be allowed in interactive sessions if the package obtains confirmation from the user*'. For this reason, this function only works in interactive sessions so that the user can **specifically confirm and allow** that this file will be created.  | ||||||
| #'  | #'  | ||||||
| #' The created compressed data file `"~/.mo_source.rds"` will be used at default for MO determination (function [as.mo()] and consequently all `mo_*` functions like [mo_genus()] and [mo_gramstain()]). The location of the original file will be saved as an R option with `options(mo_source = path)`. Its timestamp will be saved with `options(mo_source_datetime = ...)`.  | #' The created compressed data file `"~/.mo_source.rds"` will be used at default for MO determination (function [as.mo()] and consequently all `mo_*` functions like [mo_genus()] and [mo_gramstain()]). The location of the original file will be saved as an R option with `options(mo_source = path)`. Its timestamp will be saved with `options(mo_source_datetime = ...)`.  | ||||||
| #'  | #'  | ||||||
|   | |||||||
| @@ -81,7 +81,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="https://msberends.github.io/AMR/index.html">AMR (for R)</a> |         <a class="navbar-link" href="https://msberends.github.io/AMR/index.html">AMR (for R)</a> | ||||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9037</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9038</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -81,7 +81,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="index.html">AMR (for R)</a> |         <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">1.3.0.9037</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9038</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -20,7 +20,7 @@ | |||||||
| <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | ||||||
| <script src="../extra.js"></script><meta property="og:title" content="How to conduct AMR analysis"> | <script src="../extra.js"></script><meta property="og:title" content="How to conduct AMR analysis"> | ||||||
| <meta property="og:description" content="AMR"> | <meta property="og:description" content="AMR"> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg"> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png"> | ||||||
| <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | ||||||
| <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | ||||||
| <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | ||||||
| @@ -39,7 +39,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -193,7 +193,7 @@ | |||||||
|       <h1 data-toc-skip>How to conduct AMR analysis</h1> |       <h1 data-toc-skip>How to conduct AMR analysis</h1> | ||||||
|                         <h4 class="author">Matthijs S. Berends</h4> |                         <h4 class="author">Matthijs S. Berends</h4> | ||||||
|              |              | ||||||
|             <h4 class="date">03 September 2020</h4> |             <h4 class="date">30 September 2020</h4> | ||||||
|        |        | ||||||
|       <small class="dont-index">Source: <a href="https://github.com/msberends/AMR/blob/master/vignettes/AMR.Rmd"><code>vignettes/AMR.Rmd</code></a></small> |       <small class="dont-index">Source: <a href="https://github.com/msberends/AMR/blob/master/vignettes/AMR.Rmd"><code>vignettes/AMR.Rmd</code></a></small> | ||||||
|       <div class="hidden name"><code>AMR.Rmd</code></div> |       <div class="hidden name"><code>AMR.Rmd</code></div> | ||||||
| @@ -202,7 +202,7 @@ | |||||||
|  |  | ||||||
|      |      | ||||||
|      |      | ||||||
| <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 03 September 2020.</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 30 September 2020.</p> | ||||||
| <div id="introduction" class="section level1"> | <div id="introduction" class="section level1"> | ||||||
| <h1 class="hasAnchor"> | <h1 class="hasAnchor"> | ||||||
| <a href="#introduction" class="anchor"></a>Introduction</h1> | <a href="#introduction" class="anchor"></a>Introduction</h1> | ||||||
| @@ -233,21 +233,21 @@ | |||||||
| </tr></thead> | </tr></thead> | ||||||
| <tbody> | <tbody> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">2020-09-03</td> | <td align="center">2020-09-30</td> | ||||||
| <td align="center">abcd</td> | <td align="center">abcd</td> | ||||||
| <td align="center">Escherichia coli</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> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">2020-09-03</td> | <td align="center">2020-09-30</td> | ||||||
| <td align="center">abcd</td> | <td align="center">abcd</td> | ||||||
| <td align="center">Escherichia coli</td> | <td align="center">Escherichia coli</td> | ||||||
| <td align="center">S</td> | <td align="center">S</td> | ||||||
| <td align="center">R</td> | <td align="center">R</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">2020-09-03</td> | <td align="center">2020-09-30</td> | ||||||
| <td align="center">efgh</td> | <td align="center">efgh</td> | ||||||
| <td align="center">Escherichia coli</td> | <td align="center">Escherichia coli</td> | ||||||
| <td align="center">R</td> | <td align="center">R</td> | ||||||
| @@ -361,70 +361,70 @@ | |||||||
| </tr></thead> | </tr></thead> | ||||||
| <tbody> | <tbody> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">2014-05-29</td> | <td align="center">2016-08-26</td> | ||||||
| <td align="center">B4</td> | <td align="center">P9</td> | ||||||
|  | <td align="center">Hospital C</td> | ||||||
|  | <td align="center">Escherichia coli</td> | ||||||
|  | <td align="center">I</td> | ||||||
|  | <td align="center">S</td> | ||||||
|  | <td align="center">S</td> | ||||||
|  | <td align="center">R</td> | ||||||
|  | <td align="center">F</td> | ||||||
|  | </tr> | ||||||
|  | <tr class="even"> | ||||||
|  | <td align="center">2016-09-24</td> | ||||||
|  | <td align="center">T6</td> | ||||||
| <td align="center">Hospital B</td> | <td align="center">Hospital B</td> | ||||||
| <td align="center">Escherichia coli</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">S</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">M</td> |  | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="odd"> | ||||||
| <td align="center">2017-04-19</td> | <td align="center">2017-04-02</td> | ||||||
| <td align="center">S1</td> | <td align="center">X1</td> | ||||||
| <td align="center">Hospital C</td> | <td align="center">Hospital D</td> | ||||||
| <td align="center">Staphylococcus aureus</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">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">F</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="even"> | ||||||
| <td align="center">2017-04-21</td> | <td align="center">2016-12-13</td> | ||||||
| <td align="center">L3</td> | <td align="center">F1</td> | ||||||
| <td align="center">Hospital B</td> | <td align="center">Hospital A</td> | ||||||
| <td align="center">Escherichia coli</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">S</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> | <td align="center">M</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="odd"> | ||||||
| <td align="center">2011-01-19</td> | <td align="center">2012-02-05</td> | ||||||
| <td align="center">A7</td> | <td align="center">O8</td> | ||||||
| <td align="center">Hospital A</td> | <td align="center">Hospital B</td> | ||||||
| <td align="center">Staphylococcus aureus</td> | <td align="center">Staphylococcus aureus</td> | ||||||
| <td align="center">S</td> | <td align="center">S</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="odd"> |  | ||||||
| <td align="center">2011-01-24</td> |  | ||||||
| <td align="center">H10</td> |  | ||||||
| <td align="center">Hospital B</td> |  | ||||||
| <td align="center">Escherichia coli</td> |  | ||||||
| <td align="center">R</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">S</td> |  | ||||||
| <td align="center">M</td> |  | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">2011-01-31</td> | <td align="center">2017-06-17</td> | ||||||
| <td align="center">T9</td> | <td align="center">K1</td> | ||||||
| <td align="center">Hospital C</td> | <td align="center">Hospital B</td> | ||||||
| <td align="center">Streptococcus pneumoniae</td> | <td align="center">Streptococcus pneumoniae</td> | ||||||
| <td align="center">R</td> | <td align="center">R</td> | ||||||
|  | <td align="center">R</td> | ||||||
| <td align="center">S</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> | ||||||
| <td align="center">F</td> |  | ||||||
| </tr> | </tr> | ||||||
| </tbody> | </tbody> | ||||||
| </table> | </table> | ||||||
| @@ -459,16 +459,16 @@ Longest: 1</p> | |||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="left">1</td> | <td align="left">1</td> | ||||||
| <td align="left">M</td> | <td align="left">M</td> | ||||||
| <td align="right">10,409</td> | <td align="right">10,232</td> | ||||||
| <td align="right">52.05%</td> | <td align="right">51.16%</td> | ||||||
| <td align="right">10,409</td> | <td align="right">10,232</td> | ||||||
| <td align="right">52.05%</td> | <td align="right">51.16%</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="left">2</td> | <td align="left">2</td> | ||||||
| <td align="left">F</td> | <td align="left">F</td> | ||||||
| <td align="right">9,591</td> | <td align="right">9,768</td> | ||||||
| <td align="right">47.96%</td> | <td align="right">48.84%</td> | ||||||
| <td align="right">20,000</td> | <td align="right">20,000</td> | ||||||
| <td align="right">100.00%</td> | <td align="right">100.00%</td> | ||||||
| </tr> | </tr> | ||||||
| @@ -489,6 +489,7 @@ Longest: 1</p> | |||||||
| <p>Because the amoxicillin (column <code>AMX</code>) and amoxicillin/clavulanic acid (column <code>AMC</code>) in our data were generated randomly, some rows will undoubtedly contain AMX = S and AMC = R, which is technically impossible. The <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> fixes this:</p> | <p>Because the amoxicillin (column <code>AMX</code>) and amoxicillin/clavulanic acid (column <code>AMC</code>) in our data were generated randomly, some rows will undoubtedly contain AMX = S and AMC = R, which is technically impossible. The <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> fixes this:</p> | ||||||
| <div class="sourceCode" id="cb13"><pre class="downlit"> | <div class="sourceCode" id="cb13"><pre class="downlit"> | ||||||
| <span class="kw">data</span> <span class="op"><-</span> <span class="fu"><a href="../reference/eucast_rules.html">eucast_rules</a></span>(<span class="kw">data</span>, col_mo = <span class="st">"bacteria"</span>, rules = <span class="st">"all"</span>) | <span class="kw">data</span> <span class="op"><-</span> <span class="fu"><a href="../reference/eucast_rules.html">eucast_rules</a></span>(<span class="kw">data</span>, col_mo = <span class="st">"bacteria"</span>, rules = <span class="st">"all"</span>) | ||||||
|  | <span class="co"># Set amoxicillin (AMX) = R where amoxicillin/clavulanic acid (AMC) = R</span> | ||||||
| </pre></div> | </pre></div> | ||||||
| </div> | </div> | ||||||
| <div id="adding-new-variables" class="section level1"> | <div id="adding-new-variables" class="section level1"> | ||||||
| @@ -518,7 +519,7 @@ Longest: 1</p> | |||||||
| <span class="co"># NOTE: Using column `date` as input for `col_date`.</span> | <span class="co"># NOTE: Using column `date` as input for `col_date`.</span> | ||||||
| <span class="co"># NOTE: Using column `patient_id` as input for `col_patient_id`.</span> | <span class="co"># NOTE: Using column `patient_id` as input for `col_patient_id`.</span> | ||||||
| </pre></div> | </pre></div> | ||||||
| <p>So only 28.6% 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> | <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="cb16"><pre class="downlit"> | <div class="sourceCode" id="cb16"><pre class="downlit"> | ||||||
| <span class="kw">data_1st</span> <span class="op"><-</span> <span class="kw">data</span> <span class="op">%>%</span>  | <span class="kw">data_1st</span> <span class="op"><-</span> <span class="kw">data</span> <span class="op">%>%</span>  | ||||||
|   <span class="fu"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(<span class="kw">first</span> <span class="op">==</span> <span class="fl">TRUE</span>) |   <span class="fu"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(<span class="kw">first</span> <span class="op">==</span> <span class="fl">TRUE</span>) | ||||||
| @@ -532,7 +533,7 @@ Longest: 1</p> | |||||||
| <div id="first-weighted-isolates" class="section level2"> | <div id="first-weighted-isolates" class="section level2"> | ||||||
| <h2 class="hasAnchor"> | <h2 class="hasAnchor"> | ||||||
| <a href="#first-weighted-isolates" class="anchor"></a>First <em>weighted</em> isolates</h2> | <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 M8, 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 Z5, sorted on date:</p> | ||||||
| <table class="table"> | <table class="table"> | ||||||
| <thead><tr class="header"> | <thead><tr class="header"> | ||||||
| <th align="center">isolate</th> | <th align="center">isolate</th> | ||||||
| @@ -548,76 +549,76 @@ Longest: 1</p> | |||||||
| <tbody> | <tbody> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">1</td> | <td align="center">1</td> | ||||||
| <td align="center">2010-01-28</td> | <td align="center">2010-02-11</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">R</td> | <td align="center">S</td> | ||||||
| <td align="center">S</td> | <td align="center">S</td> | ||||||
| <td align="center">TRUE</td> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">2</td> | <td align="center">2</td> | ||||||
| <td align="center">2010-05-23</td> | <td align="center">2010-04-11</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">S</td> | ||||||
| <td align="center">S</td> |  | ||||||
| <td align="center">S</td> |  | ||||||
| <td align="center">FALSE</td> | <td align="center">FALSE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">3</td> | <td align="center">3</td> | ||||||
| <td align="center">2010-07-11</td> | <td align="center">2010-05-31</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">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> | <td align="center">FALSE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">4</td> | <td align="center">4</td> | ||||||
| <td align="center">2010-10-01</td> | <td align="center">2011-03-29</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">R</td> | <td align="center">R</td> | ||||||
| <td align="center">S</td> | <td align="center">S</td> | ||||||
| <td align="center">FALSE</td> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">5</td> | <td align="center">5</td> | ||||||
| <td align="center">2010-12-02</td> | <td align="center">2011-04-23</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">S</td> | ||||||
| <td align="center">S</td> |  | ||||||
| <td align="center">S</td> |  | ||||||
| <td align="center">FALSE</td> | <td align="center">FALSE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">6</td> | <td align="center">6</td> | ||||||
| <td align="center">2010-12-23</td> | <td align="center">2011-05-06</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">S</td> |  | ||||||
| <td align="center">S</td> | <td align="center">S</td> | ||||||
| <td align="center">FALSE</td> | <td align="center">FALSE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">7</td> | <td align="center">7</td> | ||||||
| <td align="center">2011-01-16</td> | <td align="center">2011-09-05</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">S</td> | ||||||
| <td align="center">S</td> | <td align="center">S</td> | ||||||
| @@ -625,19 +626,19 @@ Longest: 1</p> | |||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">8</td> | <td align="center">8</td> | ||||||
| <td align="center">2011-03-14</td> | <td align="center">2011-09-29</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">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">TRUE</td> |  | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">9</td> | <td align="center">9</td> | ||||||
| <td align="center">2011-04-02</td> | <td align="center">2011-11-16</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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> | ||||||
| @@ -647,13 +648,13 @@ Longest: 1</p> | |||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">10</td> | <td align="center">10</td> | ||||||
| <td align="center">2011-04-05</td> | <td align="center">2011-11-26</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</td> | <td align="center">B_ESCHR_COLI</td> | ||||||
| <td align="center">R</td> |  | ||||||
| <td align="center">R</td> |  | ||||||
| <td align="center">S</td> | <td align="center">S</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">FALSE</td> | ||||||
| </tr> | </tr> | ||||||
| </tbody> | </tbody> | ||||||
| @@ -686,35 +687,35 @@ Longest: 1</p> | |||||||
| <tbody> | <tbody> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">1</td> | <td align="center">1</td> | ||||||
| <td align="center">2010-01-28</td> | <td align="center">2010-02-11</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">R</td> | <td align="center">S</td> | ||||||
| <td align="center">S</td> | <td align="center">S</td> | ||||||
| <td align="center">TRUE</td> | <td align="center">TRUE</td> | ||||||
| <td align="center">TRUE</td> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">2</td> | <td align="center">2</td> | ||||||
| <td align="center">2010-05-23</td> | <td align="center">2010-04-11</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">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> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">3</td> | <td align="center">3</td> | ||||||
| <td align="center">2010-07-11</td> | <td align="center">2010-05-31</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">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> | <td align="center">FALSE</td> | ||||||
| @@ -722,97 +723,97 @@ Longest: 1</p> | |||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">4</td> | <td align="center">4</td> | ||||||
| <td align="center">2010-10-01</td> | <td align="center">2011-03-29</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">R</td> | <td align="center">R</td> | ||||||
| <td align="center">S</td> | <td align="center">S</td> | ||||||
| <td align="center">FALSE</td> | <td align="center">TRUE</td> | ||||||
| <td align="center">TRUE</td> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">5</td> | <td align="center">5</td> | ||||||
| <td align="center">2010-12-02</td> | <td align="center">2011-04-23</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">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> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">6</td> | <td align="center">6</td> | ||||||
| <td align="center">2010-12-23</td> | <td align="center">2011-05-06</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">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> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">7</td> | <td align="center">7</td> | ||||||
| <td align="center">2011-01-16</td> | <td align="center">2011-09-05</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">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">FALSE</td> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">8</td> | <td align="center">8</td> | ||||||
| <td align="center">2011-03-14</td> | <td align="center">2011-09-29</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">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">TRUE</td> |  | ||||||
| <td align="center">TRUE</td> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">9</td> | <td align="center">9</td> | ||||||
| <td align="center">2011-04-02</td> | <td align="center">2011-11-16</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</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">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> | ||||||
| <td align="center">FALSE</td> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">10</td> | <td align="center">10</td> | ||||||
| <td align="center">2011-04-05</td> | <td align="center">2011-11-26</td> | ||||||
| <td align="center">M8</td> | <td align="center">Z5</td> | ||||||
| <td align="center">B_ESCHR_COLI</td> | <td align="center">B_ESCHR_COLI</td> | ||||||
| <td align="center">R</td> |  | ||||||
| <td align="center">R</td> |  | ||||||
| <td align="center">S</td> | <td align="center">S</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">FALSE</td> | ||||||
| <td align="center">TRUE</td> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
| </tbody> | </tbody> | ||||||
| </table> | </table> | ||||||
| <p>Instead of 2, now 8 isolates are flagged. In total, 79.1% of all isolates are marked ‘first weighted’ - 50.5% 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 10 isolates are flagged. In total, 78.6% of all isolates are marked ‘first weighted’ - 50.1% 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>, there’s a shortcut for this new algorithm too:</p> | <p>As with <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code>, there’s a shortcut for this new algorithm too:</p> | ||||||
| <div class="sourceCode" id="cb19"><pre class="downlit"> | <div class="sourceCode" id="cb19"><pre class="downlit"> | ||||||
| <span class="kw">data_1st</span> <span class="op"><-</span> <span class="kw">data</span> <span class="op">%>%</span>  | <span class="kw">data_1st</span> <span class="op"><-</span> <span class="kw">data</span> <span class="op">%>%</span>  | ||||||
|   <span class="fu"><a href="../reference/first_isolate.html">filter_first_weighted_isolate</a></span>() |   <span class="fu"><a href="../reference/first_isolate.html">filter_first_weighted_isolate</a></span>() | ||||||
| </pre></div> | </pre></div> | ||||||
| <p>So we end up with 15,813 isolates for analysis.</p> | <p>So we end up with 15,718 isolates for analysis.</p> | ||||||
| <p>We can remove unneeded columns:</p> | <p>We can remove unneeded columns:</p> | ||||||
| <div class="sourceCode" id="cb20"><pre class="downlit"> | <div class="sourceCode" id="cb20"><pre class="downlit"> | ||||||
| <span class="kw">data_1st</span> <span class="op"><-</span> <span class="kw">data_1st</span> <span class="op">%>%</span>  | <span class="kw">data_1st</span> <span class="op"><-</span> <span class="kw">data_1st</span> <span class="op">%>%</span>  | ||||||
| @@ -857,32 +858,32 @@ Longest: 1</p> | |||||||
| </tr></thead> | </tr></thead> | ||||||
| <tbody> | <tbody> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="left">2</td> | <td align="left">1</td> | ||||||
| <td align="center">2017-04-19</td> | <td align="center">2016-08-26</td> | ||||||
| <td align="center">S1</td> | <td align="center">P9</td> | ||||||
| <td align="center">Hospital C</td> | <td align="center">Hospital C</td> | ||||||
| <td align="center">B_STPHY_AURS</td> | <td align="center">B_ESCHR_COLI</td> | ||||||
|  | <td align="center">I</td> | ||||||
|  | <td align="center">S</td> | ||||||
|  | <td align="center">S</td> | ||||||
|  | <td align="center">R</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">TRUE</td> | ||||||
|  | </tr> | ||||||
|  | <tr class="even"> | ||||||
|  | <td align="left">2</td> | ||||||
|  | <td align="center">2016-09-24</td> | ||||||
|  | <td align="center">T6</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 align="center">S</td> | <td align="center">S</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">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 align="left">3</td> |  | ||||||
| <td align="center">2017-04-21</td> |  | ||||||
| <td align="center">L3</td> |  | ||||||
| <td align="center">Hospital B</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">M</td> |  | ||||||
| <td align="center">Gram-negative</td> | <td align="center">Gram-negative</td> | ||||||
| <td align="center">Escherichia</td> | <td align="center">Escherichia</td> | ||||||
| <td align="center">coli</td> | <td align="center">coli</td> | ||||||
| @@ -890,27 +891,11 @@ Longest: 1</p> | |||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="left">4</td> | <td align="left">4</td> | ||||||
| <td align="center">2011-01-19</td> | <td align="center">2016-12-13</td> | ||||||
| <td align="center">A7</td> | <td align="center">F1</td> | ||||||
| <td align="center">Hospital A</td> | <td align="center">Hospital A</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">S</td> |  | ||||||
| <td align="center">M</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 align="left">5</td> |  | ||||||
| <td align="center">2011-01-24</td> |  | ||||||
| <td align="center">H10</td> |  | ||||||
| <td align="center">Hospital B</td> |  | ||||||
| <td align="center">B_ESCHR_COLI</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">S</td> | <td align="center">S</td> | ||||||
| <td align="center">S</td> | <td align="center">S</td> | ||||||
| @@ -920,31 +905,31 @@ Longest: 1</p> | |||||||
| <td align="center">coli</td> | <td align="center">coli</td> | ||||||
| <td align="center">TRUE</td> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="even"> | ||||||
| <td align="left">6</td> | <td align="left">6</td> | ||||||
| <td align="center">2011-01-31</td> | <td align="center">2017-06-17</td> | ||||||
| <td align="center">T9</td> | <td align="center">K1</td> | ||||||
| <td align="center">Hospital C</td> | <td align="center">Hospital B</td> | ||||||
| <td align="center">B_STRPT_PNMN</td> | <td align="center">B_STRPT_PNMN</td> | ||||||
| <td align="center">R</td> | <td align="center">R</td> | ||||||
| <td align="center">R</td> | <td align="center">R</td> | ||||||
| <td align="center">S</td> | <td align="center">S</td> | ||||||
| <td align="center">R</td> | <td align="center">R</td> | ||||||
| <td align="center">F</td> | <td align="center">M</td> | ||||||
| <td align="center">Gram-positive</td> | <td align="center">Gram-positive</td> | ||||||
| <td align="center">Streptococcus</td> | <td align="center">Streptococcus</td> | ||||||
| <td align="center">pneumoniae</td> | <td align="center">pneumoniae</td> | ||||||
| <td align="center">TRUE</td> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="odd"> | ||||||
| <td align="left">7</td> | <td align="left">8</td> | ||||||
| <td align="center">2012-12-27</td> | <td align="center">2011-02-20</td> | ||||||
| <td align="center">Q9</td> | <td align="center">V8</td> | ||||||
| <td align="center">Hospital A</td> | <td align="center">Hospital D</td> | ||||||
| <td align="center">B_ESCHR_COLI</td> | <td align="center">B_ESCHR_COLI</td> | ||||||
| <td align="center">R</td> | <td align="center">S</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">S</td> | ||||||
| <td align="center">F</td> | <td align="center">F</td> | ||||||
| <td align="center">Gram-negative</td> | <td align="center">Gram-negative</td> | ||||||
| @@ -952,6 +937,22 @@ Longest: 1</p> | |||||||
| <td align="center">coli</td> | <td align="center">coli</td> | ||||||
| <td align="center">TRUE</td> | <td align="center">TRUE</td> | ||||||
| </tr> | </tr> | ||||||
|  | <tr class="even"> | ||||||
|  | <td align="left">9</td> | ||||||
|  | <td align="center">2016-09-22</td> | ||||||
|  | <td align="center">D3</td> | ||||||
|  | <td align="center">Hospital A</td> | ||||||
|  | <td align="center">B_STPHY_AURS</td> | ||||||
|  | <td align="center">R</td> | ||||||
|  | <td align="center">S</td> | ||||||
|  | <td align="center">S</td> | ||||||
|  | <td align="center">R</td> | ||||||
|  | <td align="center">M</td> | ||||||
|  | <td align="center">Gram-positive</td> | ||||||
|  | <td align="center">Staphylococcus</td> | ||||||
|  | <td align="center">aureus</td> | ||||||
|  | <td align="center">TRUE</td> | ||||||
|  | </tr> | ||||||
| </tbody> | </tbody> | ||||||
| </table> | </table> | ||||||
| <p>Time for the analysis!</p> | <p>Time for the analysis!</p> | ||||||
| @@ -975,8 +976,8 @@ Longest: 1</p> | |||||||
| </pre></div> | </pre></div> | ||||||
| <p><strong>Frequency table</strong></p> | <p><strong>Frequency table</strong></p> | ||||||
| <p>Class: character<br> | <p>Class: character<br> | ||||||
| Length: 15,813<br> | Length: 15,718<br> | ||||||
| Available: 15,813 (100%, NA: 0 = 0%)<br> | Available: 15,718 (100%, NA: 0 = 0%)<br> | ||||||
| Unique: 4</p> | Unique: 4</p> | ||||||
| <p>Shortest: 16<br> | <p>Shortest: 16<br> | ||||||
| Longest: 24</p> | Longest: 24</p> | ||||||
| @@ -993,33 +994,33 @@ Longest: 24</p> | |||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="left">1</td> | <td align="left">1</td> | ||||||
| <td align="left">Escherichia coli</td> | <td align="left">Escherichia coli</td> | ||||||
| <td align="right">7,901</td> | <td align="right">7,841</td> | ||||||
| <td align="right">49.97%</td> | <td align="right">49.89%</td> | ||||||
| <td align="right">7,901</td> | <td align="right">7,841</td> | ||||||
| <td align="right">49.97%</td> | <td align="right">49.89%</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="left">2</td> | <td align="left">2</td> | ||||||
| <td align="left">Staphylococcus aureus</td> | <td align="left">Staphylococcus aureus</td> | ||||||
| <td align="right">3,946</td> | <td align="right">3,956</td> | ||||||
| <td align="right">24.95%</td> | <td align="right">25.17%</td> | ||||||
| <td align="right">11,847</td> | <td align="right">11,797</td> | ||||||
| <td align="right">74.92%</td> | <td align="right">75.05%</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="left">3</td> | <td align="left">3</td> | ||||||
| <td align="left">Streptococcus pneumoniae</td> | <td align="left">Streptococcus pneumoniae</td> | ||||||
| <td align="right">2,394</td> | <td align="right">2,346</td> | ||||||
| <td align="right">15.14%</td> | <td align="right">14.93%</td> | ||||||
| <td align="right">14,241</td> | <td align="right">14,143</td> | ||||||
| <td align="right">90.06%</td> | <td align="right">89.98%</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="left">4</td> | <td align="left">4</td> | ||||||
| <td align="left">Klebsiella pneumoniae</td> | <td align="left">Klebsiella pneumoniae</td> | ||||||
| <td align="right">1,572</td> | <td align="right">1,575</td> | ||||||
| <td align="right">9.94%</td> | <td align="right">10.02%</td> | ||||||
| <td align="right">15,813</td> | <td align="right">15,718</td> | ||||||
| <td align="right">100.00%</td> | <td align="right">100.00%</td> | ||||||
| </tr> | </tr> | ||||||
| </tbody> | </tbody> | ||||||
| @@ -1048,50 +1049,50 @@ Longest: 24</p> | |||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">E. coli</td> | <td align="center">E. coli</td> | ||||||
| <td align="center">AMX</td> | <td align="center">AMX</td> | ||||||
| <td align="center">3774</td> | <td align="center">3793</td> | ||||||
| <td align="center">257</td> | <td align="center">242</td> | ||||||
| <td align="center">3870</td> | <td align="center">3806</td> | ||||||
| <td align="center">7901</td> | <td align="center">7841</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">E. coli</td> | <td align="center">E. coli</td> | ||||||
| <td align="center">AMC</td> | <td align="center">AMC</td> | ||||||
| <td align="center">6189</td> | <td align="center">6205</td> | ||||||
| <td align="center">306</td> | <td align="center">301</td> | ||||||
| <td align="center">1406</td> | <td align="center">1335</td> | ||||||
| <td align="center">7901</td> | <td align="center">7841</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">E. coli</td> | <td align="center">E. coli</td> | ||||||
| <td align="center">CIP</td> | <td align="center">CIP</td> | ||||||
| <td align="center">6042</td> | <td align="center">5980</td> | ||||||
| <td align="center">0</td> | <td align="center">0</td> | ||||||
| <td align="center">1859</td> | <td align="center">1861</td> | ||||||
| <td align="center">7901</td> | <td align="center">7841</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">E. coli</td> | <td align="center">E. coli</td> | ||||||
| <td align="center">GEN</td> | <td align="center">GEN</td> | ||||||
| <td align="center">7094</td> | <td align="center">7075</td> | ||||||
| <td align="center">0</td> | <td align="center">0</td> | ||||||
| <td align="center">807</td> | <td align="center">766</td> | ||||||
| <td align="center">7901</td> | <td align="center">7841</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">K. pneumoniae</td> | <td align="center">K. pneumoniae</td> | ||||||
| <td align="center">AMX</td> | <td align="center">AMX</td> | ||||||
| <td align="center">0</td> | <td align="center">0</td> | ||||||
| <td align="center">0</td> | <td align="center">0</td> | ||||||
| <td align="center">1572</td> | <td align="center">1575</td> | ||||||
| <td align="center">1572</td> | <td align="center">1575</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">K. pneumoniae</td> | <td align="center">K. pneumoniae</td> | ||||||
| <td align="center">AMC</td> | <td align="center">AMC</td> | ||||||
| <td align="center">1245</td> | <td align="center">1217</td> | ||||||
| <td align="center">56</td> | <td align="center">77</td> | ||||||
| <td align="center">271</td> | <td align="center">281</td> | ||||||
| <td align="center">1572</td> | <td align="center">1575</td> | ||||||
| </tr> | </tr> | ||||||
| </tbody> | </tbody> | ||||||
| </table> | </table> | ||||||
| @@ -1116,34 +1117,34 @@ Longest: 24</p> | |||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">E. coli</td> | <td align="center">E. coli</td> | ||||||
| <td align="center">CIP</td> | <td align="center">CIP</td> | ||||||
| <td align="center">6042</td> | <td align="center">5980</td> | ||||||
| <td align="center">0</td> | <td align="center">0</td> | ||||||
| <td align="center">1859</td> | <td align="center">1861</td> | ||||||
| <td align="center">7901</td> | <td align="center">7841</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">K. pneumoniae</td> | <td align="center">K. pneumoniae</td> | ||||||
| <td align="center">CIP</td> | <td align="center">CIP</td> | ||||||
| <td align="center">1182</td> | <td align="center">1207</td> | ||||||
| <td align="center">0</td> | <td align="center">0</td> | ||||||
| <td align="center">390</td> | <td align="center">368</td> | ||||||
| <td align="center">1572</td> | <td align="center">1575</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">S. aureus</td> | <td align="center">S. aureus</td> | ||||||
| <td align="center">CIP</td> | <td align="center">CIP</td> | ||||||
| <td align="center">2966</td> | <td align="center">2971</td> | ||||||
| <td align="center">0</td> | <td align="center">0</td> | ||||||
| <td align="center">980</td> | <td align="center">985</td> | ||||||
| <td align="center">3946</td> | <td align="center">3956</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">S. pneumoniae</td> | <td align="center">S. pneumoniae</td> | ||||||
| <td align="center">CIP</td> | <td align="center">CIP</td> | ||||||
| <td align="center">1834</td> | <td align="center">1790</td> | ||||||
| <td align="center">0</td> | <td align="center">0</td> | ||||||
| <td align="center">560</td> | <td align="center">556</td> | ||||||
| <td align="center">2394</td> | <td align="center">2346</td> | ||||||
| </tr> | </tr> | ||||||
| </tbody> | </tbody> | ||||||
| </table> | </table> | ||||||
| @@ -1156,7 +1157,7 @@ Longest: 24</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> | <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="cb28"><pre class="downlit"> | <div class="sourceCode" id="cb28"><pre class="downlit"> | ||||||
| <span class="kw">data_1st</span> <span class="op">%>%</span> <span class="fu"><a href="../reference/proportion.html">resistance</a></span>(<span class="kw">AMX</span>) | <span class="kw">data_1st</span> <span class="op">%>%</span> <span class="fu"><a href="../reference/proportion.html">resistance</a></span>(<span class="kw">AMX</span>) | ||||||
| <span class="co"># [1] 0.5330424</span> | <span class="co"># [1] 0.5318107</span> | ||||||
| </pre></div> | </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> | <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="cb29"><pre class="downlit"> | <div class="sourceCode" id="cb29"><pre class="downlit"> | ||||||
| @@ -1173,19 +1174,19 @@ Longest: 24</p> | |||||||
| <tbody> | <tbody> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">Hospital A</td> | <td align="center">Hospital A</td> | ||||||
| <td align="center">0.5262478</td> | <td align="center">0.5401506</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">Hospital B</td> | <td align="center">Hospital B</td> | ||||||
| <td align="center">0.5401022</td> | <td align="center">0.5244014</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">Hospital C</td> | <td align="center">Hospital C</td> | ||||||
| <td align="center">0.5257556</td> | <td align="center">0.5256917</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">Hospital D</td> | <td align="center">Hospital D</td> | ||||||
| <td align="center">0.5357938</td> | <td align="center">0.5363864</td> | ||||||
| </tr> | </tr> | ||||||
| </tbody> | </tbody> | ||||||
| </table> | </table> | ||||||
| @@ -1206,23 +1207,23 @@ Longest: 24</p> | |||||||
| <tbody> | <tbody> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">Hospital A</td> | <td align="center">Hospital A</td> | ||||||
| <td align="center">0.5262478</td> | <td align="center">0.5401506</td> | ||||||
| <td align="center">4648</td> | <td align="center">4782</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">Hospital B</td> | <td align="center">Hospital B</td> | ||||||
| <td align="center">0.5401022</td> | <td align="center">0.5244014</td> | ||||||
| <td align="center">5673</td> | <td align="center">5471</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">Hospital C</td> | <td align="center">Hospital C</td> | ||||||
| <td align="center">0.5257556</td> | <td align="center">0.5256917</td> | ||||||
| <td align="center">2349</td> | <td align="center">2277</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">Hospital D</td> | <td align="center">Hospital D</td> | ||||||
| <td align="center">0.5357938</td> | <td align="center">0.5363864</td> | ||||||
| <td align="center">3143</td> | <td align="center">3188</td> | ||||||
| </tr> | </tr> | ||||||
| </tbody> | </tbody> | ||||||
| </table> | </table> | ||||||
| @@ -1245,27 +1246,27 @@ Longest: 24</p> | |||||||
| <tbody> | <tbody> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">Escherichia</td> | <td align="center">Escherichia</td> | ||||||
| <td align="center">0.8220478</td> | <td align="center">0.8297411</td> | ||||||
| <td align="center">0.8978610</td> | <td align="center">0.9023084</td> | ||||||
| <td align="center">0.9860777</td> | <td align="center">0.9858436</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">Klebsiella</td> | <td align="center">Klebsiella</td> | ||||||
| <td align="center">0.8276081</td> | <td align="center">0.8215873</td> | ||||||
| <td align="center">0.9001272</td> | <td align="center">0.9060317</td> | ||||||
| <td align="center">0.9860051</td> | <td align="center">0.9879365</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="center">Staphylococcus</td> | <td align="center">Staphylococcus</td> | ||||||
| <td align="center">0.8335023</td> | <td align="center">0.8276036</td> | ||||||
| <td align="center">0.9206792</td> | <td align="center">0.9160768</td> | ||||||
| <td align="center">0.9878358</td> | <td align="center">0.9848332</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="center">Streptococcus</td> | <td align="center">Streptococcus</td> | ||||||
| <td align="center">0.5396825</td> | <td align="center">0.5392157</td> | ||||||
| <td align="center">0.0000000</td> | <td align="center">0.0000000</td> | ||||||
| <td align="center">0.5396825</td> | <td align="center">0.5392157</td> | ||||||
| </tr> | </tr> | ||||||
| </tbody> | </tbody> | ||||||
| </table> | </table> | ||||||
|   | |||||||
| Before Width: | Height: | Size: 64 KiB After Width: | Height: | Size: 64 KiB | 
| Before Width: | Height: | Size: 51 KiB After Width: | Height: | Size: 51 KiB | 
| Before Width: | Height: | Size: 102 KiB After Width: | Height: | Size: 102 KiB | 
| Before Width: | Height: | Size: 83 KiB After Width: | Height: | Size: 83 KiB | 
| @@ -20,7 +20,7 @@ | |||||||
| <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | ||||||
| <script src="../extra.js"></script><meta property="og:title" content="How to apply EUCAST rules"> | <script src="../extra.js"></script><meta property="og:title" content="How to apply EUCAST rules"> | ||||||
| <meta property="og:description" content="AMR"> | <meta property="og:description" content="AMR"> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg"> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png"> | ||||||
| <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | ||||||
| <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | ||||||
| <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | ||||||
| @@ -39,7 +39,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -207,7 +207,8 @@ | |||||||
| <blockquote> | <blockquote> | ||||||
| <p><em>EUCAST expert rules are a tabulated collection of expert knowledge on intrinsic resistances, exceptional resistance phenotypes and interpretive rules that may be applied to antimicrobial susceptibility testing in order to reduce errors and make appropriate recommendations for reporting particular resistances.</em></p> | <p><em>EUCAST expert rules are a tabulated collection of expert knowledge on intrinsic resistances, exceptional resistance phenotypes and interpretive rules that may be applied to antimicrobial susceptibility testing in order to reduce errors and make appropriate recommendations for reporting particular resistances.</em></p> | ||||||
| </blockquote> | </blockquote> | ||||||
| <p>In Europe, a lot of medical microbiological laboratories already apply these rules (<a href="https://www.eurosurveillance.org/content/10.2807/1560-7917.ES2015.20.2.21008">Brown <em>et al.</em>, 2015</a>). Our package features their latest insights on intrinsic resistance and exceptional phenotypes (version 10.0, 2020). Moreover, the <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> function we use for this purpose can also apply additional rules, like forcing <help title="ATC: J01CA01">ampicillin</help> = R in isolates when <help title="ATC: J01CR02">amoxicillin/clavulanic acid</help> = R.</p> | <p>In Europe, a lot of medical microbiological laboratories already apply these rules (<a href="https://www.eurosurveillance.org/content/10.2807/1560-7917.ES2015.20.2.21008">Brown <em>et al.</em>, 2015</a>). Our package features their latest insights on intrinsic resistance and unusual phenotypes (v3.2, 2020).</p> | ||||||
|  | <p>Moreover, the <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> function we use for this purpose can also apply additional rules, like forcing <help title="ATC: J01CA01">ampicillin</help> = R in isolates when <help title="ATC: J01CR02">amoxicillin/clavulanic acid</help> = R.</p> | ||||||
| </div> | </div> | ||||||
| <div id="examples" class="section level2"> | <div id="examples" class="section level2"> | ||||||
| <h2 class="hasAnchor"> | <h2 class="hasAnchor"> | ||||||
| @@ -240,7 +241,7 @@ | |||||||
|                    COL = <span class="st">"-"</span>,       <span class="co"># Colistin</span> |                    COL = <span class="st">"-"</span>,       <span class="co"># Colistin</span> | ||||||
|                    CAZ = <span class="st">"-"</span>,       <span class="co"># Ceftazidime</span> |                    CAZ = <span class="st">"-"</span>,       <span class="co"># Ceftazidime</span> | ||||||
|                    CXM = <span class="st">"-"</span>,       <span class="co"># Cefuroxime</span> |                    CXM = <span class="st">"-"</span>,       <span class="co"># Cefuroxime</span> | ||||||
|                    PEN = <span class="st">"S"</span>,       <span class="co"># Penicillin G</span> |                    PEN = <span class="st">"S"</span>,       <span class="co"># Benzylenicillin</span> | ||||||
|                    FOX = <span class="st">"S"</span>,       <span class="co"># Cefoxitin</span> |                    FOX = <span class="st">"S"</span>,       <span class="co"># Cefoxitin</span> | ||||||
|                    stringsAsFactors = <span class="fl">FALSE</span>) |                    stringsAsFactors = <span class="fl">FALSE</span>) | ||||||
| </pre></div> | </pre></div> | ||||||
| @@ -314,8 +315,6 @@ | |||||||
| <div class="sourceCode" id="cb4"><pre class="downlit"> | <div class="sourceCode" id="cb4"><pre class="downlit"> | ||||||
| <span class="fu"><a href="../reference/eucast_rules.html">eucast_rules</a></span>(<span class="kw">data</span>) | <span class="fu"><a href="../reference/eucast_rules.html">eucast_rules</a></span>(<span class="kw">data</span>) | ||||||
| </pre></div> | </pre></div> | ||||||
| <pre><code># Warning: Not all columns with antimicrobial results are of class <rsi>. |  | ||||||
| # Transform eligible columns to class <rsi> on beforehand: your_data %>% mutate_if(is.rsi.eligible, as.rsi)</code></pre> |  | ||||||
| <table class="table"> | <table class="table"> | ||||||
| <thead><tr class="header"> | <thead><tr class="header"> | ||||||
| <th align="left">mo</th> | <th align="left">mo</th> | ||||||
|   | |||||||
| @@ -20,7 +20,7 @@ | |||||||
| <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | ||||||
| <script src="../extra.js"></script><meta property="og:title" content="How to determine multi-drug resistance (MDR)"> | <script src="../extra.js"></script><meta property="og:title" content="How to determine multi-drug resistance (MDR)"> | ||||||
| <meta property="og:description" content="AMR"> | <meta property="og:description" content="AMR"> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg"> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png"> | ||||||
| <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | ||||||
| <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | ||||||
| <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | ||||||
| @@ -39,7 +39,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -247,9 +247,6 @@ | |||||||
| <span class="kw">example_isolates</span> <span class="op">%>%</span>  | <span class="kw">example_isolates</span> <span class="op">%>%</span>  | ||||||
|   <span class="fu"><a href="../reference/mdro.html">mdro</a></span>() <span class="op">%>%</span>  |   <span class="fu"><a href="../reference/mdro.html">mdro</a></span>() <span class="op">%>%</span>  | ||||||
|   <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>() <span class="co"># show frequency table of the result</span> |   <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span>() <span class="co"># show frequency table of the result</span> | ||||||
| <span class="co"># NOTE: Using column `mo` as input for `col_mo`.</span> |  | ||||||
| <span class="co"># NOTE: Auto-guessing columns suitable for analysis...OK.</span> |  | ||||||
| <span class="co"># NOTE: Reliability would be improved if these antimicrobial results would be available too: ceftaroline (CPT), fusidic acid (FUS), telavancin (TLV), daptomycin (DAP), quinupristin/dalfopristin (QDA), minocycline (MNO), gentamicin-high (GEH), streptomycin-high (STH), doripenem (DOR), levofloxacin (LVX), netilmicin (NET), ticarcillin/clavulanic acid (TCC), ertapenem (ETP), cefotetan (CTT), aztreonam (ATM), ampicillin/sulbactam (SAM), polymyxin B (PLB)</span> |  | ||||||
| <span class="co"># Warning in mdro(.): NA introduced for isolates where the available percentage of</span> | <span class="co"># Warning in mdro(.): NA introduced for isolates where the available percentage of</span> | ||||||
| <span class="co"># antimicrobial classes was below 50% (set with `pct_required_classes`)</span> | <span class="co"># antimicrobial classes was below 50% (set with `pct_required_classes`)</span> | ||||||
| </pre></div> | </pre></div> | ||||||
| @@ -257,7 +254,7 @@ | |||||||
| <p>Class: factor > ordered (numeric)<br> | <p>Class: factor > ordered (numeric)<br> | ||||||
| Length: 2,000<br> | Length: 2,000<br> | ||||||
| Levels: 4: Negative < Multi-drug-resistant (MDR) < Extensively drug-resistant …<br> | Levels: 4: Negative < Multi-drug-resistant (MDR) < Extensively drug-resistant …<br> | ||||||
| Available: 1,711 (85.55%, NA: 289 = 14.45%)<br> | Available: 1,747 (87.35%, NA: 253 = 12.65%)<br> | ||||||
| Unique: 2</p> | Unique: 2</p> | ||||||
| <table class="table"> | <table class="table"> | ||||||
| <thead><tr class="header"> | <thead><tr class="header"> | ||||||
| @@ -272,17 +269,17 @@ Unique: 2</p> | |||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="left">1</td> | <td align="left">1</td> | ||||||
| <td align="left">Negative</td> | <td align="left">Negative</td> | ||||||
| <td align="right">1595</td> | <td align="right">1616</td> | ||||||
| <td align="right">93.22%</td> | <td align="right">92.50%</td> | ||||||
| <td align="right">1595</td> | <td align="right">1616</td> | ||||||
| <td align="right">93.22%</td> | <td align="right">92.50%</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="left">2</td> | <td align="left">2</td> | ||||||
| <td align="left">Multi-drug-resistant (MDR)</td> | <td align="left">Multi-drug-resistant (MDR)</td> | ||||||
| <td align="right">116</td> | <td align="right">131</td> | ||||||
| <td align="right">6.78%</td> | <td align="right">7.50%</td> | ||||||
| <td align="right">1711</td> | <td align="right">1747</td> | ||||||
| <td align="right">100.00%</td> | <td align="right">100.00%</td> | ||||||
| </tr> | </tr> | ||||||
| </tbody> | </tbody> | ||||||
| @@ -320,18 +317,18 @@ Unique: 2</p> | |||||||
| <div class="sourceCode" id="cb5"><pre class="downlit"> | <div class="sourceCode" id="cb5"><pre class="downlit"> | ||||||
| <span class="fu"><a href="https://rdrr.io/r/utils/head.html">head</a></span>(<span class="kw">my_TB_data</span>) | <span class="fu"><a href="https://rdrr.io/r/utils/head.html">head</a></span>(<span class="kw">my_TB_data</span>) | ||||||
| <span class="co">#   rifampicin isoniazid gatifloxacin ethambutol pyrazinamide moxifloxacin</span> | <span class="co">#   rifampicin isoniazid gatifloxacin ethambutol pyrazinamide moxifloxacin</span> | ||||||
| <span class="co"># 1          S         R            S          S            R            S</span> | <span class="co"># 1          I         R            S          R            R            S</span> | ||||||
| <span class="co"># 2          S         R            R          S            R            S</span> | <span class="co"># 2          R         R            S          S            S            R</span> | ||||||
| <span class="co"># 3          S         R            R          S            S            R</span> | <span class="co"># 3          S         S            R          S            S            S</span> | ||||||
| <span class="co"># 4          R         R            S          S            S            R</span> | <span class="co"># 4          R         R            R          S            R            R</span> | ||||||
| <span class="co"># 5          I         S            I          S            S            S</span> | <span class="co"># 5          S         R            S          R            R            S</span> | ||||||
| <span class="co"># 6          S         S            R          R            S            S</span> | <span class="co"># 6          S         S            R          R            R            S</span> | ||||||
| <span class="co">#   kanamycin</span> | <span class="co">#   kanamycin</span> | ||||||
| <span class="co"># 1         R</span> | <span class="co"># 1         I</span> | ||||||
| <span class="co"># 2         I</span> | <span class="co"># 2         R</span> | ||||||
| <span class="co"># 3         S</span> | <span class="co"># 3         R</span> | ||||||
| <span class="co"># 4         R</span> | <span class="co"># 4         R</span> | ||||||
| <span class="co"># 5         S</span> | <span class="co"># 5         R</span> | ||||||
| <span class="co"># 6         S</span> | <span class="co"># 6         S</span> | ||||||
| </pre></div> | </pre></div> | ||||||
| <p>We can now add the interpretation of MDR-TB to our data set. You can use:</p> | <p>We can now add the interpretation of MDR-TB to our data set. You can use:</p> | ||||||
| @@ -342,8 +339,6 @@ Unique: 2</p> | |||||||
| <div class="sourceCode" id="cb7"><pre class="downlit"> | <div class="sourceCode" id="cb7"><pre class="downlit"> | ||||||
| <span class="kw">my_TB_data</span><span class="op">$</span><span class="kw">mdr</span> <span class="op"><-</span> <span class="fu"><a href="../reference/mdro.html">mdr_tb</a></span>(<span class="kw">my_TB_data</span>) | <span class="kw">my_TB_data</span><span class="op">$</span><span class="kw">mdr</span> <span class="op"><-</span> <span class="fu"><a href="../reference/mdro.html">mdr_tb</a></span>(<span class="kw">my_TB_data</span>) | ||||||
| <span class="co"># NOTE: No column found as input for `col_mo`, assuming all records contain Mycobacterium tuberculosis.</span> | <span class="co"># NOTE: No column found as input for `col_mo`, assuming all records contain Mycobacterium tuberculosis.</span> | ||||||
| <span class="co"># NOTE: Auto-guessing columns suitable for analysis...OK.</span> |  | ||||||
| <span class="co"># NOTE: Reliability would be improved if these antimicrobial results would be available too: capreomycin (CAP), rifabutin (RIB), rifapentine (RFP)</span> |  | ||||||
| </pre></div> | </pre></div> | ||||||
| <p>Create a frequency table of the results:</p> | <p>Create a frequency table of the results:</p> | ||||||
| <div class="sourceCode" id="cb8"><pre class="downlit"> | <div class="sourceCode" id="cb8"><pre class="downlit"> | ||||||
| @@ -368,40 +363,40 @@ Unique: 5</p> | |||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="left">1</td> | <td align="left">1</td> | ||||||
| <td align="left">Mono-resistant</td> | <td align="left">Mono-resistant</td> | ||||||
| <td align="right">3297</td> | <td align="right">3235</td> | ||||||
| <td align="right">65.94%</td> | <td align="right">64.70%</td> | ||||||
| <td align="right">3297</td> | <td align="right">3235</td> | ||||||
| <td align="right">65.94%</td> | <td align="right">64.70%</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="left">2</td> | <td align="left">2</td> | ||||||
| <td align="left">Multi-drug-resistant</td> | <td align="left">Negative</td> | ||||||
| <td align="right">614</td> | <td align="right">657</td> | ||||||
| <td align="right">12.28%</td> | <td align="right">13.14%</td> | ||||||
| <td align="right">3911</td> | <td align="right">3892</td> | ||||||
| <td align="right">78.22%</td> | <td align="right">77.84%</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="left">3</td> | <td align="left">3</td> | ||||||
| <td align="left">Negative</td> | <td align="left">Multi-drug-resistant</td> | ||||||
| <td align="right">603</td> | <td align="right">595</td> | ||||||
| <td align="right">12.06%</td> | <td align="right">11.90%</td> | ||||||
| <td align="right">4514</td> | <td align="right">4487</td> | ||||||
| <td align="right">90.28%</td> | <td align="right">89.74%</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="even"> | <tr class="even"> | ||||||
| <td align="left">4</td> | <td align="left">4</td> | ||||||
| <td align="left">Poly-resistant</td> | <td align="left">Poly-resistant</td> | ||||||
| <td align="right">278</td> | <td align="right">306</td> | ||||||
| <td align="right">5.56%</td> | <td align="right">6.12%</td> | ||||||
| <td align="right">4792</td> | <td align="right">4793</td> | ||||||
| <td align="right">95.84%</td> | <td align="right">95.86%</td> | ||||||
| </tr> | </tr> | ||||||
| <tr class="odd"> | <tr class="odd"> | ||||||
| <td align="left">5</td> | <td align="left">5</td> | ||||||
| <td align="left">Extensively drug-resistant</td> | <td align="left">Extensively drug-resistant</td> | ||||||
| <td align="right">208</td> | <td align="right">207</td> | ||||||
| <td align="right">4.16%</td> | <td align="right">4.14%</td> | ||||||
| <td align="right">5000</td> | <td align="right">5000</td> | ||||||
| <td align="right">100.00%</td> | <td align="right">100.00%</td> | ||||||
| </tr> | </tr> | ||||||
|   | |||||||
| @@ -20,7 +20,7 @@ | |||||||
| <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | ||||||
| <script src="../extra.js"></script><meta property="og:title" content="How to conduct principal component analysis (PCA) for AMR"> | <script src="../extra.js"></script><meta property="og:title" content="How to conduct principal component analysis (PCA) for AMR"> | ||||||
| <meta property="og:description" content="AMR"> | <meta property="og:description" content="AMR"> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg"> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png"> | ||||||
| <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | ||||||
| <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | ||||||
| <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | ||||||
| @@ -39,7 +39,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -227,9 +227,9 @@ | |||||||
| <span class="co"># $ PEN             <rsi> R, R, R, R, R, R, R, R, R, R, R, R, R, R, R, R, R, R,…</span> | <span class="co"># $ PEN             <rsi> R, R, R, R, R, R, R, R, R, R, R, R, R, R, R, R, R, R,…</span> | ||||||
| <span class="co"># $ OXA             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, N…</span> | <span class="co"># $ OXA             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, N…</span> | ||||||
| <span class="co"># $ FLC             <rsi> NA, NA, R, R, R, R, S, S, R, S, S, S, NA, NA, NA, NA,…</span> | <span class="co"># $ FLC             <rsi> NA, NA, R, R, R, R, S, S, R, S, S, S, NA, NA, NA, NA,…</span> | ||||||
| <span class="co"># $ AMX             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, N…</span> | <span class="co"># $ AMX             <rsi> NA, NA, NA, NA, NA, NA, R, R, NA, NA, NA, NA, NA, NA,…</span> | ||||||
| <span class="co"># $ AMC             <rsi> I, I, NA, NA, NA, NA, S, S, NA, NA, S, S, I, I, R, I,…</span> | <span class="co"># $ AMC             <rsi> I, I, NA, NA, NA, NA, S, S, NA, NA, S, S, I, I, R, I,…</span> | ||||||
| <span class="co"># $ AMP             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, N…</span> | <span class="co"># $ AMP             <rsi> NA, NA, NA, NA, NA, NA, R, R, NA, NA, NA, NA, NA, NA,…</span> | ||||||
| <span class="co"># $ TZP             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, N…</span> | <span class="co"># $ TZP             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, N…</span> | ||||||
| <span class="co"># $ CZO             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, N…</span> | <span class="co"># $ CZO             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, N…</span> | ||||||
| <span class="co"># $ FEP             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, N…</span> | <span class="co"># $ FEP             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, N…</span> | ||||||
| @@ -252,10 +252,10 @@ | |||||||
| <span class="co"># $ VAN             <rsi> R, R, S, S, S, S, S, S, S, S, NA, NA, R, R, R, R, R, …</span> | <span class="co"># $ VAN             <rsi> R, R, S, S, S, S, S, S, S, S, NA, NA, R, R, R, R, R, …</span> | ||||||
| <span class="co"># $ TEC             <rsi> R, R, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, R, R, R…</span> | <span class="co"># $ TEC             <rsi> R, R, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, R, R, R…</span> | ||||||
| <span class="co"># $ TCY             <rsi> R, R, S, S, S, S, S, S, S, I, S, S, NA, NA, I, R, R, …</span> | <span class="co"># $ TCY             <rsi> R, R, S, S, S, S, S, S, S, I, S, S, NA, NA, I, R, R, …</span> | ||||||
| <span class="co"># $ TGC             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, N…</span> | <span class="co"># $ TGC             <rsi> NA, NA, S, S, S, S, S, S, S, NA, S, S, NA, NA, NA, R,…</span> | ||||||
| <span class="co"># $ DOX             <rsi> NA, NA, S, S, S, S, S, S, S, NA, S, S, NA, NA, NA, R,…</span> | <span class="co"># $ DOX             <rsi> NA, NA, S, S, S, S, S, S, S, NA, S, S, NA, NA, NA, R,…</span> | ||||||
| <span class="co"># $ ERY             <rsi> R, R, R, R, R, R, S, S, R, S, S, S, R, R, R, R, R, R,…</span> | <span class="co"># $ ERY             <rsi> R, R, R, R, R, R, S, S, R, S, S, S, R, R, R, R, R, R,…</span> | ||||||
| <span class="co"># $ CLI             <rsi> NA, NA, NA, NA, NA, R, NA, NA, NA, NA, NA, NA, NA, NA…</span> | <span class="co"># $ CLI             <rsi> R, R, NA, NA, NA, R, NA, NA, NA, NA, NA, NA, R, R, R,…</span> | ||||||
| <span class="co"># $ AZM             <rsi> R, R, R, R, R, R, S, S, R, S, S, S, R, R, R, R, R, R,…</span> | <span class="co"># $ AZM             <rsi> R, R, R, R, R, R, S, S, R, S, S, S, R, R, R, R, R, R,…</span> | ||||||
| <span class="co"># $ IPM             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, S, S,…</span> | <span class="co"># $ IPM             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, S, S,…</span> | ||||||
| <span class="co"># $ MEM             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, N…</span> | <span class="co"># $ MEM             <rsi> NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, NA, N…</span> | ||||||
| @@ -301,9 +301,9 @@ | |||||||
| <span class="fu"><a href="https://rdrr.io/r/base/summary.html">summary</a></span>(<span class="kw">pca_result</span>) | <span class="fu"><a href="https://rdrr.io/r/base/summary.html">summary</a></span>(<span class="kw">pca_result</span>) | ||||||
| <span class="co"># Importance of components:</span> | <span class="co"># Importance of components:</span> | ||||||
| <span class="co">#                          PC1    PC2     PC3     PC4     PC5     PC6       PC7</span> | <span class="co">#                          PC1    PC2     PC3     PC4     PC5     PC6       PC7</span> | ||||||
| <span class="co"># Standard deviation     2.154 1.6809 0.61305 0.33882 0.20755 0.03137 1.602e-16</span> | <span class="co"># Standard deviation     2.154 1.6807 0.61365 0.33902 0.20757 0.03136 1.733e-16</span> | ||||||
| <span class="co"># Proportion of Variance 0.580 0.3532 0.04698 0.01435 0.00538 0.00012 0.000e+00</span> | <span class="co"># Proportion of Variance 0.580 0.3531 0.04707 0.01437 0.00539 0.00012 0.000e+00</span> | ||||||
| <span class="co"># Cumulative Proportion  0.580 0.9332 0.98014 0.99449 0.99988 1.00000 1.000e+00</span> | <span class="co"># Cumulative Proportion  0.580 0.9331 0.98012 0.99449 0.99988 1.00000 1.000e+00</span> | ||||||
| </pre></div> | </pre></div> | ||||||
| <p>Good news. The first two components explain a total of 93.3% of the variance (see the PC1 and PC2 values of the <em>Proportion of Variance</em>. We can create a so-called biplot with the base R <code><a href="https://rdrr.io/r/stats/biplot.html">biplot()</a></code> function, to see which antimicrobial resistance per drug explain the difference per microorganism.</p> | <p>Good news. The first two components explain a total of 93.3% of the variance (see the PC1 and PC2 values of the <em>Proportion of Variance</em>. We can create a so-called biplot with the base R <code><a href="https://rdrr.io/r/stats/biplot.html">biplot()</a></code> function, to see which antimicrobial resistance per drug explain the difference per microorganism.</p> | ||||||
| </div> | </div> | ||||||
|   | |||||||
| Before Width: | Height: | Size: 86 KiB After Width: | Height: | Size: 86 KiB | 
| Before Width: | Height: | Size: 144 KiB After Width: | Height: | Size: 143 KiB | 
| Before Width: | Height: | Size: 148 KiB After Width: | Height: | Size: 148 KiB | 
| @@ -20,7 +20,7 @@ | |||||||
| <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | ||||||
| <script src="../extra.js"></script><meta property="og:title" content="How to import data from SPSS / SAS / Stata"> | <script src="../extra.js"></script><meta property="og:title" content="How to import data from SPSS / SAS / Stata"> | ||||||
| <meta property="og:description" content="AMR"> | <meta property="og:description" content="AMR"> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg"> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png"> | ||||||
| <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | ||||||
| <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | ||||||
| <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | ||||||
| @@ -39,7 +39,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -193,7 +193,7 @@ | |||||||
|       <h1 data-toc-skip>How to import data from SPSS / SAS / Stata</h1> |       <h1 data-toc-skip>How to import data from SPSS / SAS / Stata</h1> | ||||||
|                         <h4 class="author">Matthijs S. Berends</h4> |                         <h4 class="author">Matthijs S. Berends</h4> | ||||||
|              |              | ||||||
|             <h4 class="date">03 September 2020</h4> |             <h4 class="date">30 September 2020</h4> | ||||||
|        |        | ||||||
|       <small class="dont-index">Source: <a href="https://github.com/msberends/AMR/blob/master/vignettes/SPSS.Rmd"><code>vignettes/SPSS.Rmd</code></a></small> |       <small class="dont-index">Source: <a href="https://github.com/msberends/AMR/blob/master/vignettes/SPSS.Rmd"><code>vignettes/SPSS.Rmd</code></a></small> | ||||||
|       <div class="hidden name"><code>SPSS.Rmd</code></div> |       <div class="hidden name"><code>SPSS.Rmd</code></div> | ||||||
|   | |||||||
| @@ -20,7 +20,7 @@ | |||||||
| <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | ||||||
| <script src="../extra.js"></script><meta property="og:title" content="How to work with WHONET data"> | <script src="../extra.js"></script><meta property="og:title" content="How to work with WHONET data"> | ||||||
| <meta property="og:description" content="AMR"> | <meta property="og:description" content="AMR"> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg"> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png"> | ||||||
| <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | ||||||
| <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | ||||||
| <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | ||||||
| @@ -39,7 +39,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -20,7 +20,7 @@ | |||||||
| <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | ||||||
| <script src="../extra.js"></script><meta property="og:title" content="Benchmarks"> | <script src="../extra.js"></script><meta property="og:title" content="Benchmarks"> | ||||||
| <meta property="og:description" content="AMR"> | <meta property="og:description" content="AMR"> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg"> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png"> | ||||||
| <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | ||||||
| <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | ||||||
| <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | ||||||
| @@ -39,7 +39,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9016</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -226,49 +226,6 @@ | |||||||
|   <span class="fu"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"VISA"</span>), <span class="co"># Vancomycin Intermediate S. aureus</span> |   <span class="fu"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"VISA"</span>), <span class="co"># Vancomycin Intermediate S. aureus</span> | ||||||
|   <span class="fu"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"VRSA"</span>), <span class="co"># Vancomycin Resistant S. aureus</span> |   <span class="fu"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"VRSA"</span>), <span class="co"># Vancomycin Resistant S. aureus</span> | ||||||
|   times = <span class="fl">10</span>) |   times = <span class="fl">10</span>) | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| @@ -276,32 +233,75 @@ | |||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span> |  | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span>(<span class="kw">S.aureus</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">2</span>) | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
|  | <span class="fu"><a href="https://docs.ropensci.org/skimr/reference/print.html">print</a></span>(<span class="kw">S.aureus</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">2</span>) | ||||||
| <span class="co"># Unit: milliseconds</span> | <span class="co"># Unit: milliseconds</span> | ||||||
| <span class="co">#                                   expr   min    lq  mean median    uq  max</span> | <span class="co">#                                   expr   min    lq  mean median    uq    max</span> | ||||||
| <span class="co">#                           as.mo("sau")   9.9  13.0  24.0   17.0  39.0   45</span> | <span class="co">#                           as.mo("sau")  13.0  14.0  15.0   14.0  16.0   17.0</span> | ||||||
| <span class="co">#                          as.mo("stau") 200.0 210.0 240.0  240.0 260.0  290</span> | <span class="co">#                          as.mo("stau") 220.0 230.0 250.0  260.0 280.0  280.0</span> | ||||||
| <span class="co">#                          as.mo("STAU") 190.0 220.0 230.0  220.0 260.0  270</span> | <span class="co">#                          as.mo("STAU") 220.0 240.0 270.0  250.0 290.0  330.0</span> | ||||||
| <span class="co">#                        as.mo("staaur")   9.4  13.0  26.0   15.0  44.0   47</span> | <span class="co">#                        as.mo("staaur")  13.0  14.0  28.0   15.0  44.0   62.0</span> | ||||||
| <span class="co">#                        as.mo("STAAUR")   9.3  11.0  18.0   14.0  15.0   45</span> | <span class="co">#                        as.mo("STAAUR")  11.0  14.0  17.0   14.0  15.0   48.0</span> | ||||||
| <span class="co">#                     as.mo("S. aureus")  21.0  25.0  30.0   26.0  26.0   50</span> | <span class="co">#                     as.mo("S. aureus")  30.0  56.0  56.0   61.0  63.0   66.0</span> | ||||||
| <span class="co">#                      as.mo("S aureus")  25.0  47.0  48.0   51.0  56.0   64</span> | <span class="co">#                      as.mo("S aureus")  28.0  33.0  48.0   38.0  66.0   77.0</span> | ||||||
| <span class="co">#         as.mo("Staphylococcus aureus")   1.5   1.9   2.3    2.4   2.5    3</span> | <span class="co">#         as.mo("Staphylococcus aureus")   1.7   1.9   2.4    2.5   2.6    3.1</span> | ||||||
| <span class="co">#  as.mo("Staphylococcus aureus (MRSA)") 860.0 900.0 930.0  920.0 950.0 1100</span> | <span class="co">#  as.mo("Staphylococcus aureus (MRSA)") 860.0 890.0 920.0  910.0 930.0 1000.0</span> | ||||||
| <span class="co">#       as.mo("Sthafilokkockus aaureuz") 410.0 420.0 430.0  430.0 450.0  460</span> | <span class="co">#       as.mo("Sthafilokkockus aaureuz") 350.0 370.0 380.0  390.0 390.0  410.0</span> | ||||||
| <span class="co">#                          as.mo("MRSA")  12.0  13.0  16.0   14.0  15.0   41</span> | <span class="co">#                          as.mo("MRSA")  13.0  15.0  28.0   18.0  42.0   61.0</span> | ||||||
| <span class="co">#                          as.mo("VISA")  15.0  21.0  38.0   22.0  47.0  130</span> | <span class="co">#                          as.mo("VISA")  21.0  22.0  31.0   22.0  43.0   52.0</span> | ||||||
| <span class="co">#                          as.mo("VRSA")  18.0  20.0  25.0   22.0  22.0   47</span> | <span class="co">#                          as.mo("VRSA")  23.0  24.0  39.0   45.0  49.0   55.0</span> | ||||||
| <span class="co">#  neval</span> | <span class="co">#  neval</span> | ||||||
| <span class="co">#     10</span> | <span class="co">#     10</span> | ||||||
| <span class="co">#     10</span> | <span class="co">#     10</span> | ||||||
| @@ -343,12 +343,12 @@ | |||||||
| <span class="co"># now let's see:</span> | <span class="co"># now let's see:</span> | ||||||
| <span class="kw">run_it</span> <span class="op"><-</span> <span class="fu">microbenchmark</span>(<span class="fu"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="kw">x</span>), | <span class="kw">run_it</span> <span class="op"><-</span> <span class="fu">microbenchmark</span>(<span class="fu"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="kw">x</span>), | ||||||
|                          times = <span class="fl">10</span>) |                          times = <span class="fl">10</span>) | ||||||
| <span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span>(<span class="kw">run_it</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">3</span>) | <span class="fu"><a href="https://docs.ropensci.org/skimr/reference/print.html">print</a></span>(<span class="kw">run_it</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">3</span>) | ||||||
| <span class="co"># Unit: milliseconds</span> | <span class="co"># Unit: milliseconds</span> | ||||||
| <span class="co">#        expr  min  lq mean median  uq max neval</span> | <span class="co">#        expr  min  lq mean median  uq max neval</span> | ||||||
| <span class="co">#  mo_name(x) 96.1 123  140    133 144 251    10</span> | <span class="co">#  mo_name(x) 99.2 127  145    143 145 243    10</span> | ||||||
| </pre></div> | </pre></div> | ||||||
| <p>So getting official taxonomic names of 2,000,000 (!!) items consisting of 90 unique values only takes 0.133 seconds. You only lose time on your unique input values.</p> | <p>So getting official taxonomic names of 2,000,000 (!!) items consisting of 90 unique values only takes 0.143 seconds. You only lose time on your unique input values.</p> | ||||||
| </div> | </div> | ||||||
| <div id="precalculated-results" class="section level3"> | <div id="precalculated-results" class="section level3"> | ||||||
| <h3 class="hasAnchor"> | <h3 class="hasAnchor"> | ||||||
| @@ -369,12 +369,12 @@ | |||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | <span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span> | ||||||
| <span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span>(<span class="kw">run_it</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">3</span>) | <span class="fu"><a href="https://docs.ropensci.org/skimr/reference/print.html">print</a></span>(<span class="kw">run_it</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">3</span>) | ||||||
| <span class="co"># Unit: milliseconds</span> | <span class="co"># Unit: milliseconds</span> | ||||||
| <span class="co">#  expr   min    lq  mean median    uq   max neval</span> | <span class="co">#  expr   min    lq  mean median    uq   max neval</span> | ||||||
| <span class="co">#     A  7.83  7.96  8.19   8.22  8.33  8.84    10</span> | <span class="co">#     A  7.53  8.50  8.77   8.83  9.14  9.89    10</span> | ||||||
| <span class="co">#     B 18.10 19.50 27.80  20.20 20.70 65.90    10</span> | <span class="co">#     B 23.00 24.20 32.40  26.30 28.80 60.10    10</span> | ||||||
| <span class="co">#     C  1.77  2.11  2.34   2.27  2.33  3.22    10</span> | <span class="co">#     C  1.91  1.98  2.33   2.30  2.66  2.83    10</span> | ||||||
| </pre></div> | </pre></div> | ||||||
| <p>So going from <code><a href="../reference/mo_property.html">mo_name("Staphylococcus aureus")</a></code> to <code>"Staphylococcus aureus"</code> takes 0.0023 seconds - it doesn’t even start calculating <em>if the result would be the same as the expected resulting value</em>. That goes for all helper functions:</p> | <p>So going from <code><a href="../reference/mo_property.html">mo_name("Staphylococcus aureus")</a></code> to <code>"Staphylococcus aureus"</code> takes 0.0023 seconds - it doesn’t even start calculating <em>if the result would be the same as the expected resulting value</em>. That goes for all helper functions:</p> | ||||||
| <div class="sourceCode" id="cb5"><pre class="downlit"> | <div class="sourceCode" id="cb5"><pre class="downlit"> | ||||||
| @@ -387,17 +387,17 @@ | |||||||
|                          G = <span class="fu"><a href="../reference/mo_property.html">mo_phylum</a></span>(<span class="st">"Firmicutes"</span>), |                          G = <span class="fu"><a href="../reference/mo_property.html">mo_phylum</a></span>(<span class="st">"Firmicutes"</span>), | ||||||
|                          H = <span class="fu"><a href="../reference/mo_property.html">mo_kingdom</a></span>(<span class="st">"Bacteria"</span>), |                          H = <span class="fu"><a href="../reference/mo_property.html">mo_kingdom</a></span>(<span class="st">"Bacteria"</span>), | ||||||
|                          times = <span class="fl">10</span>) |                          times = <span class="fl">10</span>) | ||||||
| <span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span>(<span class="kw">run_it</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">3</span>) | <span class="fu"><a href="https://docs.ropensci.org/skimr/reference/print.html">print</a></span>(<span class="kw">run_it</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">3</span>) | ||||||
| <span class="co"># Unit: milliseconds</span> | <span class="co"># Unit: milliseconds</span> | ||||||
| <span class="co">#  expr  min   lq mean median   uq   max neval</span> | <span class="co">#  expr  min   lq mean median   uq   max neval</span> | ||||||
| <span class="co">#     A 1.56 1.62 5.61   1.93 2.26 38.90    10</span> | <span class="co">#     A 1.55 1.74 1.91   1.98 2.06  2.16    10</span> | ||||||
| <span class="co">#     B 1.50 1.72 1.88   1.90 2.01  2.34    10</span> | <span class="co">#     B 1.52 1.70 1.95   1.88 2.03  2.62    10</span> | ||||||
| <span class="co">#     C 1.52 1.76 1.88   1.89 1.96  2.27    10</span> | <span class="co">#     C 1.61 1.68 6.25   2.04 2.18 44.80    10</span> | ||||||
| <span class="co">#     D 1.47 1.62 1.85   1.86 1.89  2.80    10</span> | <span class="co">#     D 1.65 1.71 1.92   1.95 2.02  2.22    10</span> | ||||||
| <span class="co">#     E 1.51 1.84 1.98   1.88 2.07  2.56    10</span> | <span class="co">#     E 1.56 1.79 1.92   1.99 2.01  2.14    10</span> | ||||||
| <span class="co">#     F 1.44 1.50 1.68   1.57 1.89  2.19    10</span> | <span class="co">#     F 1.62 1.67 1.82   1.78 1.94  2.09    10</span> | ||||||
| <span class="co">#     G 1.47 1.48 1.65   1.59 1.84  2.00    10</span> | <span class="co">#     G 1.61 1.70 1.92   1.97 2.01  2.31    10</span> | ||||||
| <span class="co">#     H 1.55 1.60 1.75   1.69 1.81  2.34    10</span> | <span class="co">#     H 1.62 1.69 1.83   1.87 1.95  2.01    10</span> | ||||||
| </pre></div> | </pre></div> | ||||||
| <p>Of course, when running <code><a href="../reference/mo_property.html">mo_phylum("Firmicutes")</a></code> the function has zero knowledge about the actual microorganism, namely <em>S. aureus</em>. But since the result would be <code>"Firmicutes"</code> anyway, there is no point in calculating the result. And because this package ‘knows’ all phyla of all known bacteria (according to the Catalogue of Life), it can just return the initial value immediately.</p> | <p>Of course, when running <code><a href="../reference/mo_property.html">mo_phylum("Firmicutes")</a></code> the function has zero knowledge about the actual microorganism, namely <em>S. aureus</em>. But since the result would be <code>"Firmicutes"</code> anyway, there is no point in calculating the result. And because this package ‘knows’ all phyla of all known bacteria (according to the Catalogue of Life), it can just return the initial value immediately.</p> | ||||||
| </div> | </div> | ||||||
| @@ -423,16 +423,16 @@ | |||||||
|                          fr = <span class="fu"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="st">"CoNS"</span>, language = <span class="st">"fr"</span>), |                          fr = <span class="fu"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="st">"CoNS"</span>, language = <span class="st">"fr"</span>), | ||||||
|                          pt = <span class="fu"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="st">"CoNS"</span>, language = <span class="st">"pt"</span>), |                          pt = <span class="fu"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="st">"CoNS"</span>, language = <span class="st">"pt"</span>), | ||||||
|                          times = <span class="fl">100</span>) |                          times = <span class="fl">100</span>) | ||||||
| <span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span>(<span class="kw">run_it</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">4</span>) | <span class="fu"><a href="https://docs.ropensci.org/skimr/reference/print.html">print</a></span>(<span class="kw">run_it</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">4</span>) | ||||||
| <span class="co"># Unit: milliseconds</span> | <span class="co"># Unit: milliseconds</span> | ||||||
| <span class="co">#  expr   min    lq  mean median    uq   max neval</span> | <span class="co">#  expr   min    lq  mean median    uq   max neval</span> | ||||||
| <span class="co">#    en 13.84 14.04 20.10  14.54 16.47 59.20   100</span> | <span class="co">#    en 13.92 14.62 19.73  15.07 17.06 71.77   100</span> | ||||||
| <span class="co">#    de 14.79 15.10 20.00  15.76 17.64 63.37   100</span> | <span class="co">#    de 16.83 17.63 22.19  18.10 20.41 58.61   100</span> | ||||||
| <span class="co">#    nl 18.52 19.35 24.11  21.44 22.93 62.12   100</span> | <span class="co">#    nl 28.71 30.05 35.19  31.64 34.09 69.34   100</span> | ||||||
| <span class="co">#    es 14.72 15.02 20.10  16.06 17.90 60.60   100</span> | <span class="co">#    es 16.78 17.61 22.57  18.56 20.21 57.98   100</span> | ||||||
| <span class="co">#    it 14.61 14.93 18.06  15.45 17.33 52.47   100</span> | <span class="co">#    it 16.61 17.39 21.59  18.32 20.74 56.86   100</span> | ||||||
| <span class="co">#    fr 14.73 15.02 21.06  15.62 18.09 69.54   100</span> | <span class="co">#    fr 16.48 17.31 21.96  17.84 20.26 55.84   100</span> | ||||||
| <span class="co">#    pt 14.74 14.99 21.19  16.17 17.88 64.71   100</span> | <span class="co">#    pt 16.66 17.45 24.03  18.26 20.85 67.60   100</span> | ||||||
| </pre></div> | </pre></div> | ||||||
| <p>Currently supported are German, Dutch, Spanish, Italian, French and Portuguese.</p> | <p>Currently supported are German, Dutch, Spanish, Italian, French and Portuguese.</p> | ||||||
| </div> | </div> | ||||||
|   | |||||||
| Before Width: | Height: | Size: 88 KiB After Width: | Height: | Size: 88 KiB | 
| @@ -39,7 +39,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9028</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -81,7 +81,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9037</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9038</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -20,7 +20,7 @@ | |||||||
| <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | ||||||
| <script src="../extra.js"></script><meta property="og:title" content="How to predict antimicrobial resistance"> | <script src="../extra.js"></script><meta property="og:title" content="How to predict antimicrobial resistance"> | ||||||
| <meta property="og:description" content="AMR"> | <meta property="og:description" content="AMR"> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg"> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png"> | ||||||
| <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | ||||||
| <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | ||||||
| <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | ||||||
| @@ -39,7 +39,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -270,7 +270,7 @@ | |||||||
| </pre></div> | </pre></div> | ||||||
| <p>The function <code>plot</code> is available in base R, and can be extended by other packages to depend the output based on the type of input. We extended its function to cope with resistance predictions:</p> | <p>The function <code>plot</code> is available in base R, and can be extended by other packages to depend the output based on the type of input. We extended its function to cope with resistance predictions:</p> | ||||||
| <div class="sourceCode" id="cb5"><pre class="downlit"> | <div class="sourceCode" id="cb5"><pre class="downlit"> | ||||||
| <span class="fu"><a href="https://rdrr.io/r/graphics/plot.default.html">plot</a></span>(<span class="kw">predict_TZP</span>) | <span class="fu"><a href="../reference/plot.html">plot</a></span>(<span class="kw">predict_TZP</span>) | ||||||
| </pre></div> | </pre></div> | ||||||
| <p><img src="resistance_predict_files/figure-html/unnamed-chunk-4-1.png" width="720"></p> | <p><img src="resistance_predict_files/figure-html/unnamed-chunk-4-1.png" width="720"></p> | ||||||
| <p>This is the fastest way to plot the result. It automatically adds the right axes, error bars, titles, number of available observations and type of model.</p> | <p>This is the fastest way to plot the result. It automatically adds the right axes, error bars, titles, number of available observations and type of model.</p> | ||||||
|   | |||||||
| @@ -20,7 +20,7 @@ | |||||||
| <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | <script src="../pkgdown.js"></script><link href="../extra.css" rel="stylesheet"> | ||||||
| <script src="../extra.js"></script><meta property="og:title" content="Welcome to the AMR package"> | <script src="../extra.js"></script><meta property="og:title" content="Welcome to the AMR package"> | ||||||
| <meta property="og:description" content="AMR"> | <meta property="og:description" content="AMR"> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg"> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png"> | ||||||
| <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> | ||||||
| <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> | ||||||
| <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> | ||||||
| @@ -39,7 +39,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -81,7 +81,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="index.html">AMR (for R)</a> |         <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">1.3.0.9037</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9038</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -43,7 +43,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="index.html">AMR (for R)</a> |         <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">1.3.0.9037</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9038</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -81,7 +81,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9037</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9038</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -236,13 +236,13 @@ | |||||||
|       <small>Source: <a href='https://github.com/msberends/AMR/blob/master/NEWS.md'><code>NEWS.md</code></a></small> |       <small>Source: <a href='https://github.com/msberends/AMR/blob/master/NEWS.md'><code>NEWS.md</code></a></small> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|     <div id="amr-1309037" class="section level1"> |     <div id="amr-1309038" class="section level1"> | ||||||
| <h1 class="page-header" data-toc-text="1.3.0.9037"> | <h1 class="page-header" data-toc-text="1.3.0.9038"> | ||||||
| <a href="#amr-1309037" class="anchor"></a>AMR 1.3.0.9037<small> Unreleased </small> | <a href="#amr-1309038" class="anchor"></a>AMR 1.3.0.9038<small> Unreleased </small> | ||||||
| </h1> | </h1> | ||||||
| <div id="last-updated-30-september-2020" class="section level2"> | <div id="last-updated-4-october-2020" class="section level2"> | ||||||
| <h2 class="hasAnchor"> | <h2 class="hasAnchor"> | ||||||
| <a href="#last-updated-30-september-2020" class="anchor"></a><small>Last updated: 30 September 2020</small> | <a href="#last-updated-4-october-2020" class="anchor"></a><small>Last updated: 4 October 2020</small> | ||||||
| </h2> | </h2> | ||||||
| <p>Note: some changes in this version were suggested by anonymous reviewers from the journal we submitted our manuscipt about this package to. We are those reviewers very grateful for going through our code so thoroughly!</p> | <p>Note: some changes in this version were suggested by anonymous reviewers from the journal we submitted our manuscipt about this package to. We are those reviewers very grateful for going through our code so thoroughly!</p> | ||||||
| <div id="new" class="section level3"> | <div id="new" class="section level3"> | ||||||
|   | |||||||
| @@ -2,7 +2,7 @@ pandoc: 2.7.3 | |||||||
| pkgdown: 1.5.1.9000 | pkgdown: 1.5.1.9000 | ||||||
| pkgdown_sha: eae56f08694abebf93cdfc0dd8e9ede06d8c815f | pkgdown_sha: eae56f08694abebf93cdfc0dd8e9ede06d8c815f | ||||||
| articles: [] | articles: [] | ||||||
| last_built: 2020-09-30T08:54Z | last_built: 2020-10-04T17:22Z | ||||||
| urls: | urls: | ||||||
|   reference: https://msberends.github.io/AMR/reference |   reference: https://msberends.github.io/AMR/reference | ||||||
|   article: https://msberends.github.io/AMR/articles |   article: https://msberends.github.io/AMR/articles | ||||||
|   | |||||||
| @@ -50,7 +50,7 @@ | |||||||
|  |  | ||||||
| <meta property="og:title" content="The AMR Package — AMR" /> | <meta property="og:title" content="The AMR Package — AMR" /> | ||||||
| <meta property="og:description" content="Welcome to the AMR package." /> | <meta property="og:description" content="Welcome to the AMR package." /> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg" /> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png" /> | ||||||
|  |  | ||||||
|  |  | ||||||
|  |  | ||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -50,7 +50,7 @@ | |||||||
|  |  | ||||||
| <meta property="og:title" content="WHOCC: WHO Collaborating Centre for Drug Statistics Methodology — WHOCC" /> | <meta property="og:title" content="WHOCC: WHO Collaborating Centre for Drug Statistics Methodology — WHOCC" /> | ||||||
| <meta property="og:description" content="All antimicrobial drugs and their official names, ATC codes, ATC groups and defined daily dose (DDD) are included in this package, using the WHO Collaborating Centre for Drug Statistics Methodology." /> | <meta property="og:description" content="All antimicrobial drugs and their official names, ATC codes, ATC groups and defined daily dose (DDD) are included in this package, using the WHO Collaborating Centre for Drug Statistics Methodology." /> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg" /> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png" /> | ||||||
|  |  | ||||||
|  |  | ||||||
|  |  | ||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -263,7 +263,8 @@ This package contains <strong>all ~550 antibiotic, antimycotic and antiviral dru | |||||||
|     <pre class="examples"><span class='fu'><a href='as.ab.html'>as.ab</a></span>(<span class='st'>"meropenem"</span>) |     <pre class="examples"><span class='fu'><a href='as.ab.html'>as.ab</a></span>(<span class='st'>"meropenem"</span>) | ||||||
| <span class='fu'><a href='ab_property.html'>ab_name</a></span>(<span class='st'>"J01DH02"</span>) | <span class='fu'><a href='ab_property.html'>ab_name</a></span>(<span class='st'>"J01DH02"</span>) | ||||||
|  |  | ||||||
| <span class='fu'><a href='ab_property.html'>ab_tradenames</a></span>(<span class='st'>"flucloxacillin"</span>)</pre> | <span class='fu'><a href='ab_property.html'>ab_tradenames</a></span>(<span class='st'>"flucloxacillin"</span>) | ||||||
|  | </pre> | ||||||
|   </div> |   </div> | ||||||
|   <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> |   <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> | ||||||
|     <nav id="toc" data-toggle="toc" class="sticky-top"> |     <nav id="toc" data-toggle="toc" class="sticky-top"> | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -50,7 +50,7 @@ | |||||||
|  |  | ||||||
| <meta property="og:title" content="Age in years of individuals — age" /> | <meta property="og:title" content="Age in years of individuals — age" /> | ||||||
| <meta property="og:description" content="Calculates age in years based on a reference date, which is the sytem date at default." /> | <meta property="og:description" content="Calculates age in years based on a reference date, which is the sytem date at default." /> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg" /> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png" /> | ||||||
|  |  | ||||||
|  |  | ||||||
|  |  | ||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -292,7 +292,8 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>stable</s | |||||||
| <span class='co'># add exact ages</span> | <span class='co'># add exact ages</span> | ||||||
| <span class='kw'>df</span><span class='op'>$</span><span class='kw'>age_exact</span> <span class='op'><-</span> <span class='fu'>age</span>(<span class='kw'>df</span><span class='op'>$</span><span class='kw'>birth_date</span>, exact = <span class='fl'>TRUE</span>) | <span class='kw'>df</span><span class='op'>$</span><span class='kw'>age_exact</span> <span class='op'><-</span> <span class='fu'>age</span>(<span class='kw'>df</span><span class='op'>$</span><span class='kw'>birth_date</span>, exact = <span class='fl'>TRUE</span>) | ||||||
|  |  | ||||||
| <span class='kw'>df</span></pre> | <span class='kw'>df</span> | ||||||
|  | </pre> | ||||||
|   </div> |   </div> | ||||||
|   <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> |   <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> | ||||||
|     <nav id="toc" data-toggle="toc" class="sticky-top"> |     <nav id="toc" data-toggle="toc" class="sticky-top"> | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9028</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9036</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -50,7 +50,7 @@ | |||||||
|  |  | ||||||
| <meta property="og:title" content="The Catalogue of Life — catalogue_of_life" /> | <meta property="og:title" content="The Catalogue of Life — catalogue_of_life" /> | ||||||
| <meta property="og:description" content="This package contains the complete taxonomic tree of almost all microorganisms from the authoritative and comprehensive Catalogue of Life." /> | <meta property="og:description" content="This package contains the complete taxonomic tree of almost all microorganisms from the authoritative and comprehensive Catalogue of Life." /> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg" /> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png" /> | ||||||
|  |  | ||||||
|  |  | ||||||
|  |  | ||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -304,7 +304,8 @@ Function <code><a href='as.mo.html'>as.mo()</a></code> to use the data for intel | |||||||
| <span class='fu'><a href='mo_property.html'>mo_kingdom</a></span>(<span class='st'>"C. elegans"</span>) | <span class='fu'><a href='mo_property.html'>mo_kingdom</a></span>(<span class='st'>"C. elegans"</span>) | ||||||
| <span class='co'># [1] "Fungi"                 # Fungi?!</span> | <span class='co'># [1] "Fungi"                 # Fungi?!</span> | ||||||
| <span class='fu'><a href='mo_property.html'>mo_name</a></span>(<span class='st'>"C. elegans"</span>) | <span class='fu'><a href='mo_property.html'>mo_name</a></span>(<span class='st'>"C. elegans"</span>) | ||||||
| <span class='co'># [1] "Cladosporium elegans"  # Because a microorganism was found</span></pre> | <span class='co'># [1] "Cladosporium elegans"  # Because a microorganism was found</span> | ||||||
|  | </pre> | ||||||
|   </div> |   </div> | ||||||
|   <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> |   <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> | ||||||
|     <nav id="toc" data-toggle="toc" class="sticky-top"> |     <nav id="toc" data-toggle="toc" class="sticky-top"> | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -83,7 +83,7 @@ count_resistant() should be used to count resistant isolates, count_susceptible( | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -83,7 +83,7 @@ To improve the interpretation of the antibiogram before EUCAST rules are applied | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9038</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -268,7 +268,7 @@ To improve the interpretation of the antibiogram before EUCAST rules are applied | |||||||
|     </tr> |     </tr> | ||||||
|     <tr> |     <tr> | ||||||
|       <th>info</th> |       <th>info</th> | ||||||
|       <td><p>print progress</p></td> |       <td><p>a logical to indicate whether progress should be printed to the console, defaults to only print while in interactive sessions</p></td> | ||||||
|     </tr> |     </tr> | ||||||
|     <tr> |     <tr> | ||||||
|       <th>rules</th> |       <th>rules</th> | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -50,7 +50,7 @@ | |||||||
|  |  | ||||||
| <meta property="og:title" content="G-test for Count Data — g.test" /> | <meta property="og:title" content="G-test for Count Data — g.test" /> | ||||||
| <meta property="og:description" content="g.test() performs chi-squared contingency table tests and goodness-of-fit tests, just like chisq.test() but is more reliable (1). A G-test can be used to see whether the number of observations in each category fits a theoretical expectation (called a G-test of goodness-of-fit), or to see whether the proportions of one variable are different for different values of the other variable (called a G-test of independence)." /> | <meta property="og:description" content="g.test() performs chi-squared contingency table tests and goodness-of-fit tests, just like chisq.test() but is more reliable (1). A G-test can be used to see whether the number of observations in each category fits a theoretical expectation (called a G-test of goodness-of-fit), or to see whether the proportions of one variable are different for different values of the other variable (called a G-test of independence)." /> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg" /> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png" /> | ||||||
|  |  | ||||||
|  |  | ||||||
|  |  | ||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -326,7 +326,8 @@ | |||||||
| <p>Unlike the exact test of goodness-of-fit (<code><a href='https://rdrr.io/r/stats/fisher.test.html'>fisher.test()</a></code>), the <em>G</em>-test does not directly calculate the probability of obtaining the observed results or something more extreme. Instead, like almost all statistical tests, the <em>G</em>-test has an intermediate step; it uses the data to calculate a test statistic that measures how far the observed data are from the null expectation. You then use a mathematical relationship, in this case the chi-square distribution, to estimate the probability of obtaining that value of the test statistic.</p> | <p>Unlike the exact test of goodness-of-fit (<code><a href='https://rdrr.io/r/stats/fisher.test.html'>fisher.test()</a></code>), the <em>G</em>-test does not directly calculate the probability of obtaining the observed results or something more extreme. Instead, like almost all statistical tests, the <em>G</em>-test has an intermediate step; it uses the data to calculate a test statistic that measures how far the observed data are from the null expectation. You then use a mathematical relationship, in this case the chi-square distribution, to estimate the probability of obtaining that value of the test statistic.</p> | ||||||
| <p>The <em>G</em>-test uses the log of the ratio of two likelihoods as the test statistic, which is why it is also called a likelihood ratio test or log-likelihood ratio test. The formula to calculate a <em>G</em>-statistic is:</p> | <p>The <em>G</em>-test uses the log of the ratio of two likelihoods as the test statistic, which is why it is also called a likelihood ratio test or log-likelihood ratio test. The formula to calculate a <em>G</em>-statistic is:</p> | ||||||
| <p>\(G = 2 * sum(x * log(x / E))\)</p> | <p>\(G = 2 * sum(x * log(x / E))\)</p> | ||||||
| <p>where <code>E</code> are the expected values. Since this is chi-square distributed, the p value can be calculated in <span style="R">R</span> with:</p><pre><span class='kw'>p</span> <span class='op'><-</span> <span class='kw'>stats</span>::<span class='fu'><a href='https://rdrr.io/r/stats/Chisquare.html'>pchisq</a></span>(<span class='kw'>G</span>, <span class='kw'>df</span>, lower.tail = <span class='fl'>FALSE</span>)</pre> | <p>where <code>E</code> are the expected values. Since this is chi-square distributed, the p value can be calculated in <span style="R">R</span> with:</p><pre><span class='kw'>p</span> <span class='op'><-</span> <span class='kw'>stats</span>::<span class='fu'><a href='https://rdrr.io/r/stats/Chisquare.html'>pchisq</a></span>(<span class='kw'>G</span>, <span class='kw'>df</span>, lower.tail = <span class='fl'>FALSE</span>) | ||||||
|  | </pre> | ||||||
|  |  | ||||||
| <p>where <code>df</code> are the degrees of freedom.</p> | <p>where <code>df</code> are the degrees of freedom.</p> | ||||||
| <p>If there are more than two categories and you want to find out which ones are significantly different from their null expectation, you can use the same method of testing each category vs. the sum of all categories, with the Bonferroni correction. You use <em>G</em>-tests for each category, of course.</p> | <p>If there are more than two categories and you want to find out which ones are significantly different from their null expectation, you can use the same method of testing each category vs. the sum of all categories, with the Bonferroni correction. You use <em>G</em>-tests for each category, of course.</p> | ||||||
| @@ -385,6 +386,7 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>questioni | |||||||
|  |  | ||||||
| <span class='co'># There is a significant difference from a 1:1 ratio.</span> | <span class='co'># There is a significant difference from a 1:1 ratio.</span> | ||||||
| <span class='co'># Meaning: there are significantly more left-billed birds.</span> | <span class='co'># Meaning: there are significantly more left-billed birds.</span> | ||||||
|  |  | ||||||
| </pre> | </pre> | ||||||
|   </div> |   </div> | ||||||
|   <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> |   <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -81,7 +81,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9037</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9038</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9028</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -52,7 +52,7 @@ | |||||||
| <meta property="og:description" content="Functions in this AMR package are categorised using the lifecycle circle of the Tidyverse as found on www.tidyverse.org/lifecycle. | <meta property="og:description" content="Functions in this AMR package are categorised using the lifecycle circle of the Tidyverse as found on www.tidyverse.org/lifecycle. | ||||||
|   |   | ||||||
| This page contains a section for every lifecycle (with text borrowed from the aforementioned Tidyverse website), so they can be used in the manual pages of the functions." /> | This page contains a section for every lifecycle (with text borrowed from the aforementioned Tidyverse website), so they can be used in the manual pages of the functions." /> | ||||||
| <meta property="og:image" content="https://msberends.github.io/AMR/logo.svg" /> | <meta property="og:image" content="https://msberends.github.io/AMR/logo.png" /> | ||||||
|  |  | ||||||
|  |  | ||||||
|  |  | ||||||
| @@ -84,7 +84,7 @@ This page contains a section for every lifecycle (with text borrowed from the af | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9015</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9038</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -280,7 +280,7 @@ | |||||||
|     </tr> |     </tr> | ||||||
|     <tr> |     <tr> | ||||||
|       <th>info</th> |       <th>info</th> | ||||||
|       <td><p>a logical to indicate whether progress should be printed to the console</p></td> |       <td><p>a logical to indicate whether progress should be printed to the console, defaults to only print while in interactive sessions</p></td> | ||||||
|     </tr> |     </tr> | ||||||
|     <tr> |     <tr> | ||||||
|       <th>pct_required_classes</th> |       <th>pct_required_classes</th> | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -83,7 +83,7 @@ This is the fastest way to have your organisation (or analysis) specific codes p | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9028</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9038</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
| @@ -260,7 +260,7 @@ This is the fastest way to have your organisation (or analysis) specific codes p | |||||||
|     <h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2> |     <h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2> | ||||||
|  |  | ||||||
|     <p>The reference file can be a text file separated with commas (CSV) or tabs or pipes, an Excel file (either 'xls' or 'xlsx' format) or an R object file (extension '.rds'). To use an Excel file, you will need to have the <code>readxl</code> package installed.</p> |     <p>The reference file can be a text file separated with commas (CSV) or tabs or pipes, an Excel file (either 'xls' or 'xlsx' format) or an R object file (extension '.rds'). To use an Excel file, you will need to have the <code>readxl</code> package installed.</p> | ||||||
| <p><code>set_mo_source()</code> will check the file for validity: it must be a <a href='https://rdrr.io/r/base/data.frame.html'>data.frame</a>, must have a column named <code>"mo"</code> which contains values from <code><a href='microorganisms.html'>microorganisms$mo</a></code> and must have a reference column with your own defined values. If all tests pass, <code>set_mo_source()</code> will read the file into R and export it to <code>"~/.mo_source.rds"</code> after the user <strong>specifically confirms and allows</strong> that this file will be created. For this reason, this function only works in interactive sessions.</p> | <p><code>set_mo_source()</code> will check the file for validity: it must be a <a href='https://rdrr.io/r/base/data.frame.html'>data.frame</a>, must have a column named <code>"mo"</code> which contains values from <code><a href='microorganisms.html'>microorganisms$mo</a></code> and must have a reference column with your own defined values. If all tests pass, <code>set_mo_source()</code> will read the file into R and will ask to export it to <code>"~/.mo_source.rds"</code>. The CRAN policy disallows packages to write to the file system, although '<em>exceptions may be allowed in interactive sessions if the package obtains confirmation from the user</em>'. For this reason, this function only works in interactive sessions so that the user can <strong>specifically confirm and allow</strong> that this file will be created.</p> | ||||||
| <p>The created compressed data file <code>"~/.mo_source.rds"</code> will be used at default for MO determination (function <code><a href='as.mo.html'>as.mo()</a></code> and consequently all <code>mo_*</code> functions like <code><a href='mo_property.html'>mo_genus()</a></code> and <code><a href='mo_property.html'>mo_gramstain()</a></code>). The location of the original file will be saved as an R option with <code><a href='https://rdrr.io/r/base/options.html'>options(mo_source = path)</a></code>. Its timestamp will be saved with <code><a href='https://rdrr.io/r/base/options.html'>options(mo_source_datetime = ...)</a></code>.</p> | <p>The created compressed data file <code>"~/.mo_source.rds"</code> will be used at default for MO determination (function <code><a href='as.mo.html'>as.mo()</a></code> and consequently all <code>mo_*</code> functions like <code><a href='mo_property.html'>mo_genus()</a></code> and <code><a href='mo_property.html'>mo_gramstain()</a></code>). The location of the original file will be saved as an R option with <code><a href='https://rdrr.io/r/base/options.html'>options(mo_source = path)</a></code>. Its timestamp will be saved with <code><a href='https://rdrr.io/r/base/options.html'>options(mo_source_datetime = ...)</a></code>.</p> | ||||||
| <p>The function <code>get_mo_source()</code> will return the data set by reading <code>"~/.mo_source.rds"</code> with <code><a href='https://rdrr.io/r/base/readRDS.html'>readRDS()</a></code>. If the original file has changed (by checking the aforementioned options <code>mo_source</code> and <code>mo_source_datetime</code>), it will call <code>set_mo_source()</code> to update the data file automatically if used in an interactive session.</p> | <p>The function <code>get_mo_source()</code> will return the data set by reading <code>"~/.mo_source.rds"</code> with <code><a href='https://rdrr.io/r/base/readRDS.html'>readRDS()</a></code>. If the original file has changed (by checking the aforementioned options <code>mo_source</code> and <code>mo_source_datetime</code>), it will call <code>set_mo_source()</code> to update the data file automatically if used in an interactive session.</p> | ||||||
| <p>Reading an Excel file (<code>.xlsx</code>) with only one row has a size of 8-9 kB. The compressed file created with <code>set_mo_source()</code> will then have a size of 0.1 kB and can be read by <code>get_mo_source()</code> in only a couple of microseconds (millionths of a second).</p> | <p>Reading an Excel file (<code>.xlsx</code>) with only one row has a size of 8-9 kB. The compressed file created with <code>set_mo_source()</code> will then have a size of 0.1 kB and can be read by <code>get_mo_source()</code> in only a couple of microseconds (millionths of a second).</p> | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9022</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -83,7 +83,7 @@ resistance() should be used to calculate resistance, susceptibility() should be | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9035</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -83,7 +83,7 @@ When negative: the left tail is longer; the mass of the distribution is concentr | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9026</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -82,7 +82,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> |         <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">1.3.0.9022</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -81,7 +81,7 @@ | |||||||
|       </button> |       </button> | ||||||
|       <span class="navbar-brand"> |       <span class="navbar-brand"> | ||||||
|         <a class="navbar-link" href="index.html">AMR (for R)</a> |         <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">1.3.0.9037</span> |         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9038</span> | ||||||
|       </span> |       </span> | ||||||
|     </div> |     </div> | ||||||
|  |  | ||||||
|   | |||||||
| @@ -31,7 +31,7 @@ eucast_rules( | |||||||
|  |  | ||||||
| \item{col_mo}{column name of the IDs of the microorganisms (see \code{\link[=as.mo]{as.mo()}}), defaults to the first column of class \code{\link{mo}}. Values will be coerced using \code{\link[=as.mo]{as.mo()}}.} | \item{col_mo}{column name of the IDs of the microorganisms (see \code{\link[=as.mo]{as.mo()}}), defaults to the first column of class \code{\link{mo}}. Values will be coerced using \code{\link[=as.mo]{as.mo()}}.} | ||||||
|  |  | ||||||
| \item{info}{print progress} | \item{info}{a logical to indicate whether progress should be printed to the console, defaults to only print while in interactive sessions} | ||||||
|  |  | ||||||
| \item{rules}{a character vector that specifies which rules should be applied. Must be one or more of \code{"breakpoints"}, \code{"expert"}, \code{"other"}, \code{"all"}, and defaults to \code{c("breakpoints", "expert")}. The default value can be set to another value, e.g. using \code{options(AMR_eucastrules = "all")}.} | \item{rules}{a character vector that specifies which rules should be applied. Must be one or more of \code{"breakpoints"}, \code{"expert"}, \code{"other"}, \code{"all"}, and defaults to \code{c("breakpoints", "expert")}. The default value can be set to another value, e.g. using \code{options(AMR_eucastrules = "all")}.} | ||||||
|  |  | ||||||
|   | |||||||
| @@ -46,7 +46,7 @@ eucast_exceptional_phenotypes(x, guideline = "EUCAST", ...) | |||||||
|  |  | ||||||
| \item{col_mo}{column name of the IDs of the microorganisms (see \code{\link[=as.mo]{as.mo()}}), defaults to the first column of class \code{\link{mo}}. Values will be coerced using \code{\link[=as.mo]{as.mo()}}.} | \item{col_mo}{column name of the IDs of the microorganisms (see \code{\link[=as.mo]{as.mo()}}), defaults to the first column of class \code{\link{mo}}. Values will be coerced using \code{\link[=as.mo]{as.mo()}}.} | ||||||
|  |  | ||||||
| \item{info}{a logical to indicate whether progress should be printed to the console} | \item{info}{a logical to indicate whether progress should be printed to the console, defaults to only print while in interactive sessions} | ||||||
|  |  | ||||||
| \item{pct_required_classes}{minimal required percentage of antimicrobial classes that must be available per isolate, rounded down. For example, with the default guideline, 17 antimicrobial classes must be available for \emph{S. aureus}. Setting this \code{pct_required_classes} argument to \code{0.5} (default) means that for every \emph{S. aureus} isolate at least 8 different classes must be available. Any lower number of available classes will return \code{NA} for that isolate.} | \item{pct_required_classes}{minimal required percentage of antimicrobial classes that must be available per isolate, rounded down. For example, with the default guideline, 17 antimicrobial classes must be available for \emph{S. aureus}. Setting this \code{pct_required_classes} argument to \code{0.5} (default) means that for every \emph{S. aureus} isolate at least 8 different classes must be available. Any lower number of available classes will return \code{NA} for that isolate.} | ||||||
|  |  | ||||||
|   | |||||||
| @@ -21,7 +21,7 @@ This is \strong{the fastest way} to have your organisation (or analysis) specifi | |||||||
| \details{ | \details{ | ||||||
| The reference file can be a text file separated with commas (CSV) or tabs or pipes, an Excel file (either 'xls' or 'xlsx' format) or an R object file (extension '.rds'). To use an Excel file, you will need to have the \code{readxl} package installed. | The reference file can be a text file separated with commas (CSV) or tabs or pipes, an Excel file (either 'xls' or 'xlsx' format) or an R object file (extension '.rds'). To use an Excel file, you will need to have the \code{readxl} package installed. | ||||||
|  |  | ||||||
| \code{\link[=set_mo_source]{set_mo_source()}} will check the file for validity: it must be a \link{data.frame}, must have a column named \code{"mo"} which contains values from \code{\link[=microorganisms]{microorganisms$mo}} and must have a reference column with your own defined values. If all tests pass, \code{\link[=set_mo_source]{set_mo_source()}} will read the file into R and export it to \code{"~/.mo_source.rds"} after the user \strong{specifically confirms and allows} that this file will be created. For this reason, this function only works in interactive sessions. | \code{\link[=set_mo_source]{set_mo_source()}} will check the file for validity: it must be a \link{data.frame}, must have a column named \code{"mo"} which contains values from \code{\link[=microorganisms]{microorganisms$mo}} and must have a reference column with your own defined values. If all tests pass, \code{\link[=set_mo_source]{set_mo_source()}} will read the file into R and will ask to export it to \code{"~/.mo_source.rds"}. The CRAN policy disallows packages to write to the file system, although '\emph{exceptions may be allowed in interactive sessions if the package obtains confirmation from the user}'. For this reason, this function only works in interactive sessions so that the user can \strong{specifically confirm and allow} that this file will be created. | ||||||
|  |  | ||||||
| The created compressed data file \code{"~/.mo_source.rds"} will be used at default for MO determination (function \code{\link[=as.mo]{as.mo()}} and consequently all \verb{mo_*} functions like \code{\link[=mo_genus]{mo_genus()}} and \code{\link[=mo_gramstain]{mo_gramstain()}}). The location of the original file will be saved as an R option with \code{options(mo_source = path)}. Its timestamp will be saved with \code{options(mo_source_datetime = ...)}. | The created compressed data file \code{"~/.mo_source.rds"} will be used at default for MO determination (function \code{\link[=as.mo]{as.mo()}} and consequently all \verb{mo_*} functions like \code{\link[=mo_genus]{mo_genus()}} and \code{\link[=mo_gramstain]{mo_gramstain()}}). The location of the original file will be saved as an R option with \code{options(mo_source = path)}. Its timestamp will be saved with \code{options(mo_source_datetime = ...)}. | ||||||
|  |  | ||||||
|   | |||||||
| @@ -28,7 +28,9 @@ What are EUCAST rules? The European Committee on Antimicrobial Susceptibility Te | |||||||
|  |  | ||||||
| > *EUCAST expert rules are a tabulated collection of expert knowledge on intrinsic resistances, exceptional resistance phenotypes and interpretive rules that may be applied to antimicrobial susceptibility testing in order to reduce errors and make appropriate recommendations for reporting particular resistances.* | > *EUCAST expert rules are a tabulated collection of expert knowledge on intrinsic resistances, exceptional resistance phenotypes and interpretive rules that may be applied to antimicrobial susceptibility testing in order to reduce errors and make appropriate recommendations for reporting particular resistances.* | ||||||
|  |  | ||||||
| In Europe, a lot of medical microbiological laboratories already apply these rules ([Brown *et al.*, 2015](https://www.eurosurveillance.org/content/10.2807/1560-7917.ES2015.20.2.21008)). Our package features their latest insights on intrinsic resistance and exceptional phenotypes (version `r AMR:::EUCAST_VERSION_BREAKPOINTS`). Moreover, the `eucast_rules()` function we use for this purpose can also apply additional rules, like forcing <help title="ATC: J01CA01">ampicillin</help> = R in isolates when <help title="ATC: J01CR02">amoxicillin/clavulanic acid</help> = R. | In Europe, a lot of medical microbiological laboratories already apply these rules ([Brown *et al.*, 2015](https://www.eurosurveillance.org/content/10.2807/1560-7917.ES2015.20.2.21008)). Our package features their latest insights on intrinsic resistance and unusual phenotypes (`r AMR:::EUCAST_VERSION_EXPERT_RULES[[length(AMR:::EUCAST_VERSION_EXPERT_RULES)]]$version_txt`, `r AMR:::EUCAST_VERSION_EXPERT_RULES[[length(AMR:::EUCAST_VERSION_EXPERT_RULES)]]$year`). | ||||||
|  |  | ||||||
|  | Moreover, the `eucast_rules()` function we use for this purpose can also apply additional rules, like forcing <help title="ATC: J01CA01">ampicillin</help> = R in isolates when <help title="ATC: J01CR02">amoxicillin/clavulanic acid</help> = R. | ||||||
|  |  | ||||||
| ## Examples | ## Examples | ||||||
|  |  | ||||||
| @@ -58,7 +60,7 @@ data <- data.frame(mo = c("Staphylococcus aureus", | |||||||
|                    COL = "-",       # Colistin |                    COL = "-",       # Colistin | ||||||
|                    CAZ = "-",       # Ceftazidime |                    CAZ = "-",       # Ceftazidime | ||||||
|                    CXM = "-",       # Cefuroxime |                    CXM = "-",       # Cefuroxime | ||||||
|                    PEN = "S",       # Penicillin G |                    PEN = "S",       # Benzylenicillin | ||||||
|                    FOX = "S",       # Cefoxitin |                    FOX = "S",       # Cefoxitin | ||||||
|                    stringsAsFactors = FALSE) |                    stringsAsFactors = FALSE) | ||||||
| ``` | ``` | ||||||
| @@ -68,9 +70,9 @@ data | |||||||
| ```{r, echo = FALSE} | ```{r, echo = FALSE} | ||||||
| knitr::kable(data, align = "lccccccc") | knitr::kable(data, align = "lccccccc") | ||||||
| ``` | ``` | ||||||
| ```{r, eval = FALSE} | ```{r, warning = FALSE, eval = FALSE} | ||||||
| eucast_rules(data) | eucast_rules(data) | ||||||
| ``` | ``` | ||||||
| ```{r, echo = FALSE, message = FALSE} | ```{r, warning = FALSE, echo = FALSE, message = FALSE} | ||||||
| knitr::kable(eucast_rules(data), align = "lccccccc") | knitr::kable(eucast_rules(data), align = "lccccccc") | ||||||
| ``` | ``` | ||||||
|   | |||||||