mirror of
				https://github.com/msberends/AMR.git
				synced 2025-10-26 16:16:22 +01:00 
			
		
		
		
	(v1.4.0.9001) is_gram_positive(), is_gram_negative(), parameter hardening
This commit is contained in:
		
							
								
								
									
										4
									
								
								.github/workflows/check.yaml
									
									
									
									
										vendored
									
									
								
							
							
						
						
									
										4
									
								
								.github/workflows/check.yaml
									
									
									
									
										vendored
									
									
								
							| @@ -58,8 +58,8 @@ jobs: | ||||
|           - {os: ubuntu-16.04,   r: '4.0',     rspm: "https://packagemanager.rstudio.com/cran/__linux__/xenial/latest"} | ||||
|           - {os: ubuntu-16.04,   r: '3.6',     rspm: "https://packagemanager.rstudio.com/cran/__linux__/xenial/latest"} | ||||
|           - {os: ubuntu-16.04,   r: '3.5',     rspm: "https://packagemanager.rstudio.com/cran/__linux__/xenial/latest"} | ||||
|           - {os: ubuntu-16.04,   r: '3.4',     rspm: "https://packagemanager.rstudio.com/cran/__linux__/xenial/latest"} | ||||
|           - {os: ubuntu-16.04,   r: '3.3',     rspm: "https://packagemanager.rstudio.com/cran/__linux__/xenial/latest"} | ||||
|           # - {os: ubuntu-16.04,   r: '3.4',     rspm: "https://packagemanager.rstudio.com/cran/__linux__/xenial/latest"} | ||||
|           # - {os: ubuntu-16.04,   r: '3.3',     rspm: "https://packagemanager.rstudio.com/cran/__linux__/xenial/latest"} | ||||
|  | ||||
|     env: | ||||
|       R_REMOTES_NO_ERRORS_FROM_WARNINGS: true | ||||
|   | ||||
| @@ -1,6 +1,6 @@ | ||||
| Package: AMR | ||||
| Version: 1.4.0.9000 | ||||
| Date: 2020-10-15 | ||||
| Version: 1.4.0.9001 | ||||
| Date: 2020-10-19 | ||||
| Title: Antimicrobial Resistance Analysis | ||||
| Authors@R: c( | ||||
|     person(role = c("aut", "cre"),  | ||||
|   | ||||
| @@ -150,6 +150,8 @@ export(is.mic) | ||||
| export(is.mo) | ||||
| export(is.rsi) | ||||
| export(is.rsi.eligible) | ||||
| export(is_gram_negative) | ||||
| export(is_gram_positive) | ||||
| export(key_antibiotics) | ||||
| export(key_antibiotics_equal) | ||||
| export(kurtosis) | ||||
|   | ||||
							
								
								
									
										11
									
								
								NEWS.md
									
									
									
									
									
								
							
							
						
						
									
										11
									
								
								NEWS.md
									
									
									
									
									
								
							| @@ -1,5 +1,12 @@ | ||||
| # AMR 1.4.0.9000 | ||||
| ## <small>Last updated: 15 October 2020</small> | ||||
| # AMR 1.4.0.9001 | ||||
| ## <small>Last updated: 19 October 2020</small> | ||||
|  | ||||
| ### New | ||||
| * Functions `is_gram_negative()` and `is_gram_positive()` as wrappers around `mo_gramstain()`. They always return `TRUE` or `FALSE`, thus always return `FALSE` for species outside the taxonomic kingdom of Bacteria. | ||||
|  | ||||
| ### Changed | ||||
| * For all function parameters in the code, it is now defined what the exact type of user input should be (inspired by the [`typed`](https://github.com/moodymudskipper/typed) package). If the user input for a certain function does not meet the requirements for a specific parameter (such as the class or length), an informative error will be thrown. This makes the package more robust and the use of it more reproducible and reliable. In total, more than 400 arguments were defined. | ||||
| * Deprecated function `p_symbol()` that not really fits the scope of this package. It will be removed in a future version. See [here](https://github.com/msberends/AMR/blob/v1.4.0/R/p_symbol.R) for the source code to preserve it. | ||||
|  | ||||
| ### Other | ||||
| * More extensive unit tests | ||||
|   | ||||
| @@ -329,6 +329,89 @@ create_ab_documentation <- function(ab) { | ||||
|   out | ||||
| } | ||||
|  | ||||
| # a check for every single argument in all functions | ||||
| meet_criteria <- function(object, | ||||
|                           allow_class = NULL, | ||||
|                           has_length = NULL, | ||||
|                           looks_like = NULL, | ||||
|                           is_in = NULL, | ||||
|                           contains_column_class = NULL, | ||||
|                           allow_NULL = FALSE, | ||||
|                           allow_NA = FALSE, | ||||
|                           ignore.case = FALSE, | ||||
|                           .call_depth = 0) { # depth in calling | ||||
|    | ||||
|   obj_name <- deparse(substitute(object)) | ||||
|   call_depth <- -2 - abs(.call_depth) | ||||
|    | ||||
|   if (is.null(object)) { | ||||
|     stop_if(allow_NULL == FALSE, "argument `", obj_name, "` must not be NULL", call = call_depth) | ||||
|     return(invisible()) | ||||
|   } | ||||
|   if (is.null(dim(object)) && length(object) == 1 && is.na(object)) { | ||||
|     stop_if(allow_NA == FALSE, "argument `", obj_name, "` must not be NA", call = call_depth) | ||||
|     return(invisible()) | ||||
|   } | ||||
|    | ||||
|   vector_or <- function(v, quotes) { | ||||
|     if (length(v) == 1) { | ||||
|       return(paste0(ifelse(quotes, '"', ""), v, ifelse(quotes, '"', ""))) | ||||
|     } | ||||
|     # all commas except for last item, so will become '"val1", "val2", "val3" or "val4"' | ||||
|     paste0(paste0(ifelse(quotes, '"', ""), v[seq_len(length(v) - 1)], ifelse(quotes, '"', ""), collapse = ", "), | ||||
|            " or ", paste0(ifelse(quotes, '"', ""), v[length(v)], ifelse(quotes, '"', ""))) | ||||
|   } | ||||
|    | ||||
|   if (!is.null(allow_class)) { | ||||
|     stop_ifnot(inherits(object, allow_class), "argument `", obj_name,  | ||||
|                "` must ", # ifelse(allow_NULL, "be NULL or must ", ""),  | ||||
|                "be of class ", vector_or(allow_class, quotes = TRUE),  | ||||
|                ", not \"", paste(class(object), collapse = "/"), "\"", | ||||
|                call = call_depth) | ||||
|     # check data.frames for data | ||||
|     if (inherits(object, "data.frame")) { | ||||
|       stop_if(any(dim(object) == 0),  | ||||
|               "the data provided in argument `", obj_name, | ||||
|               "` must contain rows and columns (current dimensions: ",  | ||||
|               paste(dim(object), collapse = " x "), ")", | ||||
|               call = call_depth) | ||||
|     } | ||||
|   } | ||||
|   if (!is.null(has_length)) { | ||||
|     stop_ifnot(length(object) %in% has_length, "argument `", obj_name,  | ||||
|                "` must ", # ifelse(allow_NULL, "be NULL or must ", ""),  | ||||
|                "be of length ", vector_or(has_length, quotes = FALSE), | ||||
|                ", not ", length(object), | ||||
|                call = call_depth) | ||||
|   } | ||||
|   if (!is.null(looks_like)) { | ||||
|     stop_ifnot(object %like% looks_like, "argument `", obj_name,  | ||||
|                "` must ", # ifelse(allow_NULL, "be NULL or must ", ""),  | ||||
|                "resemble the regular expression \"", looks_like, "\"", | ||||
|                call = call_depth) | ||||
|   } | ||||
|   if (!is.null(is_in)) { | ||||
|     if (ignore.case == TRUE) { | ||||
|       object <- tolower(object) | ||||
|       is_in <- tolower(is_in) | ||||
|     } | ||||
|     stop_ifnot(all(object %in% is_in, na.rm = TRUE), "argument `", obj_name,  | ||||
|                "` must be ", | ||||
|                ifelse(!is.null(has_length) && length(has_length) == 1 && has_length == 1, "one of: ", ""), | ||||
|                vector_or(is_in, quotes = TRUE),  | ||||
|                ", not ", paste0("\"", object, "\"", collapse = "/"), "", | ||||
|                call = call_depth) | ||||
|   } | ||||
|   if (!is.null(contains_column_class)) { | ||||
|     stop_ifnot(any(sapply(object, function(col, columns_class = contains_column_class) inherits(col, columns_class)), na.rm = TRUE), | ||||
|                "the data provided in argument `", obj_name,  | ||||
|                "` must contain at least one column of class <", contains_column_class, ">. ", | ||||
|                "See ?as.", contains_column_class, ".", | ||||
|                call = call_depth) | ||||
|   } | ||||
|   return(invisible()) | ||||
| } | ||||
|  | ||||
| has_colour <- function() { | ||||
|   # this is a base R version of crayon::has_color | ||||
|   enabled <- getOption("crayon.enabled") | ||||
|   | ||||
							
								
								
									
										3
									
								
								R/ab.R
									
									
									
									
									
								
							
							
						
						
									
										3
									
								
								R/ab.R
									
									
									
									
									
								
							| @@ -82,6 +82,9 @@ | ||||
| #' ab_name("J01FA01")    # "Erythromycin" | ||||
| #' ab_name("eryt")       # "Erythromycin" | ||||
| as.ab <- function(x, flag_multiple_results = TRUE, info = TRUE, ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(flag_multiple_results, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(info, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   check_dataset_integrity() | ||||
|    | ||||
|   | ||||
| @@ -54,7 +54,7 @@ | ||||
| #'      | ||||
| #'   # get bug/drug combinations for only macrolides in Gram-positives: | ||||
| #'   example_isolates %>%  | ||||
| #'     filter(mo_gramstain(mo) %like% "pos") %>%  | ||||
| #'     filter(mo %>% is_gram_positive()) %>%  | ||||
| #'     select(mo, macrolides()) %>%  | ||||
| #'     bug_drug_combinations() %>% | ||||
| #'     format() | ||||
| @@ -148,9 +148,12 @@ tetracyclines <- function() { | ||||
| } | ||||
|  | ||||
| ab_selector <- function(ab_class, function_name) { | ||||
|   meet_criteria(ab_class, allow_class = "character", has_length = 1, .call_depth = 1) | ||||
|   meet_criteria(function_name, allow_class = "character", has_length = 1, .call_depth = 1) | ||||
|  | ||||
|   peek_vars_tidyselect <- import_fn("peek_vars", "tidyselect") | ||||
|   vars_vct <- peek_vars_tidyselect(fn = function_name) | ||||
|   vars_df <- data.frame(as.list(vars_vct))[0, , drop = FALSE] | ||||
|   vars_df <- data.frame(as.list(vars_vct))[1, , drop = FALSE] | ||||
|   colnames(vars_df) <- vars_vct | ||||
|   ab_in_data <- get_column_abx(vars_df, info = FALSE) | ||||
|    | ||||
|   | ||||
| @@ -92,12 +92,17 @@ ab_from_text <- function(text, | ||||
|                          translate_ab = FALSE, | ||||
|                          thorough_search = NULL, | ||||
|                          ...) { | ||||
|    | ||||
|   if (missing(type)) { | ||||
|     type <- type[1L] | ||||
|   } | ||||
|    | ||||
|   meet_criteria(text) | ||||
|   meet_criteria(type, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(collapse, has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(translate_ab, allow_NULL = FALSE) # get_translate_ab() will be more informative about what's allowed | ||||
|   meet_criteria(thorough_search, allow_class = "logical", has_length = 1, allow_NULL = TRUE) | ||||
|  | ||||
|   type <- tolower(trimws(type)) | ||||
|   stop_if(length(type) != 1, "`type` must be of length 1") | ||||
|    | ||||
|   text <- tolower(as.character(text)) | ||||
|   text_split_all <- strsplit(text, "[ ;.,:\\|]") | ||||
|   | ||||
| @@ -89,6 +89,10 @@ | ||||
| #' ab_atc("cephthriaxone") | ||||
| #' ab_atc("seephthriaaksone") | ||||
| ab_name <- function(x, language = get_locale(), tolower = FALSE, ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer")) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(tolower, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   x <- translate_AMR(ab_validate(x = x, property = "name", ...), language = language) | ||||
|   if (tolower == TRUE) { | ||||
|     # use perl to only transform the first character | ||||
| @@ -102,18 +106,21 @@ ab_name <- function(x, language = get_locale(), tolower = FALSE, ...) { | ||||
| #' @aliases ATC | ||||
| #' @export | ||||
| ab_atc <- function(x, ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer")) | ||||
|   ab_validate(x = x, property = "atc", ...) | ||||
| } | ||||
|  | ||||
| #' @rdname ab_property | ||||
| #' @export | ||||
| ab_cid <- function(x, ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer")) | ||||
|   ab_validate(x = x, property = "cid", ...) | ||||
| } | ||||
|  | ||||
| #' @rdname ab_property | ||||
| #' @export | ||||
| ab_synonyms <- function(x, ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer")) | ||||
|   syns <- ab_validate(x = x, property = "synonyms", ...) | ||||
|   names(syns) <- x | ||||
|   if (length(syns) == 1) { | ||||
| @@ -126,30 +133,38 @@ ab_synonyms <- function(x, ...) { | ||||
| #' @rdname ab_property | ||||
| #' @export | ||||
| ab_tradenames <- function(x, ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer")) | ||||
|   ab_synonyms(x, ...) | ||||
| } | ||||
|  | ||||
| #' @rdname ab_property | ||||
| #' @export | ||||
| ab_group <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer")) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   translate_AMR(ab_validate(x = x, property = "group", ...), language = language) | ||||
| } | ||||
|  | ||||
| #' @rdname ab_property | ||||
| #' @export | ||||
| ab_atc_group1 <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer")) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   translate_AMR(ab_validate(x = x, property = "atc_group1", ...), language = language) | ||||
| } | ||||
|  | ||||
| #' @rdname ab_property | ||||
| #' @export | ||||
| ab_atc_group2 <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer")) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   translate_AMR(ab_validate(x = x, property = "atc_group2", ...), language = language) | ||||
| } | ||||
|  | ||||
| #' @rdname ab_property | ||||
| #' @export | ||||
| ab_loinc <- function(x, ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer")) | ||||
|   loincs <- ab_validate(x = x, property = "loinc", ...) | ||||
|   names(loincs) <- x | ||||
|   if (length(loincs) == 1) { | ||||
| @@ -162,7 +177,10 @@ ab_loinc <- function(x, ...) { | ||||
| #' @rdname ab_property | ||||
| #' @export | ||||
| ab_ddd <- function(x, administration = "oral", units = FALSE, ...) { | ||||
|   stop_ifnot(administration %in% c("oral", "iv"), "`administration` must be 'oral' or 'iv'") | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer")) | ||||
|   meet_criteria(administration, is_in = c("oral", "iv"), has_length = 1) | ||||
|   meet_criteria(units, allow_class = "logical", has_length = 1) | ||||
|  | ||||
|   ddd_prop <- administration | ||||
|   if (units == TRUE) { | ||||
|     ddd_prop <- paste0(ddd_prop, "_units") | ||||
| @@ -175,6 +193,9 @@ ab_ddd <- function(x, administration = "oral", units = FALSE, ...) { | ||||
| #' @rdname ab_property | ||||
| #' @export | ||||
| ab_info <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer")) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   x <- as.ab(x, ...) | ||||
|   list(ab = as.character(x), | ||||
|              atc = ab_atc(x), | ||||
| @@ -194,6 +215,9 @@ ab_info <- function(x, language = get_locale(), ...) { | ||||
| #' @rdname ab_property | ||||
| #' @export | ||||
| ab_url <- function(x, open = FALSE, ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer")) | ||||
|   meet_criteria(open, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   ab <- as.ab(x = x, ... = ...) | ||||
|   u <- paste0("https://www.whocc.no/atc_ddd_index/?code=", ab_atc(ab), "&showdescription=no") | ||||
|   u[is.na(ab_atc(ab))] <- NA_character_ | ||||
| @@ -218,10 +242,9 @@ ab_url <- function(x, open = FALSE, ...) { | ||||
| #' @rdname ab_property | ||||
| #' @export | ||||
| ab_property <- function(x, property = "name", language = get_locale(), ...) { | ||||
|   stop_if(length(property) != 1L, "'property' must be of length 1.") | ||||
|   stop_ifnot(property %in% colnames(antibiotics), | ||||
|              "invalid property: '", property, "' - use a column name of the `antibiotics` data set") | ||||
|    | ||||
|   meet_criteria(x, allow_class = c("character", "numeric", "integer")) | ||||
|   meet_criteria(property, is_in = colnames(antibiotics), has_length = 1) | ||||
|   meet_criteria(language, is_in = c(LANGUAGES_SUPPORTED, ""), has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   translate_AMR(ab_validate(x = x, property = property, ...), language = language) | ||||
| } | ||||
|  | ||||
|   | ||||
							
								
								
									
										39
									
								
								R/age.R
									
									
									
									
									
								
							
							
						
						
									
										39
									
								
								R/age.R
									
									
									
									
									
								
							| @@ -28,9 +28,11 @@ | ||||
| #' Calculates age in years based on a reference date, which is the sytem date at default. | ||||
| #' @inheritSection lifecycle Stable lifecycle | ||||
| #' @param x date(s), will be coerced with [as.POSIXlt()] | ||||
| #' @param reference reference date(s) (defaults to today), will be coerced with [as.POSIXlt()] and cannot be lower than `x` | ||||
| #' @param reference reference date(s) (defaults to today), will be coerced with [as.POSIXlt()] | ||||
| #' @param exact a logical to indicate whether age calculation should be exact, i.e. with decimals. It divides the number of days of [year-to-date](https://en.wikipedia.org/wiki/Year-to-date) (YTD) of `x` by the number of days in the year of `reference` (either 365 or 366). | ||||
| #' @param na.rm a logical to indicate whether missing values should be removed | ||||
| #' @param ... parameters passed on to [as.POSIXlt()], such as `origin` | ||||
| #' @details Ages below 0 will be returned as `NA` with a warning. Ages above 120 will only give a warning. | ||||
| #' @return An [integer] (no decimals) if `exact = FALSE`, a [double] (with decimals) otherwise | ||||
| #' @seealso To split ages into groups, use the [age_groups()] function. | ||||
| #' @inheritSection AMR Read more on our website! | ||||
| @@ -44,13 +46,18 @@ | ||||
| #' df$age_exact <- age(df$birth_date, exact = TRUE) | ||||
| #' | ||||
| #' df | ||||
| age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE) { | ||||
| age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE, ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "Date", "POSIXt")) | ||||
|   meet_criteria(reference, allow_class = c("character", "Date", "POSIXt")) | ||||
|   meet_criteria(exact, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(na.rm, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   if (length(x) != length(reference)) { | ||||
|     stop_if(length(reference) != 1, "`x` and `reference` must be of same length, or `reference` must be of length 1.") | ||||
|     reference <- rep(reference, length(x)) | ||||
|   } | ||||
|   x <- as.POSIXlt(x) | ||||
|   reference <- as.POSIXlt(reference) | ||||
|   x <- as.POSIXlt(x, ...) | ||||
|   reference <- as.POSIXlt(reference, ...) | ||||
|    | ||||
|   # from https://stackoverflow.com/a/25450756/4575331 | ||||
|   years_gap <- reference$year - x$year | ||||
| @@ -98,13 +105,13 @@ age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE) { | ||||
| #' @param na.rm a [logical] to indicate whether missing values should be removed | ||||
| #' @details To split ages, the input for the `split_at` parameter can be: | ||||
| #'  | ||||
| #' * A numeric vector. A vector of e.g. `c(10, 20)` will split on 0-9, 10-19 and 20+. A value of only `50` will split on 0-49 and 50+. | ||||
| #' * A numeric vector. A value of e.g. `c(10, 20)` will split `x` on 0-9, 10-19 and 20+. A value of only `50` will split `x` on 0-49 and 50+. | ||||
| #'   The default is to split on young children (0-11), youth (12-24), young adults (25-54), middle-aged adults (55-74) and elderly (75+). | ||||
| #' * A character: | ||||
| #'   - `"children"` or `"kids"`, equivalent of: `c(0, 1, 2, 4, 6, 13, 18)`. This will split on 0, 1, 2-3, 4-5, 6-12, 13-17 and 18+. | ||||
| #'   - `"elderly"` or `"seniors"`, equivalent of: `c(65, 75, 85)`. This will split on 0-64, 65-74, 75-84, 85+. | ||||
| #'   - `"fives"`, equivalent of: `1:20 * 5`. This will split on 0-4, 5-9, 10-14, ..., 90-94, 95-99, 100+. | ||||
| #'   - `"tens"`, equivalent of: `1:10 * 10`. This will split on 0-9, 10-19, 20-29, ..., 80-89, 90-99, 100+. | ||||
| #'   - `"fives"`, equivalent of: `1:20 * 5`. This will split on 0-4, 5-9, ..., 95-99, 100+. | ||||
| #'   - `"tens"`, equivalent of: `1:10 * 10`. This will split on 0-9, 10-19, ..., 90-99, 100+. | ||||
| #' @return Ordered [factor] | ||||
| #' @seealso To determine ages, based on one or more reference dates, use the [age()] function. | ||||
| #' @export | ||||
| @@ -127,12 +134,11 @@ age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE) { | ||||
| #' age_groups(ages, split_at = "fives") | ||||
| #' | ||||
| #' # split specifically for children | ||||
| #' age_groups(ages, "children") | ||||
| #' # same: | ||||
| #' age_groups(ages, c(1, 2, 4, 6, 13, 17)) | ||||
| #' age_groups(ages, "children") | ||||
| #' | ||||
| #' \donttest{ | ||||
| #' # resistance of ciprofloxacine per age group | ||||
| #' # resistance of ciprofloxacin per age group | ||||
| #' library(dplyr) | ||||
| #' example_isolates %>% | ||||
| #'   filter_first_isolate() %>% | ||||
| @@ -142,7 +148,10 @@ age <- function(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE) { | ||||
| #'   ggplot_rsi(x = "age_group", minimum = 0) | ||||
| #' } | ||||
| age_groups <- function(x, split_at = c(12, 25, 55, 75), na.rm = FALSE) { | ||||
|   stop_ifnot(is.numeric(x), "`x` must be numeric, not ", paste0(class(x), collapse = "/")) | ||||
|   meet_criteria(x, allow_class = c("numeric", "integer")) | ||||
|   meet_criteria(split_at, allow_class = c("numeric", "integer", "character")) | ||||
|   meet_criteria(na.rm, allow_class = "logical", has_length = 1)  | ||||
|    | ||||
|   if (any(x < 0, na.rm = TRUE)) { | ||||
|     x[x < 0] <- NA | ||||
|     warning("NAs introduced for ages below 0.") | ||||
| @@ -169,17 +178,17 @@ age_groups <- function(x, split_at = c(12, 25, 55, 75), na.rm = FALSE) { | ||||
|    | ||||
|   # turn input values to 'split_at' indices | ||||
|   y <- x | ||||
|   labs <- split_at | ||||
|   lbls <- split_at | ||||
|   for (i in seq_len(length(split_at))) { | ||||
|     y[x >= split_at[i]] <- i | ||||
|     # create labels | ||||
|     labs[i - 1] <- paste0(unique(c(split_at[i - 1], split_at[i] - 1)), collapse = "-") | ||||
|     lbls[i - 1] <- paste0(unique(c(split_at[i - 1], split_at[i] - 1)), collapse = "-") | ||||
|   } | ||||
|    | ||||
|   # last category | ||||
|   labs[length(labs)] <- paste0(split_at[length(split_at)], "+") | ||||
|   lbls[length(lbls)] <- paste0(split_at[length(split_at)], "+") | ||||
|    | ||||
|   agegroups <- factor(labs[y], levels = labs, ordered = TRUE) | ||||
|   agegroups <- factor(lbls[y], levels = lbls, ordered = TRUE) | ||||
|    | ||||
|   if (isTRUE(na.rm)) { | ||||
|     agegroups <- agegroups[!is.na(agegroups)] | ||||
|   | ||||
| @@ -78,6 +78,11 @@ atc_online_property <- function(atc_code, | ||||
|                                 administration = "O", | ||||
|                                 url = "https://www.whocc.no/atc_ddd_index/?code=%s&showdescription=no", | ||||
|                                 url_vet = "https://www.whocc.no/atcvet/atcvet_index/?code=%s&showdescription=no") { | ||||
|   meet_criteria(atc_code, allow_class = "character") | ||||
|   meet_criteria(property, allow_class = "character", has_length = 1, is_in = c("ATC", "Name", "DDD", "U", "Adm.R", "Note", "groups"), ignore.case = TRUE) | ||||
|   meet_criteria(administration, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(url, allow_class = "character", has_length = 1, looks_like = "https?://") | ||||
|   meet_criteria(url_vet, allow_class = "character", has_length = 1, looks_like = "https?://") | ||||
|    | ||||
|   has_internet <- import_fn("has_internet", "curl") | ||||
|   html_attr <- import_fn("html_attr", "rvest") | ||||
| @@ -99,24 +104,12 @@ atc_online_property <- function(atc_code, | ||||
|     return(rep(NA, length(atc_code))) | ||||
|   } | ||||
|    | ||||
|   stop_if(length(property) != 1L, "`property` must be of length 1") | ||||
|   stop_if(length(administration) != 1L, "`administration` must be of length 1") | ||||
|    | ||||
|   # also allow unit as property | ||||
|   if (property %like% "unit") { | ||||
|     property <- "U" | ||||
|   } | ||||
|    | ||||
|   # validation of properties | ||||
|   valid_properties <- c("ATC", "Name", "DDD", "U", "Adm.R", "Note", "groups") | ||||
|   valid_properties.bak <- valid_properties | ||||
|    | ||||
|   property <- tolower(property) | ||||
|   valid_properties <- tolower(valid_properties) | ||||
|    | ||||
|   stop_ifnot(property %in% valid_properties, | ||||
|              "Invalid `property`, use one of ", paste(valid_properties.bak, collapse = ", ")) | ||||
|    | ||||
|   if (property == "ddd") { | ||||
|     returnvalue <- rep(NA_real_, length(atc_code)) | ||||
|   } else if (property == "groups") { | ||||
| @@ -199,11 +192,13 @@ atc_online_property <- function(atc_code, | ||||
| #' @rdname atc_online | ||||
| #' @export | ||||
| atc_online_groups <- function(atc_code, ...) { | ||||
|   meet_criteria(atc_code, allow_class = "character") | ||||
|   atc_online_property(atc_code = atc_code, property = "groups", ...) | ||||
| } | ||||
|  | ||||
| #' @rdname atc_online | ||||
| #' @export | ||||
| atc_online_ddd <- function(atc_code, ...) { | ||||
|   meet_criteria(atc_code, allow_class = "character") | ||||
|   atc_online_property(atc_code = atc_code, property = "ddd", ...) | ||||
| } | ||||
|   | ||||
| @@ -43,7 +43,9 @@ | ||||
| #'     availability() | ||||
| #' } | ||||
| availability <- function(tbl, width = NULL) { | ||||
|   stop_ifnot(is.data.frame(tbl), "`tbl` must be a data.frame") | ||||
|   meet_criteria(tbl, allow_class = "data.frame") | ||||
|   meet_criteria(width, allow_class = "numeric", allow_NULL = TRUE) | ||||
|    | ||||
|   x <- sapply(tbl, function(x) { | ||||
|     1 - sum(is.na(x)) / length(x)  | ||||
|   }) | ||||
|   | ||||
| @@ -31,8 +31,8 @@ | ||||
| #' @param combine_IR logical to indicate whether values R and I should be summed | ||||
| #' @param add_ab_group logical to indicate where the group of the antimicrobials must be included as a first column | ||||
| #' @param remove_intrinsic_resistant logical to indicate that rows and columns with 100% resistance for all tested antimicrobials must be removed from the table | ||||
| #' @param FUN the function to call on the `mo` column to transform the microorganism IDs, defaults to [mo_shortname()]  | ||||
| #' @param translate_ab a character of length 1 containing column names of the [antibiotics] data set | ||||
| #' @param FUN function to call on the `mo` column to transform the microorganism IDs, defaults to [mo_shortname()]  | ||||
| #' @param translate_ab character of length 1 containing column names of the [antibiotics] data set | ||||
| #' @param ... arguments passed on to `FUN` | ||||
| #' @inheritParams rsi_df | ||||
| #' @inheritParams base::formatC | ||||
| @@ -61,8 +61,9 @@ bug_drug_combinations <- function(x, | ||||
|                                   col_mo = NULL,  | ||||
|                                   FUN = mo_shortname, | ||||
|                                   ...) { | ||||
|   stop_ifnot(is.data.frame(x), "`x` must be a data frame") | ||||
|   stop_ifnot(any(sapply(x, is.rsi), na.rm = TRUE), "No columns with class <rsi> found. See ?as.rsi.") | ||||
|   meet_criteria(x, allow_class = "data.frame", contains_column_class = "rsi") | ||||
|   meet_criteria(col_mo, allow_class = "character", is_in = colnames(x), has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(FUN, allow_class = "function", has_length = 1) | ||||
|  | ||||
|   # try to find columns based on type | ||||
|   # -- mo | ||||
| @@ -121,6 +122,17 @@ format.bug_drug_combinations <- function(x, | ||||
|                                          decimal.mark = getOption("OutDec"), | ||||
|                                          big.mark = ifelse(decimal.mark == ",", ".", ","), | ||||
|                                          ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(translate_ab, allow_class = c("character", "logical"), has_length = 1, allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(combine_SI, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(combine_IR, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(add_ab_group, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(remove_intrinsic_resistant, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(decimal.mark, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(big.mark, allow_class = "character", has_length = 1) | ||||
|    | ||||
|   x <- as.data.frame(x, stringsAsFactors = FALSE) | ||||
|   x <- subset(x, total >= minimum) | ||||
|    | ||||
|   | ||||
| @@ -189,7 +189,6 @@ count_df <- function(data, | ||||
|                      language = get_locale(), | ||||
|                      combine_SI = TRUE, | ||||
|                      combine_IR = FALSE) { | ||||
|    | ||||
|   rsi_calc_df(type = "count", | ||||
|               data = data, | ||||
|               translate_ab = translate_ab, | ||||
|   | ||||
| @@ -30,4 +30,18 @@ | ||||
| #' @inheritSection AMR Read more on our website! | ||||
| #' @keywords internal | ||||
| #' @name AMR-deprecated | ||||
| # @export | ||||
| #' @export | ||||
| p_symbol <- function(p, emptychar = " ") { | ||||
|   .Deprecated(package = "AMR") | ||||
|    | ||||
|   p <- as.double(p) | ||||
|   s <- rep(NA_character_, length(p)) | ||||
|    | ||||
|   s[p <= 1] <- emptychar | ||||
|   s[p <= 0.100] <- "." | ||||
|   s[p <= 0.050] <- "*" | ||||
|   s[p <= 0.010] <- "**" | ||||
|   s[p <= 0.001] <- "***" | ||||
|    | ||||
|   s | ||||
| } | ||||
|   | ||||
							
								
								
									
										6
									
								
								R/disk.R
									
									
									
									
									
								
							
							
						
						
									
										6
									
								
								R/disk.R
									
									
									
									
									
								
							| @@ -58,6 +58,9 @@ | ||||
| #' as.rsi(df) | ||||
| #' } | ||||
| as.disk <- function(x, na.rm = FALSE) { | ||||
|   meet_criteria(x, allow_class = c("disk", "character", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(na.rm, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   if (!is.disk(x)) { | ||||
|     x <- x %pm>% unlist() | ||||
|     if (na.rm == TRUE) { | ||||
| @@ -109,6 +112,9 @@ as.disk <- function(x, na.rm = FALSE) { | ||||
| } | ||||
|  | ||||
| all_valid_disks <- function(x) { | ||||
|   if (!inherits(x, c("disk", "character", "numeric", "integer"))) { | ||||
|     return(FALSE) | ||||
|   } | ||||
|   x_disk <- suppressWarnings(as.disk(x[!is.na(x)])) | ||||
|   !any(is.na(x_disk)) & !all(is.na(x)) | ||||
| } | ||||
|   | ||||
| @@ -134,6 +134,13 @@ eucast_rules <- function(x, | ||||
|                          version_breakpoints = 10.0, | ||||
|                          version_expertrules = 3.2, | ||||
|                          ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(col_mo, allow_class = "character", has_length = 1, is_in = colnames(x), allow_NULL = TRUE) | ||||
|   meet_criteria(info, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(rules, allow_class = "character", has_length = c(1, 2, 3, 4), is_in = c("breakpoints", "expert", "other", "all")) | ||||
|   meet_criteria(verbose, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(version_breakpoints, allow_class = "numeric", has_length = 1) | ||||
|   meet_criteria(version_expertrules, allow_class = "numeric", has_length = 1) | ||||
|    | ||||
|   x_deparsed <- deparse(substitute(x)) | ||||
|   if (length(x_deparsed) > 1 || !all(x_deparsed %like% "[a-z]+")) { | ||||
| @@ -172,18 +179,12 @@ eucast_rules <- function(x, | ||||
|     } | ||||
|   } | ||||
|    | ||||
|   stop_ifnot(is.data.frame(x), "`x` must be a data frame") | ||||
|    | ||||
|   # try to find columns based on type | ||||
|   # -- mo | ||||
|   if (is.null(col_mo)) { | ||||
|     col_mo <- search_type_in_df(x = x, type = "mo", info = info) | ||||
|   } | ||||
|   stop_if(is.null(col_mo), "`col_mo` must be set") | ||||
|   stop_ifnot(col_mo %in% colnames(x), "column '", col_mo, "' (`col_mo`) not found") | ||||
|    | ||||
|   stop_ifnot(all(rules %in% c("breakpoints", "expert", "other", "all")), | ||||
|              '`rules` must be one or more of: "breakpoints", "expert", "other", "all".') | ||||
|    | ||||
|   decimal.mark <- getOption("OutDec") | ||||
|   big.mark <- ifelse(decimal.mark != ",", ",", ".") | ||||
| @@ -576,7 +577,7 @@ eucast_rules <- function(x, | ||||
|     # big speed gain! only analyse unique rows: | ||||
|     pm_distinct(`.rowid`, .keep_all = TRUE) %pm>%  | ||||
|     as.data.frame(stringsAsFactors = FALSE) | ||||
|   x[, col_mo] <- as.mo(x[, col_mo, drop = TRUE]) | ||||
|   x[, col_mo] <- as.mo(as.character(x[, col_mo, drop = TRUE])) | ||||
|   x <- x %pm>% | ||||
|     left_join_microorganisms(by = col_mo, suffix = c("_oldcols", "")) | ||||
|   x$gramstain <- mo_gramstain(x[, col_mo, drop = TRUE], language = NULL) | ||||
|   | ||||
| @@ -80,16 +80,22 @@ filter_ab_class <- function(x, | ||||
|                             result = NULL, | ||||
|                             scope = "any", | ||||
|                             ...) { | ||||
|   .call_depth <- list(...)$`.call_depth` | ||||
|   if (is.null(.call_depth)) { | ||||
|     .call_depth <- 0 | ||||
|   } | ||||
|   meet_criteria(x, allow_class = "data.frame", .call_depth = .call_depth) | ||||
|   meet_criteria(ab_class, allow_class = "character", has_length = 1, .call_depth = .call_depth) | ||||
|   meet_criteria(result, allow_class = "character", has_length = c(1, 2, 3), allow_NULL = TRUE, .call_depth = .call_depth) | ||||
|   meet_criteria(scope, allow_class = "character", has_length = 1, is_in = c("all", "any"), .call_depth = .call_depth) | ||||
|  | ||||
|   check_dataset_integrity() | ||||
|   stop_ifnot(is.data.frame(x), "`x` must be a data frame") | ||||
|  | ||||
|   # save to return later | ||||
|   x_class <- class(x) | ||||
|   x.bak <- x | ||||
|   x <- as.data.frame(x, stringsAsFactors = FALSE) | ||||
|    | ||||
|   scope <- scope[1L] | ||||
|   if (is.null(result)) { | ||||
|     result <- c("S", "I", "R") | ||||
|   } | ||||
| @@ -174,6 +180,7 @@ filter_aminoglycosides <- function(x, | ||||
|                   ab_class = "aminoglycoside", | ||||
|                   result = result, | ||||
|                   scope = scope, | ||||
|                   .call_depth = 1, | ||||
|                   ...) | ||||
| } | ||||
|  | ||||
| @@ -187,6 +194,7 @@ filter_carbapenems <- function(x, | ||||
|                   ab_class = "carbapenem", | ||||
|                   result = result, | ||||
|                   scope = scope, | ||||
|                   .call_depth = 1, | ||||
|                   ...) | ||||
| } | ||||
|  | ||||
| @@ -200,6 +208,7 @@ filter_cephalosporins <- function(x, | ||||
|                   ab_class = "cephalosporin", | ||||
|                   result = result, | ||||
|                   scope = scope, | ||||
|                   .call_depth = 1, | ||||
|                   ...) | ||||
| } | ||||
|  | ||||
| @@ -213,6 +222,7 @@ filter_1st_cephalosporins <- function(x, | ||||
|                   ab_class = "cephalosporins (1st gen.)", | ||||
|                   result = result, | ||||
|                   scope = scope, | ||||
|                   .call_depth = 1, | ||||
|                   ...) | ||||
| } | ||||
|  | ||||
| @@ -226,6 +236,7 @@ filter_2nd_cephalosporins <- function(x, | ||||
|                   ab_class = "cephalosporins (2nd gen.)", | ||||
|                   result = result, | ||||
|                   scope = scope, | ||||
|                   .call_depth = 1, | ||||
|                   ...) | ||||
| } | ||||
|  | ||||
| @@ -239,6 +250,7 @@ filter_3rd_cephalosporins <- function(x, | ||||
|                   ab_class = "cephalosporins (3rd gen.)", | ||||
|                   result = result, | ||||
|                   scope = scope, | ||||
|                   .call_depth = 1, | ||||
|                   ...) | ||||
| } | ||||
|  | ||||
| @@ -252,6 +264,7 @@ filter_4th_cephalosporins <- function(x, | ||||
|                   ab_class = "cephalosporins (4th gen.)", | ||||
|                   result = result, | ||||
|                   scope = scope, | ||||
|                   .call_depth = 1, | ||||
|                   ...) | ||||
| } | ||||
|  | ||||
| @@ -265,6 +278,7 @@ filter_5th_cephalosporins <- function(x, | ||||
|                   ab_class = "cephalosporins (5th gen.)", | ||||
|                   result = result, | ||||
|                   scope = scope, | ||||
|                   .call_depth = 1, | ||||
|                   ...) | ||||
| } | ||||
|  | ||||
| @@ -278,6 +292,7 @@ filter_fluoroquinolones <- function(x, | ||||
|                   ab_class = "fluoroquinolone", | ||||
|                   result = result, | ||||
|                   scope = scope, | ||||
|                   .call_depth = 1, | ||||
|                   ...) | ||||
| } | ||||
|  | ||||
| @@ -291,6 +306,7 @@ filter_glycopeptides <- function(x, | ||||
|                   ab_class = "glycopeptide", | ||||
|                   result = result, | ||||
|                   scope = scope, | ||||
|                   .call_depth = 1, | ||||
|                   ...) | ||||
| } | ||||
|  | ||||
| @@ -304,6 +320,7 @@ filter_macrolides <- function(x, | ||||
|                   ab_class = "macrolide", | ||||
|                   result = result, | ||||
|                   scope = scope, | ||||
|                   .call_depth = 1, | ||||
|                   ...) | ||||
| } | ||||
|  | ||||
| @@ -317,6 +334,7 @@ filter_penicillins <- function(x, | ||||
|                   ab_class = "penicillin", | ||||
|                   result = result, | ||||
|                   scope = scope, | ||||
|                   .call_depth = 1, | ||||
|                   ...) | ||||
| } | ||||
|  | ||||
| @@ -330,6 +348,7 @@ filter_tetracyclines <- function(x, | ||||
|                   ab_class = "tetracycline", | ||||
|                   result = result, | ||||
|                   scope = scope, | ||||
|                   .call_depth = 1, | ||||
|                   ...) | ||||
| } | ||||
|  | ||||
|   | ||||
| @@ -139,6 +139,23 @@ first_isolate <- function(x, | ||||
|                           info = interactive(), | ||||
|                           include_unknown = FALSE, | ||||
|                           ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(col_date, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   meet_criteria(col_patient_id, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   meet_criteria(col_mo, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   meet_criteria(col_testcode, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   meet_criteria(col_specimen, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   meet_criteria(col_icu, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   meet_criteria(col_keyantibiotics, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   meet_criteria(episode_days, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(testcodes_exclude, allow_class = "character", allow_NULL = TRUE) | ||||
|   meet_criteria(icu_exclude, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(specimen_group, allow_class = "character", has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(type, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(ignore_I, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(points_threshold, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(info, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(include_unknown, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   dots <- unlist(list(...)) | ||||
|   if (length(dots) != 0) { | ||||
| @@ -352,20 +369,20 @@ first_isolate <- function(x, | ||||
|                                              info = info) | ||||
|     # with key antibiotics | ||||
|     x$newvar_first_isolate <- pm_if_else(x$newvar_row_index_sorted >= row.start & | ||||
|                                         x$newvar_row_index_sorted <= row.end & | ||||
|                                         x$newvar_genus_species != "" &  | ||||
|                                         (x$other_pat_or_mo | x$more_than_episode_ago | x$other_key_ab), | ||||
|                                       TRUE, | ||||
|                                       FALSE) | ||||
|                                            x$newvar_row_index_sorted <= row.end & | ||||
|                                            x$newvar_genus_species != "" &  | ||||
|                                            (x$other_pat_or_mo | x$more_than_episode_ago | x$other_key_ab), | ||||
|                                          TRUE, | ||||
|                                          FALSE) | ||||
|      | ||||
|   } else { | ||||
|     # no key antibiotics | ||||
|     x$newvar_first_isolate <- pm_if_else(x$newvar_row_index_sorted >= row.start & | ||||
|                                         x$newvar_row_index_sorted <= row.end & | ||||
|                                         x$newvar_genus_species != "" &  | ||||
|                                         (x$other_pat_or_mo | x$more_than_episode_ago), | ||||
|                                       TRUE, | ||||
|                                       FALSE) | ||||
|                                            x$newvar_row_index_sorted <= row.end & | ||||
|                                            x$newvar_genus_species != "" &  | ||||
|                                            (x$other_pat_or_mo | x$more_than_episode_ago), | ||||
|                                          TRUE, | ||||
|                                          FALSE) | ||||
|   } | ||||
|    | ||||
|   # first one as TRUE | ||||
| @@ -442,6 +459,10 @@ filter_first_isolate <- function(x, | ||||
|                                  col_patient_id = NULL, | ||||
|                                  col_mo = NULL, | ||||
|                                  ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(col_date, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   meet_criteria(col_patient_id, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   meet_criteria(col_mo, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   subset(x, first_isolate(x = x, | ||||
|                           col_date = col_date, | ||||
|                           col_patient_id = col_patient_id, | ||||
| @@ -457,6 +478,11 @@ filter_first_weighted_isolate <- function(x, | ||||
|                                           col_mo = NULL, | ||||
|                                           col_keyantibiotics = NULL, | ||||
|                                           ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(col_date, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   meet_criteria(col_patient_id, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   meet_criteria(col_mo, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   meet_criteria(col_keyantibiotics, allow_class = "character", has_length = 1, allow_NULL = TRUE, is_in = colnames(x)) | ||||
|   y <- x | ||||
|   if (is.null(col_keyantibiotics)) { | ||||
|     # first try to look for it | ||||
|   | ||||
| @@ -53,9 +53,10 @@ | ||||
| #' As per their GPL-2 licence that demands documentation of code changes, the changes made based on the source code were:  | ||||
| #' 1. Rewritten code to remove the dependency on packages `plyr`, `scales` and `grid` | ||||
| #' 2. Parametrised more options, like arrow and ellipse settings | ||||
| #' 3. Added total amount of explained variance as a caption in the plot | ||||
| #' 4. Cleaned all syntax based on the `lintr` package and added integrity checks | ||||
| #' 5. Updated documentation | ||||
| #' 3. Hardened all input possibilities by defining the exact type of user input for every parameter | ||||
| #' 4. Added total amount of explained variance as a caption in the plot | ||||
| #' 5. Cleaned all syntax based on the `lintr` package, fixed grammatical errors and added integrity checks | ||||
| #' 6. Updated documentation | ||||
| #' @details The colours for labels and points can be changed by adding another scale layer for colour, like `scale_colour_viridis_d()` or `scale_colour_brewer()`. | ||||
| #' @rdname ggplot_pca | ||||
| #' @export | ||||
| @@ -85,7 +86,7 @@ | ||||
| #' } | ||||
| ggplot_pca <- function(x, | ||||
|                        choices = 1:2, | ||||
|                        scale = TRUE, | ||||
|                        scale = 1, | ||||
|                        pc.biplot = TRUE, | ||||
|                        labels = NULL, | ||||
|                        labels_textsize = 3, | ||||
| @@ -107,22 +108,27 @@ ggplot_pca <- function(x, | ||||
|                        ...) { | ||||
|    | ||||
|   stop_ifnot_installed("ggplot2") | ||||
|   stop_ifnot(length(choices) == 2, "`choices` must be of length 2") | ||||
|   stop_ifnot(is.logical(arrows), "`arrows` must be TRUE or FALSE") | ||||
|   stop_ifnot(is.logical(arrows_textangled), "`arrows_textangled` must be TRUE or FALSE") | ||||
|   stop_ifnot(is.logical(ellipse), "`ellipse` must be TRUE or FALSE") | ||||
|   stop_ifnot(is.logical(pc.biplot), "`pc.biplot` must be TRUE or FALSE") | ||||
|   stop_ifnot(is.logical(scale), "`scale` must be TRUE or FALSE") | ||||
|   stop_ifnot(is.numeric(arrows_alpha), "`arrows_alpha` must be numeric") | ||||
|   stop_ifnot(is.numeric(arrows_size), "`arrows_size` must be numeric") | ||||
|   stop_ifnot(is.numeric(arrows_textsize), "`arrows_textsize` must be numeric") | ||||
|   stop_ifnot(is.numeric(base_textsize), "`base_textsize` must be numeric") | ||||
|   stop_ifnot(is.numeric(choices), "`choices` must be numeric") | ||||
|   stop_ifnot(is.numeric(ellipse_alpha), "`ellipse_alpha` must be numeric") | ||||
|   stop_ifnot(is.numeric(ellipse_prob), "`ellipse_prob` must be numeric") | ||||
|   stop_ifnot(is.numeric(ellipse_size), "`ellipse_size` must be numeric") | ||||
|   stop_ifnot(is.numeric(labels_text_placement), "`labels_text_placement` must be numeric") | ||||
|   stop_ifnot(is.numeric(labels_textsize), "`labels_textsize` must be numeric") | ||||
|   meet_criteria(x, allow_class = c("prcomp", "princomp", "PCA", "lda")) | ||||
|   meet_criteria(choices, allow_class = c("numeric", "integer"), has_length = 2) | ||||
|   meet_criteria(scale, allow_class = c("numeric", "integer", "logical"), has_length = 1) | ||||
|   meet_criteria(pc.biplot, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(labels, allow_class = "character", allow_NULL = TRUE) | ||||
|   meet_criteria(labels_textsize, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(labels_text_placement, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(groups, allow_class = "character", allow_NULL = TRUE) | ||||
|   meet_criteria(ellipse, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(ellipse_prob, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(ellipse_size, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(ellipse_alpha, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(points_size, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(points_alpha, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(arrows, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(arrows_colour, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(arrows_size, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(arrows_textsize, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(arrows_textangled, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(arrows_alpha, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(base_textsize, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|    | ||||
|   calculations <- pca_calculations(pca_model = x, | ||||
|                                    groups = groups,  | ||||
| @@ -302,7 +308,7 @@ pca_calculations <- function(pca_model, | ||||
|     v <- pca_model$scaling | ||||
|     d.total <- sum(d ^ 2) | ||||
|   } else { | ||||
|     stop("Expected a object of class prcomp, princomp, PCA, or lda") | ||||
|     stop("Expected an object of class prcomp, princomp, PCA, or lda") | ||||
|   } | ||||
|    | ||||
|   # Scores | ||||
|   | ||||
| @@ -171,9 +171,28 @@ ggplot_rsi <- function(data, | ||||
|                        ...) { | ||||
|    | ||||
|   stop_ifnot_installed("ggplot2") | ||||
|    | ||||
|   x <- x[1] | ||||
|   facet <- facet[1] | ||||
|   meet_criteria(data, allow_class = "data.frame", contains_column_class = "rsi") | ||||
|   meet_criteria(position, allow_class = "character", has_length = 1, is_in = c("fill", "stack", "dodge"), allow_NULL = TRUE) | ||||
|   meet_criteria(x, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(fill, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(facet, allow_class = "character", has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(breaks, allow_class = c("numeric", "integer")) | ||||
|   meet_criteria(limits, allow_class = c("numeric", "integer"), has_length = 2, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(translate_ab, allow_class = c("character", "logical"), has_length = 1, allow_NA = TRUE) | ||||
|   meet_criteria(combine_SI, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(combine_IR, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(nrow, allow_class = c("numeric", "integer"), has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(colours, allow_class = "character") | ||||
|   meet_criteria(datalabels, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(datalabels.size, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(datalabels.colour, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(title, allow_class = "character", has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(subtitle, allow_class = "character", has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(caption, allow_class = "character", has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(x.title, allow_class = "character", has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(y.title, allow_class = "character", has_length = 1, allow_NULL = TRUE) | ||||
|  | ||||
|   # we work with aes_string later on | ||||
|   x_deparse <- deparse(substitute(x)) | ||||
| @@ -256,7 +275,15 @@ geom_rsi <- function(position = NULL, | ||||
|                      ...)  { | ||||
|    | ||||
|   stop_ifnot_installed("ggplot2") | ||||
|   stop_if(is.data.frame(position), "`position` is invalid. Did you accidentally use '%pm>%' instead of '+'?") | ||||
|   stop_if(is.data.frame(position), "`position` is invalid. Did you accidentally use '%>%' instead of '+'?") | ||||
|   meet_criteria(position, allow_class = "character", has_length = 1, is_in = c("fill", "stack", "dodge"), allow_NULL = TRUE) | ||||
|   meet_criteria(x, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(fill, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(translate_ab, allow_class = c("character", "logical"), has_length = 1, allow_NA = TRUE) | ||||
|   meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(combine_SI, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(combine_IR, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   y <- "value" | ||||
|   if (missing(position) | is.null(position)) { | ||||
| @@ -300,10 +327,10 @@ geom_rsi <- function(position = NULL, | ||||
| #' @rdname ggplot_rsi | ||||
| #' @export | ||||
| facet_rsi <- function(facet = c("interpretation", "antibiotic"), nrow = NULL) { | ||||
|    | ||||
|   stop_ifnot_installed("ggplot2") | ||||
|    | ||||
|   facet <- facet[1] | ||||
|   stop_ifnot_installed("ggplot2") | ||||
|   meet_criteria(facet, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(nrow, allow_class = c("numeric", "integer"), has_length = 1, allow_NULL = TRUE) | ||||
|    | ||||
|   # we work with aes_string later on | ||||
|   facet_deparse <- deparse(substitute(facet)) | ||||
| @@ -327,6 +354,8 @@ facet_rsi <- function(facet = c("interpretation", "antibiotic"), nrow = NULL) { | ||||
| #' @export | ||||
| scale_y_percent <- function(breaks = seq(0, 1, 0.1), limits = NULL) { | ||||
|   stop_ifnot_installed("ggplot2") | ||||
|   meet_criteria(breaks, allow_class = c("numeric", "integer")) | ||||
|   meet_criteria(limits, allow_class = c("numeric", "integer"), has_length = 2, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   if (all(breaks[breaks != 0] > 1)) { | ||||
|     breaks <- breaks / 100 | ||||
| @@ -344,6 +373,8 @@ scale_rsi_colours <- function(colours = c(S = "#61a8ff", | ||||
|                                           IR = "#ff6961", | ||||
|                                           R = "#ff6961")) { | ||||
|   stop_ifnot_installed("ggplot2") | ||||
|   meet_criteria(colours, allow_class = "character") | ||||
|    | ||||
|   # previous colour: palette = "RdYlGn" | ||||
|   # previous colours: values = c("#b22222", "#ae9c20", "#7cfc00") | ||||
|    | ||||
| @@ -383,6 +414,16 @@ labels_rsi_count <- function(position = NULL, | ||||
|                              datalabels.size = 3, | ||||
|                              datalabels.colour = "gray15") { | ||||
|   stop_ifnot_installed("ggplot2") | ||||
|   meet_criteria(position, allow_class = "character", has_length = 1, is_in = c("fill", "stack", "dodge"), allow_NULL = TRUE) | ||||
|   meet_criteria(x, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(translate_ab, allow_class = c("character", "logical"), has_length = 1, allow_NA = TRUE) | ||||
|   meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(combine_SI, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(combine_IR, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(datalabels.size, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(datalabels.colour, allow_class = "character", has_length = 1) | ||||
|    | ||||
|   if (is.null(position)) { | ||||
|     position <- "fill" | ||||
|   } | ||||
|   | ||||
| @@ -30,7 +30,7 @@ | ||||
| #' @param x a [data.frame] | ||||
| #' @param search_string a text to search `x` for, will be checked with [as.ab()] if this value is not a column in `x` | ||||
| #' @param verbose a logical to indicate whether additional info should be printed | ||||
| #' @details You can look for an antibiotic (trade) name or abbreviation and it will search `x` and the [antibiotics] data set for any column containing a name or code of that antibiotic. **Longer columns names take precendence over shorter column names.** | ||||
| #' @details You can look for an antibiotic (trade) name or abbreviation and it will search `x` and the [antibiotics] data set for any column containing a name or code of that antibiotic. **Longer columns names take precedence over shorter column names.** | ||||
| #' @return A column name of `x`, or `NULL` when no result is found. | ||||
| #' @export | ||||
| #' @inheritSection AMR Read more on our website! | ||||
| @@ -63,16 +63,13 @@ | ||||
| #' guess_ab_col(df, "ampicillin") | ||||
| #' # [1] "AMP_ED20" | ||||
| guess_ab_col <- function(x = NULL, search_string = NULL, verbose = FALSE) { | ||||
|   meet_criteria(x, allow_class = "data.frame", allow_NULL = TRUE) | ||||
|   meet_criteria(search_string, allow_class = "character", has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(verbose, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   if (is.null(x) & is.null(search_string)) { | ||||
|     return(as.name("guess_ab_col")) | ||||
|   } | ||||
|   stop_ifnot(is.data.frame(x), "`x` must be a data.frame") | ||||
|    | ||||
|   if (length(search_string) > 1) { | ||||
|     warning("argument 'search_string' has length > 1 and only the first element will be used") | ||||
|     search_string <- search_string[1] | ||||
|   } | ||||
|   search_string <- as.character(search_string) | ||||
|    | ||||
|   if (search_string %in% colnames(x)) { | ||||
|     ab_result <- search_string | ||||
| @@ -116,6 +113,11 @@ get_column_abx <- function(x, | ||||
|                            verbose = FALSE, | ||||
|                            info = TRUE, | ||||
|                            ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(soft_dependencies, allow_class = "character", allow_NULL = TRUE) | ||||
|   meet_criteria(hard_dependencies, allow_class = "character", allow_NULL = TRUE) | ||||
|   meet_criteria(verbose, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(info, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   if (info == TRUE) { | ||||
|     message(font_blue("NOTE: Auto-guessing columns suitable for analysis"), appendLF = FALSE) | ||||
|   | ||||
| @@ -61,8 +61,12 @@ | ||||
| #' } | ||||
| #' } | ||||
| inner_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) { | ||||
|   meet_criteria(x, allow_class = c("data.frame", "character")) | ||||
|   meet_criteria(by, allow_class = "character", allow_NULL = TRUE) | ||||
|   meet_criteria(suffix, allow_class = "character", has_length = 2) | ||||
|    | ||||
|   check_dataset_integrity() | ||||
|   check_groups_before_join(x, "inner_join_microorganisms") | ||||
|   x <- check_groups_before_join(x, "inner_join_microorganisms") | ||||
|   checked <- joins_check_df(x, by) | ||||
|   x_class <- get_prejoined_class(x) | ||||
|   x <- checked$x | ||||
| @@ -88,8 +92,12 @@ inner_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) { | ||||
| #' @rdname join | ||||
| #' @export | ||||
| left_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) { | ||||
|   meet_criteria(x, allow_class = c("data.frame", "character")) | ||||
|   meet_criteria(by, allow_class = "character", allow_NULL = TRUE) | ||||
|   meet_criteria(suffix, allow_class = "character", has_length = 2) | ||||
|    | ||||
|   check_dataset_integrity() | ||||
|   check_groups_before_join(x, "left_join_microorganisms") | ||||
|   x <- check_groups_before_join(x, "left_join_microorganisms") | ||||
|   checked <- joins_check_df(x, by) | ||||
|   x_class <- get_prejoined_class(x) | ||||
|   x <- checked$x | ||||
| @@ -115,8 +123,12 @@ left_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) { | ||||
| #' @rdname join | ||||
| #' @export | ||||
| right_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) { | ||||
|   meet_criteria(x, allow_class = c("data.frame", "character")) | ||||
|   meet_criteria(by, allow_class = "character", allow_NULL = TRUE) | ||||
|   meet_criteria(suffix, allow_class = "character", has_length = 2) | ||||
|    | ||||
|   check_dataset_integrity() | ||||
|   check_groups_before_join(x, "right_join_microorganisms") | ||||
|   x <- check_groups_before_join(x, "right_join_microorganisms") | ||||
|   checked <- joins_check_df(x, by) | ||||
|   x_class <- get_prejoined_class(x) | ||||
|   x <- checked$x | ||||
| @@ -142,8 +154,12 @@ right_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) { | ||||
| #' @rdname join | ||||
| #' @export | ||||
| full_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) { | ||||
|   meet_criteria(x, allow_class = c("data.frame", "character")) | ||||
|   meet_criteria(by, allow_class = "character", allow_NULL = TRUE) | ||||
|   meet_criteria(suffix, allow_class = "character", has_length = 2) | ||||
|    | ||||
|   check_dataset_integrity() | ||||
|   check_groups_before_join(x, "full_join_microorganisms") | ||||
|   x <- check_groups_before_join(x, "full_join_microorganisms") | ||||
|   checked <- joins_check_df(x, by) | ||||
|   x_class <- get_prejoined_class(x) | ||||
|   x <- checked$x | ||||
| @@ -169,8 +185,11 @@ full_join_microorganisms <- function(x, by = NULL, suffix = c("2", ""), ...) { | ||||
| #' @rdname join | ||||
| #' @export | ||||
| semi_join_microorganisms <- function(x, by = NULL, ...) { | ||||
|   meet_criteria(x, allow_class = c("data.frame", "character")) | ||||
|   meet_criteria(by, allow_class = "character", allow_NULL = TRUE) | ||||
|    | ||||
|   check_dataset_integrity() | ||||
|   check_groups_before_join(x, "semi_join_microorganisms") | ||||
|   x <- check_groups_before_join(x, "semi_join_microorganisms") | ||||
|   x_class <- get_prejoined_class(x) | ||||
|   checked <- joins_check_df(x, by) | ||||
|   x <- checked$x | ||||
| @@ -193,8 +212,11 @@ semi_join_microorganisms <- function(x, by = NULL, ...) { | ||||
| #' @rdname join | ||||
| #' @export | ||||
| anti_join_microorganisms <- function(x, by = NULL, ...) { | ||||
|   meet_criteria(x, allow_class = c("data.frame", "character")) | ||||
|   meet_criteria(by, allow_class = "character", allow_NULL = TRUE) | ||||
|    | ||||
|   check_dataset_integrity() | ||||
|   check_groups_before_join(x, "anti_join_microorganisms") | ||||
|   x <- check_groups_before_join(x, "anti_join_microorganisms") | ||||
|   checked <- joins_check_df(x, by) | ||||
|   x_class <- get_prejoined_class(x) | ||||
|   x <- checked$x | ||||
| @@ -255,6 +277,10 @@ get_prejoined_class <- function(x) { | ||||
|  | ||||
| check_groups_before_join <- function(x, fn) { | ||||
|   if (is.data.frame(x) && !is.null(attributes(x)$groups)) { | ||||
|     warning("Groups are dropped, since the ", fn, "() function relies on merge() from base R, not on join() from dplyr.", call. = FALSE) | ||||
|     x <- pm_ungroup(x) | ||||
|     attr(x, "groups") <- NULL | ||||
|     class(x) <- class(x)[!class(x) %like% "group"] | ||||
|     warning("Groups are dropped, since the ", fn, "() function relies on merge() from base R if dplyr is not installed.", call. = FALSE) | ||||
|   } | ||||
|   x | ||||
| } | ||||
|   | ||||
| @@ -27,14 +27,14 @@ | ||||
| #' | ||||
| #' These function can be used to determine first isolates (see [first_isolate()]). Using key antibiotics to determine first isolates is more reliable than without key antibiotics. These selected isolates will then be called first *weighted* isolates. | ||||
| #' @inheritSection lifecycle Stable lifecycle | ||||
| #' @param x table with antibiotics coloms, like `AMX` or `amox` | ||||
| #' @param y,z characters to compare | ||||
| #' @param x a data.frame with antibiotics columns, like `AMX` or `amox` | ||||
| #' @param y,z character vectors to compare | ||||
| #' @inheritParams first_isolate | ||||
| #' @param universal_1,universal_2,universal_3,universal_4,universal_5,universal_6 column names of **broad-spectrum** antibiotics, case-insensitive. At default, the columns containing these antibiotics will be guessed with [guess_ab_col()]. | ||||
| #' @param GramPos_1,GramPos_2,GramPos_3,GramPos_4,GramPos_5,GramPos_6 column names of antibiotics for **Gram-positives**, case-insensitive. At default, the columns containing these antibiotics will be guessed with [guess_ab_col()]. | ||||
| #' @param GramNeg_1,GramNeg_2,GramNeg_3,GramNeg_4,GramNeg_5,GramNeg_6 column names of antibiotics for **Gram-negatives**, case-insensitive. At default, the columns containing these antibiotics will be guessed with [guess_ab_col()]. | ||||
| #' @param warnings give warning about missing antibiotic columns, they will anyway be ignored | ||||
| #' @param ... other parameters passed on to function | ||||
| #' @param universal_1,universal_2,universal_3,universal_4,universal_5,universal_6 column names of **broad-spectrum** antibiotics, case-insensitive. See details for which antibiotics will be used at default (which are guessed with [guess_ab_col()]). | ||||
| #' @param GramPos_1,GramPos_2,GramPos_3,GramPos_4,GramPos_5,GramPos_6 column names of antibiotics for **Gram-positives**, case-insensitive. See details for which antibiotics will be used at default (which are guessed with [guess_ab_col()]). | ||||
| #' @param GramNeg_1,GramNeg_2,GramNeg_3,GramNeg_4,GramNeg_5,GramNeg_6 column names of antibiotics for **Gram-negatives**, case-insensitive. See details for which antibiotics will be used at default (which are guessed with [guess_ab_col()]). | ||||
| #' @param warnings give a warning about missing antibiotic columns (they will be ignored) | ||||
| #' @param ... other parameters passed on to functions | ||||
| #' @details The function [key_antibiotics()] returns a character vector with 12 antibiotic results for every isolate. These isolates can then be compared using [key_antibiotics_equal()], to check if two isolates have generally the same antibiogram. Missing and invalid values are replaced with a dot (`"."`) by [key_antibiotics()] and ignored by [key_antibiotics_equal()]. | ||||
| #'  | ||||
| #' The [first_isolate()] function only uses this function on the same microbial species from the same patient. Using this, e.g. an MRSA will be included after a susceptible *S. aureus* (MSSA) is found within the same patient episode. Without key antibiotic comparison it would not. See [first_isolate()] for more info. | ||||
| @@ -127,6 +127,27 @@ key_antibiotics <- function(x, | ||||
|                             GramNeg_6 = guess_ab_col(x, "meropenem"), | ||||
|                             warnings = TRUE, | ||||
|                             ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(col_mo, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(universal_1, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(universal_2, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(universal_3, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(universal_4, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(universal_5, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(universal_6, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(GramPos_1, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(GramPos_2, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(GramPos_3, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(GramPos_4, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(GramPos_5, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(GramPos_6, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(GramNeg_1, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(GramNeg_2, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(GramNeg_3, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(GramNeg_4, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(GramNeg_5, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(GramNeg_6, allow_class = "character", has_length = 1, allow_NULL = TRUE, allow_NA = TRUE) | ||||
|   meet_criteria(warnings, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   dots <- unlist(list(...)) | ||||
|   if (length(dots) != 0) { | ||||
| @@ -258,14 +279,20 @@ key_antibiotics_equal <- function(y, | ||||
|                                   ignore_I = TRUE, | ||||
|                                   points_threshold = 2, | ||||
|                                   info = FALSE) { | ||||
|   meet_criteria(y, allow_class = "character") | ||||
|   meet_criteria(z, allow_class = "character") | ||||
|   meet_criteria(type, allow_class = "character", has_length = c(1, 2)) | ||||
|   meet_criteria(ignore_I, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(points_threshold, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(info, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   stop_ifnot(length(y) == length(z), "length of `y` and `z` must be equal") | ||||
|   # y is active row, z is lag | ||||
|   x <- y | ||||
|   y <- z | ||||
|    | ||||
|   type <- type[1] | ||||
|    | ||||
|   stop_ifnot(length(x) == length(y), "length of `x` and `y` must be equal") | ||||
|    | ||||
|   # only show progress bar on points or when at least 5000 isolates | ||||
|   info_needed <- info == TRUE & (type == "points" | length(x) > 5000) | ||||
|    | ||||
|   | ||||
| @@ -35,6 +35,8 @@ | ||||
| #' @inheritSection AMR Read more on our website! | ||||
| #' @export | ||||
| kurtosis <- function(x, na.rm = FALSE, excess = FALSE) { | ||||
|   meet_criteria(na.rm, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(excess, allow_class = "logical", has_length = 1) | ||||
|   UseMethod("kurtosis") | ||||
| } | ||||
|  | ||||
| @@ -42,6 +44,8 @@ kurtosis <- function(x, na.rm = FALSE, excess = FALSE) { | ||||
| #' @rdname kurtosis | ||||
| #' @export | ||||
| kurtosis.default <- function(x, na.rm = FALSE, excess = FALSE) { | ||||
|   meet_criteria(na.rm, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(excess, allow_class = "logical", has_length = 1) | ||||
|   x <- as.vector(x) | ||||
|   if (na.rm == TRUE) { | ||||
|     x <- x[!is.na(x)] | ||||
| @@ -56,6 +60,8 @@ kurtosis.default <- function(x, na.rm = FALSE, excess = FALSE) { | ||||
| #' @rdname kurtosis | ||||
| #' @export | ||||
| kurtosis.matrix <- function(x, na.rm = FALSE, excess = FALSE) { | ||||
|   meet_criteria(na.rm, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(excess, allow_class = "logical", has_length = 1) | ||||
|   apply(x, 2, kurtosis.default, na.rm = na.rm, excess = excess) | ||||
| } | ||||
|  | ||||
| @@ -63,5 +69,7 @@ kurtosis.matrix <- function(x, na.rm = FALSE, excess = FALSE) { | ||||
| #' @rdname kurtosis | ||||
| #' @export | ||||
| kurtosis.data.frame <- function(x, na.rm = FALSE, excess = FALSE) { | ||||
|   meet_criteria(na.rm, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(excess, allow_class = "logical", has_length = 1) | ||||
|   sapply(x, kurtosis.default, na.rm = na.rm, excess = excess) | ||||
| } | ||||
|   | ||||
							
								
								
									
										14
									
								
								R/like.R
									
									
									
									
									
								
							
							
						
						
									
										14
									
								
								R/like.R
									
									
									
									
									
								
							| @@ -68,6 +68,10 @@ | ||||
| #' } | ||||
| #' } | ||||
| like <- function(x, pattern, ignore.case = TRUE) { | ||||
|   meet_criteria(x, allow_NA = TRUE) | ||||
|   meet_criteria(pattern, allow_class = "character") | ||||
|   meet_criteria(ignore.case, allow_class = "logical", has_length = 1) | ||||
|  | ||||
|   # set to fixed if no regex found | ||||
|   fixed <- !any(is_possibly_regex(pattern)) | ||||
|   if (ignore.case == TRUE) { | ||||
| @@ -80,6 +84,10 @@ like <- function(x, pattern, ignore.case = TRUE) { | ||||
|     x <- rep(x, length(pattern)) | ||||
|   } | ||||
|    | ||||
|   if (all(is.na(x))) { | ||||
|     return(rep(FALSE, length(x))) | ||||
|   } | ||||
|      | ||||
|   if (length(pattern) > 1) { | ||||
|     res <- vector(length = length(pattern)) | ||||
|     if (length(x) != length(pattern)) { | ||||
| @@ -137,18 +145,24 @@ like <- function(x, pattern, ignore.case = TRUE) { | ||||
| #' @rdname like | ||||
| #' @export | ||||
| "%like%" <- function(x, pattern) { | ||||
|   meet_criteria(x, allow_NA = TRUE) | ||||
|   meet_criteria(pattern, allow_class = "character") | ||||
|   like(x, pattern, ignore.case = TRUE) | ||||
| } | ||||
|  | ||||
| #' @rdname like | ||||
| #' @export | ||||
| "%like_case%" <- function(x, pattern) { | ||||
|   meet_criteria(x, allow_NA = TRUE) | ||||
|   meet_criteria(pattern, allow_class = "character") | ||||
|   like(x, pattern, ignore.case = FALSE) | ||||
| } | ||||
|  | ||||
| # don't export his one, it's just for convenience in eucast_rules() | ||||
| # match all Klebsiella and Raoultella, but not K. aerogenes: fullname %like_perl% "^(Klebsiella(?! aerogenes)|Raoultella)" | ||||
| "%like_perl%" <- function(x, pattern) { | ||||
|   meet_criteria(x) | ||||
|   meet_criteria(pattern, allow_class = "character") | ||||
|   grepl(x = tolower(x), | ||||
|         pattern = tolower(pattern), | ||||
|         perl = TRUE, | ||||
|   | ||||
							
								
								
									
										22
									
								
								R/mdro.R
									
									
									
									
									
								
							
							
						
						
									
										22
									
								
								R/mdro.R
									
									
									
									
									
								
							| @@ -93,6 +93,13 @@ mdro <- function(x, | ||||
|                  combine_SI = TRUE, | ||||
|                  verbose = FALSE, | ||||
|                  ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(guideline, allow_class = "character", has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(col_mo, allow_class = "character", has_length = 1, is_in = colnames(x), allow_NULL = TRUE) | ||||
|   meet_criteria(info, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(pct_required_classes, allow_class = "numeric", has_length = 1) | ||||
|   meet_criteria(combine_SI, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(verbose, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   check_dataset_integrity() | ||||
|    | ||||
| @@ -128,9 +135,8 @@ mdro <- function(x, | ||||
|     warning("Using `country` is deprecated, use `guideline` instead. Please see ?mdro.", call. = FALSE) | ||||
|     guideline <- list(...)$country | ||||
|   } | ||||
|   stop_ifnot(length(guideline) == 1, "`guideline` must be of length 1") | ||||
|  | ||||
|   guideline.bak <- guideline | ||||
|     guideline.bak <- guideline | ||||
|   guideline <- tolower(gsub("[^a-zA-Z0-9.]+", "", guideline)) | ||||
|   if (is.null(guideline)) { | ||||
|     # default to the paper by Magiorakos et al. (2012) | ||||
| @@ -631,7 +637,7 @@ mdro <- function(x, | ||||
|     } | ||||
|   } | ||||
|    | ||||
|   x[, col_mo] <- as.mo(x[, col_mo, drop = TRUE]) | ||||
|   x[, col_mo] <- as.mo(as.character(x[, col_mo, drop = TRUE])) | ||||
|   # join to microorganisms data set | ||||
|   x <- left_join_microorganisms(x, by = col_mo) | ||||
|   x$MDRO <- ifelse(!is.na(x$genus), 1, NA_integer_) | ||||
| @@ -1243,29 +1249,39 @@ mdro <- function(x, | ||||
| #' @rdname mdro | ||||
| #' @export | ||||
| brmo <- function(x, guideline = "BRMO", ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(guideline, allow_class = "character", has_length = 1) | ||||
|   mdro(x, guideline = "BRMO", ...) | ||||
| } | ||||
|  | ||||
| #' @rdname mdro | ||||
| #' @export | ||||
| mrgn <- function(x, guideline = "MRGN", ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(guideline, allow_class = "character", has_length = 1) | ||||
|   mdro(x = x, guideline = "MRGN", ...) | ||||
| } | ||||
|  | ||||
| #' @rdname mdro | ||||
| #' @export | ||||
| mdr_tb <- function(x, guideline = "TB", ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(guideline, allow_class = "character", has_length = 1) | ||||
|   mdro(x = x, guideline = "TB", ...) | ||||
| } | ||||
|  | ||||
| #' @rdname mdro | ||||
| #' @export | ||||
| mdr_cmi2012 <- function(x, guideline = "CMI2012", ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(guideline, allow_class = "character", has_length = 1) | ||||
|   mdro(x = x, guideline = "CMI2012", ...) | ||||
| } | ||||
|  | ||||
| #' @rdname mdro | ||||
| #' @export | ||||
| eucast_exceptional_phenotypes <- function(x, guideline = "EUCAST", ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(guideline, allow_class = "character", has_length = 1) | ||||
|   mdro(x = x, guideline = "EUCAST", ...) | ||||
| } | ||||
|   | ||||
							
								
								
									
										16
									
								
								R/mic.R
									
									
									
									
									
								
							
							
						
						
									
										16
									
								
								R/mic.R
									
									
									
									
									
								
							| @@ -56,6 +56,9 @@ | ||||
| #' plot(mic_data) | ||||
| #' barplot(mic_data) | ||||
| as.mic <- function(x, na.rm = FALSE) { | ||||
|   meet_criteria(x, allow_class = c("mic", "character", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(na.rm, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   if (is.mic(x)) { | ||||
|     x | ||||
|   } else { | ||||
| @@ -134,6 +137,9 @@ as.mic <- function(x, na.rm = FALSE) { | ||||
| } | ||||
|  | ||||
| all_valid_mics <- function(x) { | ||||
|   if (!inherits(x, c("mic", "character", "factor", "numeric", "integer"))) { | ||||
|     return(FALSE) | ||||
|   } | ||||
|   x_mic <- tryCatch(suppressWarnings(as.mic(x[!is.na(x)])), | ||||
|                     error = function(e) NA) | ||||
|   !any(is.na(x_mic)) & !all(is.na(x)) | ||||
| @@ -221,6 +227,11 @@ plot.mic <- function(x, | ||||
|                      xlab = "MIC value", | ||||
|                      axes = FALSE, | ||||
|                      ...) { | ||||
|   meet_criteria(main, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(ylab, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(xlab, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(axes, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   barplot(table(droplevels.factor(x)), | ||||
|           ylab = ylab, | ||||
|           xlab = xlab, | ||||
| @@ -240,6 +251,11 @@ barplot.mic <- function(height, | ||||
|                         xlab = "MIC value", | ||||
|                         axes = FALSE, | ||||
|                         ...) { | ||||
|   meet_criteria(main, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(ylab, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(xlab, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(axes, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   barplot(table(droplevels.factor(height)), | ||||
|           ylab = ylab, | ||||
|           xlab = xlab, | ||||
|   | ||||
							
								
								
									
										25
									
								
								R/mo.R
									
									
									
									
									
								
							
							
						
						
									
										25
									
								
								R/mo.R
									
									
									
									
									
								
							| @@ -158,6 +158,13 @@ as.mo <- function(x, | ||||
|                   ignore_pattern = getOption("AMR_ignore_pattern"), | ||||
|                   language = get_locale(), | ||||
|                   ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(Becker, allow_class = c("logical", "character"), has_length = 1) | ||||
|   meet_criteria(Lancefield, allow_class = c("logical", "character"), has_length = 1) | ||||
|   meet_criteria(allow_uncertain, allow_class = c("logical", "numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(reference_df, allow_class = "data.frame", allow_NULL = TRUE) | ||||
|   meet_criteria(ignore_pattern, allow_class = "character", has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   check_dataset_integrity() | ||||
|    | ||||
| @@ -268,6 +275,20 @@ exec_as.mo <- function(x, | ||||
|                        actual_uncertainty = 1, | ||||
|                        actual_input = NULL, | ||||
|                        language = get_locale()) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(Becker, allow_class = c("logical", "character"), has_length = 1) | ||||
|   meet_criteria(Lancefield, allow_class = c("logical", "character"), has_length = 1) | ||||
|   meet_criteria(allow_uncertain, allow_class = c("logical", "numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(reference_df, allow_class = "data.frame", allow_NULL = TRUE) | ||||
|   meet_criteria(property, allow_class = "character", has_length = 1, is_in = colnames(microorganisms)) | ||||
|   meet_criteria(initial_search, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(dyslexia_mode, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(debug, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(ignore_pattern, allow_class = "character", has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(reference_data_to_use, allow_class = "data.frame") | ||||
|   meet_criteria(actual_uncertainty, allow_class = "numeric", has_length = 1) | ||||
|   meet_criteria(actual_input, allow_class = "character", allow_NULL = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   check_dataset_integrity() | ||||
|    | ||||
| @@ -1607,8 +1628,8 @@ get_skimmers.mo <- function(column) { | ||||
|   sfl( | ||||
|     skim_type = "mo", | ||||
|     unique_total = ~pm_n_distinct(., na.rm = TRUE), | ||||
|     gram_negative = ~sum(mo_gramstain(stats::na.omit(.), language = NULL) == "Gram-negative", na.rm = TRUE), | ||||
|     gram_positive = ~sum(mo_gramstain(stats::na.omit(.), language = NULL) == "Gram-positive", na.rm = TRUE), | ||||
|     gram_negative = ~sum(is_gram_negative(stats::na.omit(.))), | ||||
|     gram_positive = ~sum(is_gram_positive(stats::na.omit(.))), | ||||
|     top_genus = ~names(sort(-table(mo_genus(stats::na.omit(.), language = NULL))))[1L], | ||||
|     top_species = ~names(sort(-table(mo_name(stats::na.omit(.), language = NULL))))[1L] | ||||
|   ) | ||||
|   | ||||
| @@ -53,6 +53,9 @@ | ||||
| #' mo_matching_score(x = "E. coli", | ||||
| #'                   n = c("Escherichia coli", "Entamoeba coli")) | ||||
| mo_matching_score <- function(x, n) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list")) | ||||
|   meet_criteria(n, allow_class = "character") | ||||
|    | ||||
|   x <- parse_and_convert(x) | ||||
|   # no dots and other non-whitespace characters | ||||
|   x <- gsub("[^a-zA-Z0-9 \\(\\)]+", "", x) | ||||
|   | ||||
| @@ -27,7 +27,7 @@ | ||||
| #' | ||||
| #' Use these functions to return a specific property of a microorganism based on the latest accepted taxonomy. All input values will be evaluated internally with [as.mo()], which makes it possible to use microbial abbreviations, codes and names as input. Please see *Examples*. | ||||
| #' @inheritSection lifecycle Stable lifecycle | ||||
| #' @param x any (vector of) text that can be coerced to a valid microorganism code with [as.mo()] | ||||
| #' @param x any character (vector) that can be coerced to a valid microorganism code with [as.mo()] | ||||
| #' @param property one of the column names of the [microorganisms] data set or `"shortname"` | ||||
| #' @param language language of the returned text, defaults to system language (see [get_locale()]) and can be overwritten by setting the option `AMR_locale`, e.g. `options(AMR_locale = "de")`, see [translate]. Use `language = NULL` or `language = ""` to prevent translation. | ||||
| #' @param ... other parameters passed on to [as.mo()], such as 'allow_uncertain' and 'ignore_pattern' | ||||
| @@ -41,7 +41,7 @@ | ||||
| #'  | ||||
| #' Since the top-level of the taxonomy is sometimes referred to as 'kingdom' and sometimes as 'domain', the functions [mo_kingdom()] and [mo_domain()] return the exact same results. | ||||
| #' | ||||
| #' The Gram stain - [mo_gramstain()] - will be determined based on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002, [PMID 11837318](https://pubmed.ncbi.nlm.nih.gov/11837318)), who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value `NA`. | ||||
| #' The Gram stain - [mo_gramstain()] - will be determined based on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002, [PMID 11837318](https://pubmed.ncbi.nlm.nih.gov/11837318)), who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value `NA`. Functions [is_gram_negative()] and [is_gram_positive()] always return `TRUE` or `FALSE`, even for species outside the kingdom of Bacteria. | ||||
| #' | ||||
| #' All output will be [translate]d where possible. | ||||
| #' | ||||
| @@ -146,6 +146,9 @@ | ||||
| #' mo_info("E. coli") | ||||
| #' } | ||||
| mo_name <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   translate_AMR(mo_validate(x = x, property = "fullname", language = language, ...), language = language, only_unknown = FALSE) | ||||
| } | ||||
|  | ||||
| @@ -156,6 +159,9 @@ mo_fullname <- mo_name | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_shortname <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   x.mo <- as.mo(x, language = language, ...) | ||||
|    | ||||
|   metadata <- get_mo_failures_uncertainties_renamed() | ||||
| @@ -186,48 +192,72 @@ mo_shortname <- function(x, language = get_locale(), ...) { | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_subspecies <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   translate_AMR(mo_validate(x = x, property = "subspecies", language = language, ...), language = language, only_unknown = TRUE) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_species <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   translate_AMR(mo_validate(x = x, property = "species", language = language, ...), language = language, only_unknown = TRUE) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_genus <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   translate_AMR(mo_validate(x = x, property = "genus", language = language, ...), language = language, only_unknown = TRUE) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_family <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   translate_AMR(mo_validate(x = x, property = "family", language = language, ...), language = language, only_unknown = TRUE) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_order <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   translate_AMR(mo_validate(x = x, property = "order", language = language, ...), language = language, only_unknown = TRUE) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_class <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   translate_AMR(mo_validate(x = x, property = "class", language = language, ...), language = language, only_unknown = TRUE) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_phylum <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   translate_AMR(mo_validate(x = x, property = "phylum", language = language, ...), language = language, only_unknown = TRUE) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_kingdom <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   translate_AMR(mo_validate(x = x, property = "kingdom", language = language, ...), language = language, only_unknown = TRUE) | ||||
| } | ||||
|  | ||||
| @@ -238,12 +268,18 @@ mo_domain <- mo_kingdom | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_type <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   translate_AMR(mo_validate(x = x, property = "kingdom", language = language, ...), language = language, only_unknown = FALSE) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_gramstain <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   x.mo <- as.mo(x, language = language, ...) | ||||
|   metadata <- get_mo_failures_uncertainties_renamed() | ||||
|    | ||||
| @@ -272,21 +308,46 @@ mo_gramstain <- function(x, language = get_locale(), ...) { | ||||
|   translate_AMR(x, language = language, only_unknown = FALSE) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| is_gram_negative <- function(x, ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   grams <- mo_gramstain(x, language = NULL, ...) | ||||
|   "Gram-negative" == grams & !is.na(grams) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| is_gram_positive <- function(x, ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   grams <- mo_gramstain(x, language = NULL, ...) | ||||
|   "Gram-positive" == grams & !is.na(grams) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_snomed <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   mo_validate(x = x, property = "snomed", language = language, ...) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_ref <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   mo_validate(x = x, property = "ref", language = language, ...) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_authors <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   x <- mo_validate(x = x, property = "ref", language = language, ...) | ||||
|   # remove last 4 digits and presumably the comma and space that preceed them | ||||
|   x[!is.na(x)] <- gsub(",? ?[0-9]{4}", "", x[!is.na(x)]) | ||||
| @@ -296,6 +357,9 @@ mo_authors <- function(x, language = get_locale(), ...) { | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_year <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   x <- mo_validate(x = x, property = "ref", language = language, ...) | ||||
|   # get last 4 digits | ||||
|   x[!is.na(x)] <- gsub(".*([0-9]{4})$", "\\1", x[!is.na(x)]) | ||||
| @@ -305,12 +369,18 @@ mo_year <- function(x, language = get_locale(), ...) { | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_rank <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   mo_validate(x = x, property = "rank", language = language, ...) | ||||
| } | ||||
|  | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_taxonomy <- function(x, language = get_locale(),  ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   x <- as.mo(x, language = language, ...) | ||||
|   metadata <- get_mo_failures_uncertainties_renamed() | ||||
|    | ||||
| @@ -330,6 +400,9 @@ mo_taxonomy <- function(x, language = get_locale(),  ...) { | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_synonyms <- function(x, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   x <- as.mo(x, language = language, ...) | ||||
|   metadata <- get_mo_failures_uncertainties_renamed() | ||||
|    | ||||
| @@ -356,6 +429,9 @@ mo_synonyms <- function(x, language = get_locale(), ...) { | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_info <- function(x, language = get_locale(),  ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   x <- as.mo(x, language = language, ...) | ||||
|   metadata <- get_mo_failures_uncertainties_renamed() | ||||
|    | ||||
| @@ -379,6 +455,10 @@ mo_info <- function(x, language = get_locale(),  ...) { | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_url <- function(x, open = FALSE, language = get_locale(), ...) { | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(open, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|    | ||||
|   mo <- as.mo(x = x, language = language, ... = ...) | ||||
|   mo_names <- mo_name(mo) | ||||
|   metadata <- get_mo_failures_uncertainties_renamed() | ||||
| @@ -408,15 +488,14 @@ mo_url <- function(x, open = FALSE, language = get_locale(), ...) { | ||||
| #' @rdname mo_property | ||||
| #' @export | ||||
| mo_property <- function(x, property = "fullname", language = get_locale(), ...) { | ||||
|   stop_ifnot(length(property) == 1L, "'property' must be of length 1") | ||||
|   stop_ifnot(property %in% colnames(microorganisms), | ||||
|              "invalid property: '", property, "' - use a column name of the `microorganisms` data set") | ||||
|   meet_criteria(x, allow_class = c("character", "data.frame", "list", "numeric", "integer"), allow_NA = TRUE) | ||||
|   meet_criteria(property, allow_class = "character", has_length = 1, is_in = colnames(microorganisms)) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE) | ||||
|  | ||||
|   translate_AMR(mo_validate(x = x, property = property, language = language, ...), language = language, only_unknown = TRUE) | ||||
| } | ||||
|  | ||||
| mo_validate <- function(x, property, language, ...) { | ||||
|    | ||||
|   check_dataset_integrity() | ||||
|    | ||||
|   if (tryCatch(all(x[!is.na(x)] %in% MO_lookup$mo) & length(list(...)) == 0, error = function(e) FALSE)) { | ||||
|   | ||||
| @@ -115,11 +115,11 @@ | ||||
| #' @export | ||||
| #' @inheritSection AMR Read more on our website! | ||||
| set_mo_source <- function(path) { | ||||
|   meet_criteria(path, allow_class = "character", has_length = 1) | ||||
|    | ||||
|   file_location <- path.expand("~/mo_source.rds") | ||||
|    | ||||
|   stop_ifnot(interactive(), "This function can only be used in interactive mode, since it must ask for the user's permission to write a file to their home folder.") | ||||
|   stop_ifnot(length(path) == 1, "`path` must be of length 1") | ||||
|  | ||||
|   if (is.null(path) || path %in% c(FALSE, "")) { | ||||
|     options(mo_source = NULL) | ||||
| @@ -131,8 +131,7 @@ set_mo_source <- function(path) { | ||||
|     return(invisible()) | ||||
|   } | ||||
|    | ||||
|   stop_ifnot(file.exists(path), | ||||
|              "file not found: ", path) | ||||
|   stop_ifnot(file.exists(path), "file not found: ", path) | ||||
|    | ||||
|   if (path %like% "[.]rds$") { | ||||
|     df <- readRDS(path) | ||||
| @@ -237,7 +236,6 @@ get_mo_source <- function() { | ||||
| } | ||||
|  | ||||
| mo_source_isvalid <- function(x, refer_to_name = "`reference_df`", stop_on_error = TRUE) { | ||||
|    | ||||
|   check_dataset_integrity() | ||||
|    | ||||
|   if (deparse(substitute(x)) == "get_mo_source()") { | ||||
|   | ||||
							
								
								
									
										48
									
								
								R/p_symbol.R
									
									
									
									
									
								
							
							
						
						
									
										48
									
								
								R/p_symbol.R
									
									
									
									
									
								
							| @@ -1,48 +0,0 @@ | ||||
| # ==================================================================== # | ||||
| # TITLE                                                                # | ||||
| # Antimicrobial Resistance (AMR) Analysis for R                        # | ||||
| #                                                                      # | ||||
| # SOURCE                                                               # | ||||
| # https://github.com/msberends/AMR                                     # | ||||
| #                                                                      # | ||||
| # LICENCE                                                              # | ||||
| # (c) 2018-2020 Berends MS, Luz CF et al.                              # | ||||
| # Developed at the University of Groningen, the Netherlands, in        # | ||||
| # collaboration with non-profit organisations Certe Medical            # | ||||
| # Diagnostics & Advice, and University Medical Center Groningen.       #  | ||||
| #                                                                      # | ||||
| # This R package is free software; you can freely use and distribute   # | ||||
| # it for both personal and commercial purposes under the terms of the  # | ||||
| # GNU General Public License version 2.0 (GNU GPL-2), as published by  # | ||||
| # the Free Software Foundation.                                        # | ||||
| # We created this package for both routine data analysis and academic  # | ||||
| # research and it was publicly released in the hope that it will be    # | ||||
| # useful, but it comes WITHOUT ANY WARRANTY OR LIABILITY.              # | ||||
| #                                                                      # | ||||
| # Visit our website for the full manual and a complete tutorial about  # | ||||
| # how to conduct AMR analysis: https://msberends.github.io/AMR/        # | ||||
| # ==================================================================== # | ||||
|  | ||||
| #' Symbol of a p-value | ||||
| #' | ||||
| #' Return the symbol related to the p-value: 0 '`***`' 0.001 '`**`' 0.01 '`*`' 0.05 '`.`' 0.1 ' ' 1. Values above `p = 1` will return `NA`. | ||||
| #' @inheritSection lifecycle Questioning lifecycle | ||||
| #' @param p p value | ||||
| #' @param emptychar text to show when `p > 0.1` | ||||
| #' @details **NOTE**: this function will be moved to the `cleaner` package when a new version is being published on CRAN. | ||||
| #' @return Text | ||||
| #' @inheritSection AMR Read more on our website! | ||||
| #' @export | ||||
| p_symbol <- function(p, emptychar = " ") { | ||||
|    | ||||
|   p <- as.double(p) | ||||
|   s <- rep(NA_character_, length(p)) | ||||
|    | ||||
|   s[p <= 1] <- emptychar | ||||
|   s[p <= 0.100] <- "." | ||||
|   s[p <= 0.050] <- "*" | ||||
|   s[p <= 0.010] <- "**" | ||||
|   s[p <= 0.001] <- "***" | ||||
|    | ||||
|   s | ||||
| } | ||||
							
								
								
									
										9
									
								
								R/pca.R
									
									
									
									
									
								
							
							
						
						
									
										9
									
								
								R/pca.R
									
									
									
									
									
								
							| @@ -66,9 +66,12 @@ pca <- function(x, | ||||
|                 scale. = TRUE, | ||||
|                 tol = NULL, | ||||
|                 rank. = NULL) { | ||||
|    | ||||
|   stop_ifnot(is.data.frame(x), "`x` must be a data.frame") | ||||
|   stop_if(any(dim(x) == 0), "`x` must contain rows and columns") | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(retx, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(center, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(scale., allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(tol, allow_class = "numeric", has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(rank., allow_class = "numeric", has_length = 1, allow_NULL = TRUE) | ||||
|    | ||||
|   # unset data.table, tibble, etc. | ||||
|   # also removes groups made by dplyr::group_by | ||||
|   | ||||
| @@ -266,7 +266,6 @@ proportion_df <- function(data, | ||||
|                           as_percent = FALSE, | ||||
|                           combine_SI = TRUE, | ||||
|                           combine_IR = FALSE) { | ||||
|    | ||||
|   rsi_calc_df(type = "proportion", | ||||
|               data = data, | ||||
|               translate_ab = translate_ab, | ||||
|   | ||||
| @@ -126,12 +126,19 @@ resistance_predict <- function(x, | ||||
|                                preserve_measurements = TRUE, | ||||
|                                info = interactive(), | ||||
|                                ...) { | ||||
|   meet_criteria(x, allow_class = "data.frame") | ||||
|   meet_criteria(col_ab, allow_class = "character", has_length = 1, is_in = colnames(x)) | ||||
|   meet_criteria(col_date, allow_class = "character", has_length = 1, is_in = colnames(x), allow_NULL = TRUE) | ||||
|   meet_criteria(year_min, allow_class = c("numeric", "integer"), has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(year_max, allow_class = c("numeric", "integer"), has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(year_every, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(model, allow_class = c("character", "function"), has_length = 1, allow_NULL = TRUE) | ||||
|   meet_criteria(I_as_S, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(preserve_measurements, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(info, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   stop_ifnot(is.data.frame(x), "`x` must be a data.frame") | ||||
|   stop_if(any(dim(x) == 0), "`x` must contain rows and columns") | ||||
|   stop_if(is.null(model), 'choose a regression model with the `model` parameter, e.g. resistance_predict(..., model = "binomial")') | ||||
|   stop_ifnot(col_ab %in% colnames(x), | ||||
|              "column `", col_ab, "` not found") | ||||
|  | ||||
|   dots <- unlist(list(...)) | ||||
|   if (length(dots) != 0) { | ||||
| @@ -300,6 +307,7 @@ rsi_predict <- resistance_predict | ||||
| #' @rdname resistance_predict | ||||
| plot.resistance_predict <- function(x, main = paste("Resistance Prediction of", x_name), ...) { | ||||
|   x_name <- paste0(ab_name(attributes(x)$ab), " (", attributes(x)$ab, ")") | ||||
|   meet_criteria(main, allow_class = "character", has_length = 1) | ||||
|    | ||||
|   if (attributes(x)$I_as_S == TRUE) { | ||||
|     ylab <- "%R" | ||||
| @@ -342,11 +350,13 @@ ggplot_rsi_predict <- function(x, | ||||
|                                main = paste("Resistance Prediction of", x_name), | ||||
|                                ribbon = TRUE, | ||||
|                                ...) { | ||||
|   x_name <- paste0(ab_name(attributes(x)$ab), " (", attributes(x)$ab, ")") | ||||
|   meet_criteria(main, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(ribbon, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   stop_ifnot_installed("ggplot2") | ||||
|   stop_ifnot(inherits(x, "resistance_predict"), "`x` must be a resistance prediction model created with resistance_predict()") | ||||
|    | ||||
|   x_name <- paste0(ab_name(attributes(x)$ab), " (", attributes(x)$ab, ")") | ||||
|    | ||||
|   if (attributes(x)$I_as_S == TRUE) { | ||||
|     ylab <- "%R" | ||||
|   | ||||
							
								
								
									
										50
									
								
								R/rsi.R
									
									
									
									
									
								
							
							
						
						
									
										50
									
								
								R/rsi.R
									
									
									
									
									
								
							| @@ -31,7 +31,7 @@ | ||||
| #' @param x vector of values (for class [`mic`]: an MIC value in mg/L, for class [`disk`]: a disk diffusion radius in millimetres) | ||||
| #' @param mo any (vector of) text that can be coerced to a valid microorganism code with [as.mo()], will be determined automatically if the `dplyr` package is installed | ||||
| #' @param ab any (vector of) text that can be coerced to a valid antimicrobial code with [as.ab()] | ||||
| #' @param uti (Urinary Tract Infection) A vector with [logical]s (`TRUE` or `FALSE`) to specify whether a UTI specific interpretation from the guideline should be chosen. For using [as.rsi()] on a [data.frame], this can also be a column containing [logical]s or when left blank, the data set will be search for a 'specimen' and rows containing 'urin' in that column will be regarded isolates from a UTI. See *Examples*. | ||||
| #' @param uti (Urinary Tract Infection) A vector with [logical]s (`TRUE` or `FALSE`) to specify whether a UTI specific interpretation from the guideline should be chosen. For using [as.rsi()] on a [data.frame], this can also be a column containing [logical]s or when left blank, the data set will be searched for a 'specimen' and rows containing 'urin' (such as 'urine', 'urina') in that column will be regarded isolates from a UTI. See *Examples*. | ||||
| #' @inheritParams first_isolate | ||||
| #' @param guideline defaults to the latest included EUCAST guideline, see Details for all options | ||||
| #' @param conserve_capped_values a logical to indicate that MIC values starting with `">"` (but not `">="`) must always return "R" , and that MIC values starting with `"<"` (but not `"<="`) must always return "S" | ||||
| @@ -193,6 +193,8 @@ is.rsi <- function(x) { | ||||
| #' @rdname as.rsi | ||||
| #' @export | ||||
| is.rsi.eligible <- function(x, threshold = 0.05) { | ||||
|   meet_criteria(threshold, allow_class = "numeric", has_length = 1) | ||||
|    | ||||
|   stop_if(NCOL(x) > 1, "`x` must be a one-dimensional vector.") | ||||
|   if (any(c("logical", | ||||
|             "numeric", | ||||
| @@ -293,6 +295,13 @@ as.rsi.mic <- function(x, | ||||
|                        conserve_capped_values = FALSE, | ||||
|                        add_intrinsic_resistance = FALSE, | ||||
|                        ...) { | ||||
|   meet_criteria(x) | ||||
|   meet_criteria(mo, allow_class = c("mo", "character"), allow_NULL = TRUE) | ||||
|   meet_criteria(ab, allow_class = c("ab", "character")) | ||||
|   meet_criteria(guideline, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(uti, allow_class = "logical", has_length = c(1, length(x))) | ||||
|   meet_criteria(conserve_capped_values, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(add_intrinsic_resistance, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   # for dplyr's across() | ||||
|   cur_column_dplyr <- import_fn("cur_column", "dplyr", error_on_fail = FALSE) | ||||
| @@ -323,6 +332,9 @@ as.rsi.mic <- function(x, | ||||
|           "`data %>% mutate_at(vars(...), as.rsi, mo = .$x)`, where x is your column with microorganisms.\n\n", | ||||
|           "To tranform all MIC values in a data set, use `data %>% as.rsi()` or data %>% mutate_if(is.mic, as.rsi).", call = FALSE) | ||||
|   } | ||||
|   if (length(ab) == 1 && ab %like% "as.mic") { | ||||
|     stop_('No unambiguous name was supplied about the antibiotic (parameter "ab"). See ?as.rsi.', call = FALSE) | ||||
|   } | ||||
|    | ||||
|   ab_coerced <- suppressWarnings(as.ab(ab)) | ||||
|   mo_coerced <- suppressWarnings(as.mo(mo)) | ||||
| @@ -364,6 +376,12 @@ as.rsi.disk <- function(x, | ||||
|                         uti = FALSE, | ||||
|                         add_intrinsic_resistance = FALSE, | ||||
|                         ...) { | ||||
|   meet_criteria(x) | ||||
|   meet_criteria(mo, allow_class = c("mo", "character"), allow_NULL = TRUE) | ||||
|   meet_criteria(ab, allow_class = c("ab", "character")) | ||||
|   meet_criteria(guideline, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(uti, allow_class = "logical", has_length = c(1, length(x))) | ||||
|   meet_criteria(add_intrinsic_resistance, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   # for dplyr's across() | ||||
|   cur_column_dplyr <- import_fn("cur_column", "dplyr", error_on_fail = FALSE) | ||||
| @@ -394,6 +412,9 @@ as.rsi.disk <- function(x, | ||||
|           "`data %>% mutate_at(vars(...), as.rsi, mo = .$x)`, where x is your column with microorganisms.\n\n", | ||||
|           "To tranform all disk diffusion zones in a data set, use `data %>% as.rsi()` or data %>% mutate_if(is.disk, as.rsi).", call = FALSE) | ||||
|   } | ||||
|   if (length(ab) == 1 && ab %like% "as.disk") { | ||||
|     stop_('No unambiguous name was supplied about the antibiotic (parameter "ab"). See ?as.rsi.', call = FALSE) | ||||
|   } | ||||
|    | ||||
|   ab_coerced <- suppressWarnings(as.ab(ab)) | ||||
|   mo_coerced <- suppressWarnings(as.mo(mo)) | ||||
| @@ -433,6 +454,12 @@ as.rsi.data.frame <- function(x, | ||||
|                               uti = NULL, | ||||
|                               conserve_capped_values = FALSE, | ||||
|                               add_intrinsic_resistance = FALSE) { | ||||
|   meet_criteria(x, allow_class = "data.frame") # will also check for dimensions > 0 | ||||
|   meet_criteria(col_mo, allow_class = "character", is_in = colnames(x), allow_NULL = TRUE) | ||||
|   meet_criteria(guideline, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(uti, allow_class = "logical", has_length = c(1, nrow(x)), allow_NULL = TRUE) | ||||
|   meet_criteria(conserve_capped_values, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(add_intrinsic_resistance, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   # -- UTIs | ||||
|   col_uti <- uti | ||||
| @@ -731,6 +758,14 @@ type_sum.rsi <- function(x, ...) { | ||||
| freq.rsi <- function(x, ...) { | ||||
|   x_name <- deparse(substitute(x)) | ||||
|   x_name <- gsub(".*[$]", "", x_name) | ||||
|   if (x_name %in% c("x", ".")) { | ||||
|     # try again going through system calls | ||||
|     x_name <- na.omit(sapply(sys.calls(),  | ||||
|                              function(call) { | ||||
|                                call_txt <- as.character(call) | ||||
|                                ifelse(call_txt[1] %like% "freq$", call_txt[length(call_txt)], character(0)) | ||||
|                              }))[1L] | ||||
|   } | ||||
|   ab <- suppressMessages(suppressWarnings(as.ab(x_name))) | ||||
|   freq.default <- import_fn("freq.default", "cleaner", error_on_fail = FALSE) | ||||
|   digits <- list(...)$digits | ||||
| @@ -850,6 +885,13 @@ plot.rsi <- function(x, | ||||
|                      main = paste("Resistance Overview of", deparse(substitute(x))), | ||||
|                      axes = FALSE, | ||||
|                      ...) { | ||||
|   meet_criteria(lwd, allow_class = c("numeric", "integer"), has_length = 1) | ||||
|   meet_criteria(ylim, allow_class = c("numeric", "integer"), allow_NULL = TRUE) | ||||
|   meet_criteria(ylab, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(xlab, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(main, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(axes, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   data <- as.data.frame(table(x), stringsAsFactors = FALSE) | ||||
|   colnames(data) <- c("x", "n") | ||||
|   data$s <- round((data$n / sum(data$n)) * 100, 1) | ||||
| @@ -901,6 +943,12 @@ barplot.rsi <- function(height, | ||||
|                         beside = TRUE, | ||||
|                         axes = beside, | ||||
|                         ...) { | ||||
|   meet_criteria(col, allow_class = "character", has_length = 3) | ||||
|   meet_criteria(xlab, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(main, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(ylab, allow_class = "character", has_length = 1) | ||||
|   meet_criteria(beside, allow_class = "logical", has_length = 1) | ||||
|   meet_criteria(axes, allow_class = "logical", has_length = 1) | ||||
|    | ||||
|   if (axes == TRUE) { | ||||
|     par(mar =  c(5, 4, 4, 2) + 0.1) | ||||
|   | ||||
							
								
								
									
										23
									
								
								R/rsi_calc.R
									
									
									
									
									
								
							
							
						
						
									
										23
									
								
								R/rsi_calc.R
									
									
									
									
									
								
							| @@ -36,10 +36,11 @@ rsi_calc <- function(..., | ||||
|                      as_percent = FALSE, | ||||
|                      only_all_tested = FALSE, | ||||
|                      only_count = FALSE) { | ||||
|    | ||||
|   stop_ifnot(is.numeric(minimum), "`minimum` must be numeric", call = -2) | ||||
|   stop_ifnot(is.logical(as_percent), "`as_percent` must be logical", call = -2) | ||||
|   stop_ifnot(is.logical(only_all_tested), "`only_all_tested` must be logical", call = -2) | ||||
|   meet_criteria(ab_result, allow_class = c("character", "numeric", "integer"), has_length = c(1, 2, 3), .call_depth = 1) | ||||
|   meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1, .call_depth = 1) | ||||
|   meet_criteria(as_percent, allow_class = "logical", has_length = 1, .call_depth = 1) | ||||
|   meet_criteria(only_all_tested, allow_class = "logical", has_length = 1, .call_depth = 1) | ||||
|   meet_criteria(only_count, allow_class = "logical", has_length = 1, .call_depth = 1) | ||||
|    | ||||
|   data_vars <- dots2vars(...) | ||||
|    | ||||
| @@ -177,17 +178,21 @@ rsi_calc_df <- function(type, # "proportion", "count" or "both" | ||||
|                         combine_SI = TRUE, | ||||
|                         combine_IR = FALSE, | ||||
|                         combine_SI_missing = FALSE) { | ||||
|   meet_criteria(type, is_in = c("proportion", "count", "both"), has_length = 1, .call_depth = 1) | ||||
|   meet_criteria(data, allow_class = "data.frame", contains_column_class = "rsi", .call_depth = 1) | ||||
|   meet_criteria(translate_ab, allow_class = c("character", "logical"), has_length = 1, allow_NA = TRUE, .call_depth = 1) | ||||
|   meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE, .call_depth = 1) | ||||
|   meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1, .call_depth = 1) | ||||
|   meet_criteria(as_percent, allow_class = "logical", has_length = 1, .call_depth = 1) | ||||
|   meet_criteria(combine_SI, allow_class = "logical", has_length = 1, .call_depth = 1) | ||||
|   meet_criteria(combine_SI_missing, allow_class = "logical", has_length = 1, .call_depth = 1) | ||||
|    | ||||
|   check_dataset_integrity() | ||||
|   stop_ifnot(is.data.frame(data), "`data` must be a data.frame", call = -2) | ||||
|   stop_if(any(dim(data) == 0), "`data` must contain rows and columns", call = -2) | ||||
|   stop_ifnot(any(sapply(data, is.rsi), na.rm = TRUE), "no columns with class <rsi> found. See ?as.rsi.", call = -2) | ||||
|    | ||||
|   if (isTRUE(combine_IR) & isTRUE(combine_SI_missing)) { | ||||
|     combine_SI <- FALSE | ||||
|   } | ||||
|   stop_if(isTRUE(combine_SI) & isTRUE(combine_IR), "either `combine_SI` or `combine_IR` can be TRUE, not both", call = -2) | ||||
|   stop_ifnot(is.numeric(minimum), "`minimum` must be numeric", call = -2) | ||||
|   stop_ifnot(is.logical(as_percent), "`as_percent` must be logical", call = -2) | ||||
|    | ||||
|   translate_ab <- get_translate_ab(translate_ab) | ||||
|    | ||||
|   | ||||
| @@ -32,7 +32,6 @@ rsi_df <- function(data, | ||||
|                    as_percent = FALSE, | ||||
|                    combine_SI = TRUE, | ||||
|                    combine_IR = FALSE) { | ||||
|    | ||||
|   rsi_calc_df(type = "both", | ||||
|               data = data, | ||||
|               translate_ab = translate_ab, | ||||
|   | ||||
| @@ -36,6 +36,7 @@ | ||||
| #' @inheritSection AMR Read more on our website! | ||||
| #' @export | ||||
| skewness <- function(x, na.rm = FALSE) { | ||||
|   meet_criteria(na.rm, allow_class = "logical", has_length = 1) | ||||
|   UseMethod("skewness") | ||||
| } | ||||
|  | ||||
| @@ -43,6 +44,7 @@ skewness <- function(x, na.rm = FALSE) { | ||||
| #' @rdname skewness | ||||
| #' @export | ||||
| skewness.default <- function(x, na.rm = FALSE) { | ||||
|   meet_criteria(na.rm, allow_class = "logical", has_length = 1) | ||||
|   x <- as.vector(x) | ||||
|   if (na.rm == TRUE) { | ||||
|     x <- x[!is.na(x)] | ||||
| @@ -55,6 +57,7 @@ skewness.default <- function(x, na.rm = FALSE) { | ||||
| #' @rdname skewness | ||||
| #' @export | ||||
| skewness.matrix <- function(x, na.rm = FALSE) { | ||||
|   meet_criteria(na.rm, allow_class = "logical", has_length = 1) | ||||
|   apply(x, 2, skewness.default, na.rm = na.rm) | ||||
| } | ||||
|  | ||||
| @@ -62,5 +65,6 @@ skewness.matrix <- function(x, na.rm = FALSE) { | ||||
| #' @rdname skewness | ||||
| #' @export | ||||
| skewness.data.frame <- function(x, na.rm = FALSE) { | ||||
|   meet_criteria(na.rm, allow_class = "logical", has_length = 1) | ||||
|   sapply(x, skewness.default, na.rm = na.rm) | ||||
| } | ||||
|   | ||||
| @@ -73,7 +73,7 @@ | ||||
| #' mo_name("CoNS", language = "pt") | ||||
| #' #> "Staphylococcus coagulase negativo (CoNS)" | ||||
| get_locale <- function() { | ||||
|   # AMR versions prior to 1.3.0 used the environmental variable: | ||||
|   # AMR versions 1.3.0 and prior used the environmental variable: | ||||
|   if (!identical("", Sys.getenv("AMR_locale"))) { | ||||
|     options(AMR_locale = Sys.getenv("AMR_locale")) | ||||
|   } | ||||
| @@ -101,20 +101,20 @@ get_locale <- function() { | ||||
|  | ||||
| coerce_language_setting <- function(lang) { | ||||
|   # grepl() with ignore.case = FALSE is faster than %like% | ||||
|   if (grepl("^(English|en_|EN_)", lang, ignore.case = FALSE)) { | ||||
|   if (grepl("^(English|en_|EN_)", lang, ignore.case = FALSE, perl = TRUE)) { | ||||
|     # as first option to optimise speed | ||||
|     "en" | ||||
|   } else if (grepl("^(German|Deutsch|de_|DE_)", lang, ignore.case = FALSE)) { | ||||
|   } else if (grepl("^(German|Deutsch|de_|DE_)", lang, ignore.case = FALSE, perl = TRUE)) { | ||||
|     "de" | ||||
|   } else if (grepl("^(Dutch|Nederlands|nl_|NL_)", lang, ignore.case = FALSE)) { | ||||
|   } else if (grepl("^(Dutch|Nederlands|nl_|NL_)", lang, ignore.case = FALSE, perl = TRUE)) { | ||||
|     "nl" | ||||
|   } else if (grepl("^(Spanish|Espa.+ol|es_|ES_)", lang, ignore.case = FALSE)) { | ||||
|   } else if (grepl("^(Spanish|Espa.+ol|es_|ES_)", lang, ignore.case = FALSE, perl = TRUE)) { | ||||
|     "es" | ||||
|   } else if (grepl("^(Italian|Italiano|it_|IT_)", lang, ignore.case = FALSE)) { | ||||
|   } else if (grepl("^(Italian|Italiano|it_|IT_)", lang, ignore.case = FALSE, perl = TRUE)) { | ||||
|     "it" | ||||
|   } else if (grepl("^(French|Fran.+ais|fr_|FR_)", lang, ignore.case = FALSE)) { | ||||
|   } else if (grepl("^(French|Fran.+ais|fr_|FR_)", lang, ignore.case = FALSE, perl = TRUE)) { | ||||
|     "fr" | ||||
|   } else if (grepl("^(Portuguese|Portugu.+s|pt_|PT_)", lang, ignore.case = FALSE)) { | ||||
|   } else if (grepl("^(Portuguese|Portugu.+s|pt_|PT_)", lang, ignore.case = FALSE, perl = TRUE)) { | ||||
|     "pt" | ||||
|   } else { | ||||
|     # other language -> set to English | ||||
|   | ||||
| @@ -81,7 +81,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <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.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
|   | ||||
| @@ -81,7 +81,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
|   | ||||
| @@ -81,7 +81,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
|   | ||||
| @@ -81,7 +81,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
|   | ||||
| @@ -43,7 +43,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
|   | ||||
| @@ -81,7 +81,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
| @@ -236,14 +236,29 @@ | ||||
|       <small>Source: <a href='https://github.com/msberends/AMR/blob/master/NEWS.md'><code>NEWS.md</code></a></small> | ||||
|     </div> | ||||
|  | ||||
|     <div id="amr-1409000" class="section level1"> | ||||
| <h1 class="page-header" data-toc-text="1.4.0.9000"> | ||||
| <a href="#amr-1409000" class="anchor"></a>AMR 1.4.0.9000<small> Unreleased </small> | ||||
|     <div id="amr-1409001" class="section level1"> | ||||
| <h1 class="page-header" data-toc-text="1.4.0.9001"> | ||||
| <a href="#amr-1409001" class="anchor"></a>AMR 1.4.0.9001<small> Unreleased </small> | ||||
| </h1> | ||||
| <div id="last-updated-15-october-2020" class="section level2"> | ||||
| <div id="last-updated-19-october-2020" class="section level2"> | ||||
| <h2 class="hasAnchor"> | ||||
| <a href="#last-updated-15-october-2020" class="anchor"></a><small>Last updated: 15 October 2020</small> | ||||
| <a href="#last-updated-19-october-2020" class="anchor"></a><small>Last updated: 19 October 2020</small> | ||||
| </h2> | ||||
| <div id="new" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#new" class="anchor"></a>New</h3> | ||||
| <ul> | ||||
| <li>Functions <code><a href="../reference/mo_property.html">is_gram_negative()</a></code> and <code><a href="../reference/mo_property.html">is_gram_positive()</a></code> as wrappers around <code><a href="../reference/mo_property.html">mo_gramstain()</a></code>. They always return <code>TRUE</code> or <code>FALSE</code>, thus always return <code>FALSE</code> for species outside the taxonomic kingdom of Bacteria.</li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="changed" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#changed" class="anchor"></a>Changed</h3> | ||||
| <ul> | ||||
| <li>For all function parameters in the code, it is now defined what the exact type of user input should be (inspired by the <a href="https://github.com/moodymudskipper/typed"><code>typed</code></a> package). If the user input for a certain function does not meet the requirements for a specific parameter (such as the class or length), an informative error will be thrown. This makes the package more robust and the use of it more reproducible and reliable. In total, more than 400 arguments were defined.</li> | ||||
| <li>Deprecated function <code><a href="../reference/AMR-deprecated.html">p_symbol()</a></code> that not really fits the scope of this package. It will be removed in a future version. See <a href="https://github.com/msberends/AMR/blob/v1.4.0/R/p_symbol.R">here</a> for the source code to preserve it.</li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="other" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#other" class="anchor"></a>Other</h3> | ||||
| @@ -258,9 +273,9 @@ | ||||
| <a href="#amr-140" class="anchor"></a>AMR 1.4.0<small> 2020-10-08 </small> | ||||
| </h1> | ||||
| <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-1" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#new" class="anchor"></a>New</h3> | ||||
| <a href="#new-1" class="anchor"></a>New</h3> | ||||
| <ul> | ||||
| <li><p>Support for ‘EUCAST Expert Rules’ / ‘EUCAST Intrinsic Resistance and Unusual Phenotypes’ version 3.2 of May 2020. With this addition to the previously implemented version 3.1 of 2016, the <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> function can now correct for more than 180 different antibiotics and the <code><a href="../reference/mdro.html">mdro()</a></code> function can determine multidrug resistance based on more than 150 different antibiotics. All previously implemented versions of the EUCAST rules are now maintained and kept available in this package. The <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> function consequently gained the parameters <code>version_breakpoints</code> (at the moment defaults to v10.0, 2020) and <code>version_expertrules</code> (at the moment defaults to v3.2, 2020). The <code>example_isolates</code> data set now also reflects the change from v3.1 to v3.2. The <code><a href="../reference/mdro.html">mdro()</a></code> function now accepts <code>guideline == "EUCAST3.1"</code> and <code>guideline == "EUCAST3.2"</code>.</p></li> | ||||
| <li><p>A new vignette and website page with info about all our public and freely available data sets, that can be downloaded as flat files or in formats for use in R, SPSS, SAS, Stata and Excel: <a href="https://msberends.github.io/AMR/articles/datasets.html" class="uri">https://msberends.github.io/AMR/articles/datasets.html</a></p></li> | ||||
| @@ -279,9 +294,9 @@ | ||||
| <li><p>Support for skimming classes <code><rsi></code>, <code><mic></code>, <code><disk></code> and <code><mo></code> with the <code>skimr</code> package</p></li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="changed" class="section level3"> | ||||
| <div id="changed-1" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#changed" class="anchor"></a>Changed</h3> | ||||
| <a href="#changed-1" class="anchor"></a>Changed</h3> | ||||
| <ul> | ||||
| <li><p>Although advertised that this package should work under R 3.0.0, we still had a dependency on R 3.6.0. This is fixed, meaning that our package should now work under R 3.0.0.</p></li> | ||||
| <li> | ||||
| @@ -359,9 +374,9 @@ | ||||
| <h1 class="page-header" data-toc-text="1.3.0"> | ||||
| <a href="#amr-130" class="anchor"></a>AMR 1.3.0<small> 2020-07-31 </small> | ||||
| </h1> | ||||
| <div id="new-1" class="section level3"> | ||||
| <div id="new-2" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#new-1" class="anchor"></a>New</h3> | ||||
| <a href="#new-2" class="anchor"></a>New</h3> | ||||
| <ul> | ||||
| <li><p>Function <code><a href="../reference/ab_from_text.html">ab_from_text()</a></code> to retrieve antimicrobial drug names, doses and forms of administration from clinical texts in e.g. health care records, which also corrects for misspelling since it uses <code><a href="../reference/as.ab.html">as.ab()</a></code> internally</p></li> | ||||
| <li> | ||||
| @@ -382,9 +397,9 @@ | ||||
| <li><p>Added parameter <code>conserve_capped_values</code> to <code><a href="../reference/as.rsi.html">as.rsi()</a></code> for interpreting MIC values - it makes sure that values starting with “<” (but not “<=”) will always return “S” and values starting with “>” (but not “>=”) will always return “R”. The default behaviour of <code><a href="../reference/as.rsi.html">as.rsi()</a></code> has not changed, so you need to specifically do <code><a href="../reference/as.rsi.html">as.rsi(..., conserve_capped_values = TRUE)</a></code>.</p></li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="changed-1" class="section level3"> | ||||
| <div id="changed-2" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#changed-1" class="anchor"></a>Changed</h3> | ||||
| <a href="#changed-2" class="anchor"></a>Changed</h3> | ||||
| <ul> | ||||
| <li> | ||||
| <p>Big speed improvement for using any function on microorganism codes from earlier package versions (prior to <code>AMR</code> v1.2.0), such as <code><a href="../reference/as.mo.html">as.mo()</a></code>, <code><a href="../reference/mo_property.html">mo_name()</a></code>, <code><a href="../reference/first_isolate.html">first_isolate()</a></code>, <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code>, <code><a href="../reference/mdro.html">mdro()</a></code>, etc.</p> | ||||
| @@ -450,7 +465,7 @@ | ||||
| <p>Making this package independent of especially the tidyverse (e.g. packages <code>dplyr</code> and <code>tidyr</code>) tremendously increases sustainability on the long term, since tidyverse functions change quite often. Good for users, but hard for package maintainers. Most of our functions are replaced with versions that only rely on base R, which keeps this package fully functional for many years to come, without requiring a lot of maintenance to keep up with other packages anymore. Another upside it that this package can now be used with all versions of R since R-3.0.0 (April 2013). Our package is being used in settings where the resources are very limited. Fewer dependencies on newer software is helpful for such settings.</p> | ||||
| <p>Negative effects of this change are:</p> | ||||
| <ul> | ||||
| <li>Function <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> that was borrowed from the <code>cleaner</code> package was removed. Use <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">cleaner::freq()</a></code>, or run <code><a href="https://github.com/msberends/cleaner">library("cleaner")</a></code> before you use <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code>.</li> | ||||
| <li>Function <code>freq()</code> that was borrowed from the <code>cleaner</code> package was removed. Use <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">cleaner::freq()</a></code>, or run <code><a href="https://github.com/msberends/cleaner">library("cleaner")</a></code> before you use <code>freq()</code>.</li> | ||||
| <li><del>Printing values of class <code>mo</code> or <code>rsi</code> in a tibble will no longer be in colour and printing <code>rsi</code> in a tibble will show the class <code><ord></code>, not <code><rsi></code> anymore. This is purely a visual effect.</del></li> | ||||
| <li><del>All functions from the <code>mo_*</code> family (like <code><a href="../reference/mo_property.html">mo_name()</a></code> and <code><a href="../reference/mo_property.html">mo_gramstain()</a></code>) are noticeably slower when running on hundreds of thousands of rows.</del></li> | ||||
| <li>For developers: classes <code>mo</code> and <code>ab</code> now both also inherit class <code>character</code>, to support any data transformation. This change invalidates code that checks for class length == 1.</li> | ||||
| @@ -458,9 +473,9 @@ | ||||
| </li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="changed-2" class="section level3"> | ||||
| <div id="changed-3" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#changed-2" class="anchor"></a>Changed</h3> | ||||
| <a href="#changed-3" class="anchor"></a>Changed</h3> | ||||
| <ul> | ||||
| <li>Taxonomy: | ||||
| <ul> | ||||
| @@ -495,7 +510,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#other-3" class="anchor"></a>Other</h3> | ||||
| <ul> | ||||
| <li>Removed previously deprecated function <code>p.symbol()</code> - it was replaced with <code><a href="../reference/p_symbol.html">p_symbol()</a></code> | ||||
| <li>Removed previously deprecated function <code>p.symbol()</code> - it was replaced with <code><a href="../reference/AMR-deprecated.html">p_symbol()</a></code> | ||||
| </li> | ||||
| <li>Removed function <code>read.4d()</code>, that was only useful for reading data from an old test database.</li> | ||||
| </ul> | ||||
| @@ -505,17 +520,17 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <h1 class="page-header" data-toc-text="1.1.0"> | ||||
| <a href="#amr-110" class="anchor"></a>AMR 1.1.0<small> 2020-04-15 </small> | ||||
| </h1> | ||||
| <div id="new-2" class="section level3"> | ||||
| <div id="new-3" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#new-2" class="anchor"></a>New</h3> | ||||
| <a href="#new-3" class="anchor"></a>New</h3> | ||||
| <ul> | ||||
| <li>Support for easy principal component analysis for AMR, using the new <code><a href="../reference/pca.html">pca()</a></code> function</li> | ||||
| <li>Plotting biplots for principal component analysis using the new <code><a href="../reference/ggplot_pca.html">ggplot_pca()</a></code> function</li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="changed-3" class="section level3"> | ||||
| <div id="changed-4" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#changed-3" class="anchor"></a>Changed</h3> | ||||
| <a href="#changed-4" class="anchor"></a>Changed</h3> | ||||
| <ul> | ||||
| <li>Improvements for the algorithm used by <code><a href="../reference/as.mo.html">as.mo()</a></code> (and consequently all <code>mo_*</code> functions, that use <code><a href="../reference/as.mo.html">as.mo()</a></code> internally): | ||||
| <ul> | ||||
| @@ -547,9 +562,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <h1 class="page-header" data-toc-text="1.0.1"> | ||||
| <a href="#amr-101" class="anchor"></a>AMR 1.0.1<small> 2020-02-23 </small> | ||||
| </h1> | ||||
| <div id="changed-4" class="section level3"> | ||||
| <div id="changed-5" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#changed-4" class="anchor"></a>Changed</h3> | ||||
| <a href="#changed-5" class="anchor"></a>Changed</h3> | ||||
| <ul> | ||||
| <li><p>Fixed important floating point error for some MIC comparisons in EUCAST 2020 guideline</p></li> | ||||
| <li> | ||||
| @@ -572,9 +587,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <a href="#amr-100" class="anchor"></a>AMR 1.0.0<small> 2020-02-17 </small> | ||||
| </h1> | ||||
| <p>This software is now out of beta and considered stable. Nonetheless, this package will be developed continually.</p> | ||||
| <div id="new-3" class="section level3"> | ||||
| <div id="new-4" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#new-3" class="anchor"></a>New</h3> | ||||
| <a href="#new-4" class="anchor"></a>New</h3> | ||||
| <ul> | ||||
| <li>Support for the newest <a href="https://www.eucast.org/clinical_breakpoints/">EUCAST Clinical Breakpoint Tables v.10.0</a>, valid from 1 January 2020. This affects translation of MIC and disk zones using <code><a href="../reference/as.rsi.html">as.rsi()</a></code> and inferred resistance and susceptibility using <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code>.</li> | ||||
| <li>The repository of this package now contains a clean version of the EUCAST and CLSI guidelines from 2011-2020 to translate MIC and disk diffusion values to R/SI: <a href="https://github.com/msberends/AMR/blob/master/data-raw/rsi_translation.txt" class="uri">https://github.com/msberends/AMR/blob/master/data-raw/rsi_translation.txt</a>. This <strong>allows for machine reading these guidelines</strong>, which is almost impossible with the Excel and PDF files distributed by EUCAST and CLSI. This file used to process the EUCAST Clinical Breakpoints Excel file <a href="https://github.com/msberends/AMR/blob/master/data-raw/read_EUCAST.R">can be found here</a>.</li> | ||||
| @@ -666,9 +681,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| </li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="new-4" class="section level3"> | ||||
| <div id="new-5" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#new-4" class="anchor"></a>New</h3> | ||||
| <a href="#new-5" class="anchor"></a>New</h3> | ||||
| <ul> | ||||
| <li> | ||||
| <p>Functions <code><a href="../reference/proportion.html">susceptibility()</a></code> and <code><a href="../reference/proportion.html">resistance()</a></code> as aliases of <code><a href="../reference/proportion.html">proportion_SI()</a></code> and <code><a href="../reference/proportion.html">proportion_R()</a></code>, respectively. These functions were added to make it more clear that “I” should be considered susceptible and not resistant.</p> | ||||
| @@ -778,13 +793,13 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <span class="co">#> invalid microorganism code, NA generated</span></pre></div> | ||||
| <p>This is important, because a value like <code>"testvalue"</code> could never be understood by e.g. <code><a href="../reference/mo_property.html">mo_name()</a></code>, although the class would suggest a valid microbial code.</p> | ||||
| </li> | ||||
| <li><p>Function <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> has moved to a new package, <a href="https://github.com/msberends/clean"><code>clean</code></a> (<a href="https://cran.r-project.org/package=clean">CRAN link</a>), since creating frequency tables actually does not fit the scope of this package. The <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> function still works, since it is re-exported from the <code>clean</code> package (which will be installed automatically upon updating this <code>AMR</code> package).</p></li> | ||||
| <li><p>Function <code>freq()</code> has moved to a new package, <a href="https://github.com/msberends/clean"><code>clean</code></a> (<a href="https://cran.r-project.org/package=clean">CRAN link</a>), since creating frequency tables actually does not fit the scope of this package. The <code>freq()</code> function still works, since it is re-exported from the <code>clean</code> package (which will be installed automatically upon updating this <code>AMR</code> package).</p></li> | ||||
| <li><p>Renamed data set <code>septic_patients</code> to <code>example_isolates</code></p></li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="new-5" class="section level3"> | ||||
| <div id="new-6" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#new-5" class="anchor"></a>New</h3> | ||||
| <a href="#new-6" class="anchor"></a>New</h3> | ||||
| <ul> | ||||
| <li> | ||||
| <p>Function <code><a href="../reference/bug_drug_combinations.html">bug_drug_combinations()</a></code> to quickly get a <code>data.frame</code> with the results of all bug-drug combinations in a data set. The column containing microorganism codes is guessed automatically and its input is transformed with <code><a href="../reference/mo_property.html">mo_shortname()</a></code> at default:</p> | ||||
| @@ -845,9 +860,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| </li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="changed-5" class="section level3"> | ||||
| <div id="changed-6" class="section level3"> | ||||
| <h3 class="hasAnchor"> | ||||
| <a href="#changed-5" class="anchor"></a>Changed</h3> | ||||
| <a href="#changed-6" class="anchor"></a>Changed</h3> | ||||
| <ul> | ||||
| <li>Many algorithm improvements for <code><a href="../reference/as.mo.html">as.mo()</a></code> (of which some led to additions to the <code>microorganisms</code> data set). Many thanks to all contributors that helped improving the algorithms. | ||||
| <ul> | ||||
| @@ -889,7 +904,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <li>Improved <code><a href="../reference/filter_ab_class.html">filter_ab_class()</a></code> to be more reliable and to support 5th generation cephalosporins</li> | ||||
| <li>Function <code><a href="../reference/availability.html">availability()</a></code> now uses <code>portion_R()</code> instead of <code>portion_IR()</code>, to comply with EUCAST insights</li> | ||||
| <li>Functions <code><a href="../reference/age.html">age()</a></code> and <code><a href="../reference/age_groups.html">age_groups()</a></code> now have a <code>na.rm</code> parameter to remove empty values</li> | ||||
| <li>Renamed function <code>p.symbol()</code> to <code><a href="../reference/p_symbol.html">p_symbol()</a></code> (the former is now deprecated and will be removed in a future version)</li> | ||||
| <li>Renamed function <code>p.symbol()</code> to <code><a href="../reference/AMR-deprecated.html">p_symbol()</a></code> (the former is now deprecated and will be removed in a future version)</li> | ||||
| <li>Using negative values for <code>x</code> in <code><a href="../reference/age_groups.html">age_groups()</a></code> will now introduce <code>NA</code>s and not return an error anymore</li> | ||||
| <li>Fix for determining the system’s language</li> | ||||
| <li>Fix for <code><a href="../reference/key_antibiotics.html">key_antibiotics()</a></code> on foreign systems</li> | ||||
| @@ -912,9 +927,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <h1 class="page-header" data-toc-text="0.7.1"> | ||||
| <a href="#amr-071" class="anchor"></a>AMR 0.7.1<small> 2019-06-23 </small> | ||||
| </h1> | ||||
| <div id="new-6" class="section level4"> | ||||
| <div id="new-7" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#new-6" class="anchor"></a>New</h4> | ||||
| <a href="#new-7" class="anchor"></a>New</h4> | ||||
| <ul> | ||||
| <li> | ||||
| <p>Function <code><a href="../reference/proportion.html">rsi_df()</a></code> to transform a <code>data.frame</code> to a data set containing only the microbial interpretation (S, I, R), the antibiotic, the percentage of S/I/R and the number of available isolates. This is a convenient combination of the existing functions <code><a href="../reference/count.html">count_df()</a></code> and <code>portion_df()</code> to immediately show resistance percentages and number of available isolates:</p> | ||||
| @@ -956,9 +971,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <li><p>Function <code><a href="../reference/mo_property.html">mo_synonyms()</a></code> to get all previously accepted taxonomic names of a microorganism</p></li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="changed-6" class="section level4"> | ||||
| <div id="changed-7" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#changed-6" class="anchor"></a>Changed</h4> | ||||
| <a href="#changed-7" class="anchor"></a>Changed</h4> | ||||
| <ul> | ||||
| <li>Column names of output <code><a href="../reference/count.html">count_df()</a></code> and <code>portion_df()</code> are now lowercase</li> | ||||
| <li>Fixed bug in translation of microorganism names</li> | ||||
| @@ -995,9 +1010,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <h1 class="page-header" data-toc-text="0.7.0"> | ||||
| <a href="#amr-070" class="anchor"></a>AMR 0.7.0<small> 2019-06-03 </small> | ||||
| </h1> | ||||
| <div id="new-7" class="section level4"> | ||||
| <div id="new-8" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#new-7" class="anchor"></a>New</h4> | ||||
| <a href="#new-8" class="anchor"></a>New</h4> | ||||
| <ul> | ||||
| <li>Support for translation of disk diffusion and MIC values to RSI values (i.e. antimicrobial interpretations). Supported guidelines are EUCAST (2011 to 2019) and CLSI (2011 to 2019). Use <code><a href="../reference/as.rsi.html">as.rsi()</a></code> on an MIC value (created with <code><a href="../reference/as.mic.html">as.mic()</a></code>), a disk diffusion value (created with the new <code><a href="../reference/as.disk.html">as.disk()</a></code>) or on a complete date set containing columns with MIC or disk diffusion values.</li> | ||||
| <li>Function <code><a href="../reference/mo_property.html">mo_name()</a></code> as alias of <code><a href="../reference/mo_property.html">mo_fullname()</a></code> | ||||
| @@ -1005,9 +1020,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <li>Added guidelines of the WHO to determine multi-drug resistance (MDR) for TB (<code><a href="../reference/mdro.html">mdr_tb()</a></code>) and added a new vignette about MDR. Read this tutorial <a href="https://msberends.gitlab.io/AMR/articles/MDR.html">here on our website</a>.</li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="changed-7" class="section level4"> | ||||
| <div id="changed-8" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#changed-7" class="anchor"></a>Changed</h4> | ||||
| <a href="#changed-8" class="anchor"></a>Changed</h4> | ||||
| <ul> | ||||
| <li>Fixed a critical bug in <code><a href="../reference/first_isolate.html">first_isolate()</a></code> where missing species would lead to incorrect FALSEs. This bug was not present in AMR v0.5.0, but was in v0.6.0 and v0.6.1.</li> | ||||
| <li>Fixed a bug in <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> where antibiotics from WHONET software would not be recognised</li> | ||||
| @@ -1041,7 +1056,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <li>The <code><a href="../reference/age.html">age()</a></code> function gained a new parameter <code>exact</code> to determine ages with decimals</li> | ||||
| <li>Removed deprecated functions <code>guess_mo()</code>, <code>guess_atc()</code>, <code>EUCAST_rules()</code>, <code>interpretive_reading()</code>, <code><a href="../reference/as.rsi.html">rsi()</a></code> | ||||
| </li> | ||||
| <li>Frequency tables (<code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code>): | ||||
| <li>Frequency tables (<code>freq()</code>): | ||||
| <ul> | ||||
| <li><p>speed improvement for microbial IDs</p></li> | ||||
| <li><p>fixed factor level names for R Markdown</p></li> | ||||
| @@ -1050,12 +1065,12 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <p>support for boxplots:</p> | ||||
| <div class="sourceCode" id="cb20"><pre class="downlit"> | ||||
| <span class="va">septic_patients</span> <span class="op">%>%</span>  | ||||
|   <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">age</span><span class="op">)</span> <span class="op">%>%</span>  | ||||
|   <span class="fu">freq</span><span class="op">(</span><span class="va">age</span><span class="op">)</span> <span class="op">%>%</span>  | ||||
|   <span class="fu"><a href="https://rdrr.io/r/graphics/boxplot.html">boxplot</a></span><span class="op">(</span><span class="op">)</span> | ||||
| <span class="co"># grouped boxplots:</span> | ||||
| <span class="va">septic_patients</span> <span class="op">%>%</span>  | ||||
|   <span class="fu"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span><span class="op">(</span><span class="va">hospital_id</span><span class="op">)</span> <span class="op">%>%</span>  | ||||
|   <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">age</span><span class="op">)</span> <span class="op">%>%</span> | ||||
|   <span class="fu">freq</span><span class="op">(</span><span class="va">age</span><span class="op">)</span> <span class="op">%>%</span> | ||||
|   <span class="fu"><a href="https://rdrr.io/r/graphics/boxplot.html">boxplot</a></span><span class="op">(</span><span class="op">)</span></pre></div> | ||||
| </li> | ||||
| </ul> | ||||
| @@ -1065,7 +1080,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <li>Added ceftazidim intrinsic resistance to <em>Streptococci</em> | ||||
| </li> | ||||
| <li>Changed default settings for <code><a href="../reference/age_groups.html">age_groups()</a></code>, to let groups of fives and tens end with 100+ instead of 120+</li> | ||||
| <li>Fix for <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> for when all values are <code>NA</code> | ||||
| <li>Fix for <code>freq()</code> for when all values are <code>NA</code> | ||||
| </li> | ||||
| <li>Fix for <code><a href="../reference/first_isolate.html">first_isolate()</a></code> for when dates are missing</li> | ||||
| <li>Improved speed of <code><a href="../reference/guess_ab_col.html">guess_ab_col()</a></code> | ||||
| @@ -1091,9 +1106,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <h1 class="page-header" data-toc-text="0.6.1"> | ||||
| <a href="#amr-061" class="anchor"></a>AMR 0.6.1<small> 2019-03-29 </small> | ||||
| </h1> | ||||
| <div id="changed-8" class="section level4"> | ||||
| <div id="changed-9" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#changed-8" class="anchor"></a>Changed</h4> | ||||
| <a href="#changed-9" class="anchor"></a>Changed</h4> | ||||
| <ul> | ||||
| <li>Fixed a critical bug when using <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> with <code>verbose = TRUE</code> | ||||
| </li> | ||||
| @@ -1111,9 +1126,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <li>Contains the complete manual of this package and all of its functions with an explanation of their parameters</li> | ||||
| <li>Contains a comprehensive tutorial about how to conduct antimicrobial resistance analysis, import data from WHONET or SPSS and many more.</li> | ||||
| </ul> | ||||
| <div id="new-8" class="section level4"> | ||||
| <div id="new-9" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#new-8" class="anchor"></a>New</h4> | ||||
| <a href="#new-9" class="anchor"></a>New</h4> | ||||
| <ul> | ||||
| <li><p><strong>BREAKING</strong>: removed deprecated functions, parameters and references to ‘bactid’. Use <code><a href="../reference/as.mo.html">as.mo()</a></code> to identify an MO code.</p></li> | ||||
| <li> | ||||
| @@ -1205,9 +1220,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <li><p>New vignettes about how to conduct AMR analysis, predict antimicrobial resistance, use the <em>G</em>-test and more. These are also available (and even easier readable) on our website: <a href="https://msberends.gitlab.io/AMR" class="uri">https://msberends.gitlab.io/AMR</a>.</p></li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="changed-9" class="section level4"> | ||||
| <div id="changed-10" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#changed-9" class="anchor"></a>Changed</h4> | ||||
| <a href="#changed-10" class="anchor"></a>Changed</h4> | ||||
| <ul> | ||||
| <li>Function <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code>: | ||||
| <ul> | ||||
| @@ -1297,7 +1312,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| </li> | ||||
| </ul> | ||||
| </li> | ||||
| <li>Frequency tables (<code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> function): | ||||
| <li>Frequency tables (<code>freq()</code> function): | ||||
| <ul> | ||||
| <li> | ||||
| <p>Support for tidyverse quasiquotation! Now you can create frequency tables of function outcomes:</p> | ||||
| @@ -1306,15 +1321,15 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <span class="co"># OLD WAY</span> | ||||
| <span class="va">septic_patients</span> <span class="op">%>%</span> | ||||
|   <span class="fu"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span><span class="op">(</span>genus <span class="op">=</span> <span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span> <span class="op">%>%</span> | ||||
|   <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">genus</span><span class="op">)</span> | ||||
|   <span class="fu">freq</span><span class="op">(</span><span class="va">genus</span><span class="op">)</span> | ||||
| <span class="co"># NEW WAY</span> | ||||
| <span class="va">septic_patients</span> <span class="op">%>%</span>  | ||||
|   <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span> | ||||
|   <span class="fu">freq</span><span class="op">(</span><span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span> | ||||
|  | ||||
| <span class="co"># Even supports grouping variables:</span> | ||||
| <span class="va">septic_patients</span> <span class="op">%>%</span> | ||||
|   <span class="fu"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span><span class="op">(</span><span class="va">gender</span><span class="op">)</span> <span class="op">%>%</span>  | ||||
|   <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span></pre></div> | ||||
|   <span class="fu">freq</span><span class="op">(</span><span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span></pre></div> | ||||
| </li> | ||||
| <li><p>Header info is now available as a list, with the <code>header</code> function</p></li> | ||||
| <li><p>The parameter <code>header</code> is now set to <code>TRUE</code> at default, even for markdown</p></li> | ||||
| @@ -1347,9 +1362,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <h1 class="page-header" data-toc-text="0.5.0"> | ||||
| <a href="#amr-050" class="anchor"></a>AMR 0.5.0<small> 2018-11-30 </small> | ||||
| </h1> | ||||
| <div id="new-9" class="section level4"> | ||||
| <div id="new-10" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#new-9" class="anchor"></a>New</h4> | ||||
| <a href="#new-10" class="anchor"></a>New</h4> | ||||
| <ul> | ||||
| <li>Repository moved to GitLab</li> | ||||
| <li>Function <code>count_all</code> to get all available isolates (that like all <code>portion_*</code> and <code>count_*</code> functions also supports <code>summarise</code> and <code>group_by</code>), the old <code>n_rsi</code> is now an alias of <code>count_all</code> | ||||
| @@ -1360,9 +1375,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <li>Functions <code>mo_authors</code> and <code>mo_year</code> to get specific values about the scientific reference of a taxonomic entry</li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="changed-10" class="section level4"> | ||||
| <div id="changed-11" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#changed-10" class="anchor"></a>Changed</h4> | ||||
| <a href="#changed-11" class="anchor"></a>Changed</h4> | ||||
| <ul> | ||||
| <li><p>Functions <code>MDRO</code>, <code>BRMO</code>, <code>MRGN</code> and <code>EUCAST_exceptional_phenotypes</code> were renamed to <code>mdro</code>, <code>brmo</code>, <code>mrgn</code> and <code>eucast_exceptional_phenotypes</code></p></li> | ||||
| <li><p><code>EUCAST_rules</code> was renamed to <code>eucast_rules</code>, the old function still exists as a deprecated function</p></li> | ||||
| @@ -1396,20 +1411,20 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <li><p>Using <code>portion_*</code> functions now throws a warning when total available isolate is below parameter <code>minimum</code></p></li> | ||||
| <li><p>Functions <code>as.mo</code>, <code>as.rsi</code>, <code>as.mic</code>, <code>as.atc</code> and <code>freq</code> will not set package name as attribute anymore</p></li> | ||||
| <li> | ||||
| <p>Frequency tables - <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code>:</p> | ||||
| <p>Frequency tables - <code>freq()</code>:</p> | ||||
| <ul> | ||||
| <li> | ||||
| <p>Support for grouping variables, test with:</p> | ||||
| <div class="sourceCode" id="cb32"><pre class="downlit"> | ||||
| <span class="va">septic_patients</span> <span class="op">%>%</span>  | ||||
|   <span class="fu"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span><span class="op">(</span><span class="va">hospital_id</span><span class="op">)</span> <span class="op">%>%</span>  | ||||
|   <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">gender</span><span class="op">)</span></pre></div> | ||||
|   <span class="fu">freq</span><span class="op">(</span><span class="va">gender</span><span class="op">)</span></pre></div> | ||||
| </li> | ||||
| <li> | ||||
| <p>Support for (un)selecting columns:</p> | ||||
| <div class="sourceCode" id="cb33"><pre class="downlit"> | ||||
| <span class="va">septic_patients</span> <span class="op">%>%</span>  | ||||
|   <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">hospital_id</span><span class="op">)</span> <span class="op">%>%</span>  | ||||
|   <span class="fu">freq</span><span class="op">(</span><span class="va">hospital_id</span><span class="op">)</span> <span class="op">%>%</span>  | ||||
|   <span class="fu"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span><span class="op">(</span><span class="op">-</span><span class="va">count</span>, <span class="op">-</span><span class="va">cum_count</span><span class="op">)</span> <span class="co"># only get item, percent, cum_percent</span></pre></div> | ||||
| </li> | ||||
| <li><p>Check for <code><a href="https://hms.tidyverse.org/reference/Deprecated.html">hms::is.hms</a></code></p></li> | ||||
| @@ -1427,7 +1442,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <li><p>Removed diacritics from all authors (columns <code>microorganisms$ref</code> and <code>microorganisms.old$ref</code>) to comply with CRAN policy to only allow ASCII characters</p></li> | ||||
| <li><p>Fix for <code>mo_property</code> not working properly</p></li> | ||||
| <li><p>Fix for <code>eucast_rules</code> where some Streptococci would become ceftazidime R in EUCAST rule 4.5</p></li> | ||||
| <li><p>Support for named vectors of class <code>mo</code>, useful for <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">top_freq()</a></code></p></li> | ||||
| <li><p>Support for named vectors of class <code>mo</code>, useful for <code>top_freq()</code></p></li> | ||||
| <li><p><code>ggplot_rsi</code> and <code>scale_y_percent</code> have <code>breaks</code> parameter</p></li> | ||||
| <li> | ||||
| <p>AI improvements for <code>as.mo</code>:</p> | ||||
| @@ -1468,9 +1483,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <h1 class="page-header" data-toc-text="0.4.0"> | ||||
| <a href="#amr-040" class="anchor"></a>AMR 0.4.0<small> 2018-10-01 </small> | ||||
| </h1> | ||||
| <div id="new-10" class="section level4"> | ||||
| <div id="new-11" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#new-10" class="anchor"></a>New</h4> | ||||
| <a href="#new-11" class="anchor"></a>New</h4> | ||||
| <ul> | ||||
| <li><p>The data set <code>microorganisms</code> now contains <strong>all microbial taxonomic data from ITIS</strong> (kingdoms Bacteria, Fungi and Protozoa), the Integrated Taxonomy Information System, available via <a href="https://itis.gov" class="uri">https://itis.gov</a>. The data set now contains more than 18,000 microorganisms with all known bacteria, fungi and protozoa according ITIS with genus, species, subspecies, family, order, class, phylum and subkingdom. The new data set <code>microorganisms.old</code> contains all previously known taxonomic names from those kingdoms.</p></li> | ||||
| <li> | ||||
| @@ -1544,9 +1559,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <li><p>Renamed <code>septic_patients$sex</code> to <code>septic_patients$gender</code></p></li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="changed-11" class="section level4"> | ||||
| <div id="changed-12" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#changed-11" class="anchor"></a>Changed</h4> | ||||
| <a href="#changed-12" class="anchor"></a>Changed</h4> | ||||
| <ul> | ||||
| <li><p>Added three antimicrobial agents to the <code>antibiotics</code> data set: Terbinafine (D01BA02), Rifaximin (A07AA11) and Isoconazole (D01AC05)</p></li> | ||||
| <li> | ||||
| @@ -1588,12 +1603,12 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <p>Support for types (classes) list and matrix for <code>freq</code></p> | ||||
| <div class="sourceCode" id="cb40"><pre class="downlit"> | ||||
| <span class="va">my_matrix</span> <span class="op">=</span> <span class="fu"><a href="https://rdrr.io/r/base/with.html">with</a></span><span class="op">(</span><span class="va">septic_patients</span>, <span class="fu"><a href="https://rdrr.io/r/base/matrix.html">matrix</a></span><span class="op">(</span><span class="fu"><a href="https://rdrr.io/r/base/c.html">c</a></span><span class="op">(</span><span class="va">age</span>, <span class="va">gender</span><span class="op">)</span>, ncol <span class="op">=</span> <span class="fl">2</span><span class="op">)</span><span class="op">)</span> | ||||
| <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">my_matrix</span><span class="op">)</span></pre></div> | ||||
| <span class="fu">freq</span><span class="op">(</span><span class="va">my_matrix</span><span class="op">)</span></pre></div> | ||||
| <p>For lists, subsetting is possible:</p> | ||||
| <div class="sourceCode" id="cb41"><pre class="downlit"> | ||||
| <span class="va">my_list</span> <span class="op">=</span> <span class="fu"><a href="https://rdrr.io/r/base/list.html">list</a></span><span class="op">(</span>age <span class="op">=</span> <span class="va">septic_patients</span><span class="op">$</span><span class="va">age</span>, gender <span class="op">=</span> <span class="va">septic_patients</span><span class="op">$</span><span class="va">gender</span><span class="op">)</span> | ||||
| <span class="va">my_list</span> <span class="op">%>%</span> <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">age</span><span class="op">)</span> | ||||
| <span class="va">my_list</span> <span class="op">%>%</span> <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">gender</span><span class="op">)</span></pre></div> | ||||
| <span class="va">my_list</span> <span class="op">%>%</span> <span class="fu">freq</span><span class="op">(</span><span class="va">age</span><span class="op">)</span> | ||||
| <span class="va">my_list</span> <span class="op">%>%</span> <span class="fu">freq</span><span class="op">(</span><span class="va">gender</span><span class="op">)</span></pre></div> | ||||
| </li> | ||||
| </ul> | ||||
| </div> | ||||
| @@ -1609,9 +1624,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <h1 class="page-header" data-toc-text="0.3.0"> | ||||
| <a href="#amr-030" class="anchor"></a>AMR 0.3.0<small> 2018-08-14 </small> | ||||
| </h1> | ||||
| <div id="new-11" class="section level4"> | ||||
| <div id="new-12" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#new-11" class="anchor"></a>New</h4> | ||||
| <a href="#new-12" class="anchor"></a>New</h4> | ||||
| <ul> | ||||
| <li> | ||||
| <strong>BREAKING</strong>: <code>rsi_df</code> was removed in favour of new functions <code>portion_R</code>, <code>portion_IR</code>, <code>portion_I</code>, <code>portion_SI</code> and <code>portion_S</code> to selectively calculate resistance or susceptibility. These functions are 20 to 30 times faster than the old <code>rsi</code> function. The old function still works, but is deprecated. | ||||
| @@ -1667,13 +1682,13 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <ul> | ||||
| <li>A vignette to explain its usage</li> | ||||
| <li>Support for <code>rsi</code> (antimicrobial resistance) to use as input</li> | ||||
| <li>Support for <code>table</code> to use as input: <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq(table(x, y))</a></code> | ||||
| <li>Support for <code>table</code> to use as input: <code>freq(table(x, y))</code> | ||||
| </li> | ||||
| <li>Support for existing functions <code>hist</code> and <code>plot</code> to use a frequency table as input: <code><a href="https://rdrr.io/r/graphics/hist.html">hist(freq(df$age))</a></code> | ||||
| </li> | ||||
| <li>Support for <code>as.vector</code>, <code>as.data.frame</code>, <code>as_tibble</code> and <code>format</code> | ||||
| </li> | ||||
| <li>Support for quasiquotation: <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq(mydata, mycolumn)</a></code> is the same as <code>mydata %>% freq(mycolumn)</code> | ||||
| <li>Support for quasiquotation: <code>freq(mydata, mycolumn)</code> is the same as <code>mydata %>% freq(mycolumn)</code> | ||||
| </li> | ||||
| <li>Function <code>top_freq</code> function to return the top/below <em>n</em> items as vector</li> | ||||
| <li>Header of frequency tables now also show Mean Absolute Deviaton (MAD) and Interquartile Range (IQR)</li> | ||||
| @@ -1682,9 +1697,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| </li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="changed-12" class="section level4"> | ||||
| <div id="changed-13" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#changed-12" class="anchor"></a>Changed</h4> | ||||
| <a href="#changed-13" class="anchor"></a>Changed</h4> | ||||
| <ul> | ||||
| <li>Improvements for forecasting with <code>resistance_predict</code> and added more examples</li> | ||||
| <li>More antibiotics added as parameters for EUCAST rules</li> | ||||
| @@ -1746,9 +1761,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <h1 class="page-header" data-toc-text="0.2.0"> | ||||
| <a href="#amr-020" class="anchor"></a>AMR 0.2.0<small> 2018-05-03 </small> | ||||
| </h1> | ||||
| <div id="new-12" class="section level4"> | ||||
| <div id="new-13" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#new-12" class="anchor"></a>New</h4> | ||||
| <a href="#new-13" class="anchor"></a>New</h4> | ||||
| <ul> | ||||
| <li>Full support for Windows, Linux and macOS</li> | ||||
| <li>Full support for old R versions, only R-3.0.0 (April 2013) or later is needed (needed packages may have other dependencies)</li> | ||||
| @@ -1768,9 +1783,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/ | ||||
| <li>New print format for <code>tibble</code>s and <code>data.table</code>s</li> | ||||
| </ul> | ||||
| </div> | ||||
| <div id="changed-13" class="section level4"> | ||||
| <div id="changed-14" class="section level4"> | ||||
| <h4 class="hasAnchor"> | ||||
| <a href="#changed-13" class="anchor"></a>Changed</h4> | ||||
| <a href="#changed-14" class="anchor"></a>Changed</h4> | ||||
| <ul> | ||||
| <li>Fixed <code>rsi</code> class for vectors that contain only invalid antimicrobial interpretations</li> | ||||
| <li>Renamed dataset <code>ablist</code> to <code>antibiotics</code> | ||||
|   | ||||
| @@ -12,7 +12,7 @@ articles: | ||||
|   datasets: datasets.html | ||||
|   resistance_predict: resistance_predict.html | ||||
|   welcome_to_AMR: welcome_to_AMR.html | ||||
| last_built: 2020-10-15T07:41Z | ||||
| last_built: 2020-10-19T15:08Z | ||||
| urls: | ||||
|   reference: https://msberends.github.io/AMR//reference | ||||
|   article: https://msberends.github.io/AMR//articles | ||||
|   | ||||
| @@ -50,7 +50,7 @@ | ||||
|  | ||||
| <meta property="og:title" content="Deprecated functions — AMR-deprecated" /> | ||||
| <meta property="og:description" content="These functions are so-called 'Deprecated'. They will be removed in a future release. Using the functions will give a warning with the name of the function it has been replaced by (if there is one)." /> | ||||
| <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> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9015</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
| @@ -242,17 +242,7 @@ | ||||
|     <p>These functions are so-called '<a href='https://rdrr.io/r/base/Deprecated.html'>Deprecated</a>'. They will be removed in a future release. Using the functions will give a warning with the name of the function it has been replaced by (if there is one).</p> | ||||
|     </div> | ||||
|  | ||||
|     <pre class="usage"><span class='fu'>portion_R</span>(<span class='kw'>...</span>) | ||||
|  | ||||
| <span class='fu'>portion_IR</span>(<span class='kw'>...</span>) | ||||
|  | ||||
| <span class='fu'>portion_I</span>(<span class='kw'>...</span>) | ||||
|  | ||||
| <span class='fu'>portion_SI</span>(<span class='kw'>...</span>) | ||||
|  | ||||
| <span class='fu'>portion_S</span>(<span class='kw'>...</span>) | ||||
|  | ||||
| <span class='fu'>portion_df</span>(<span class='kw'>...</span>)</pre> | ||||
|     <pre class="usage"><span class='fu'>p_symbol</span><span class='op'>(</span><span class='va'>p</span>, emptychar <span class='op'>=</span> <span class='st'>" "</span><span class='op'>)</span></pre> | ||||
|  | ||||
|  | ||||
|     <h2 class="hasAnchor" id="retired-lifecycle"><a class="anchor" href="#retired-lifecycle"></a>Retired lifecycle</h2> | ||||
| @@ -265,7 +255,7 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>retired</ | ||||
|  | ||||
|      | ||||
|  | ||||
| <p>On our website <a href='https://msberends.github.io/AMR'>https://msberends.github.io/AMR</a> you can find <a href='https://msberends.github.io/AMR/articles/AMR.html'>a comprehensive tutorial</a> about how to conduct AMR analysis, the <a href='https://msberends.github.io/AMR/reference'>complete documentation of all functions</a> (which reads a lot easier than here in R) and <a href='https://msberends.github.io/AMR/articles/WHONET.html'>an example analysis using WHONET data</a>. As we would like to better understand the backgrounds and needs of our users, please <a href='https://msberends.github.io/AMR/survey.html'>participate in our survey</a>!</p> | ||||
| <p>On our website <a href='https://msberends.github.io/AMR/'>https://msberends.github.io/AMR/</a> you can find <a href='https://msberends.github.io/AMR/articles/AMR.html'>a comprehensive tutorial</a> about how to conduct AMR analysis, the <a href='https://msberends.github.io/AMR/reference/'>complete documentation of all functions</a> and <a href='https://msberends.github.io/AMR/articles/WHONET.html'>an example analysis using WHONET data</a>. As we would like to better understand the backgrounds and needs of our users, please <a href='https://msberends.github.io/AMR/survey.html'>participate in our survey</a>!</p> | ||||
|  | ||||
|   </div> | ||||
|   <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> | ||||
| @@ -282,7 +272,7 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>retired</ | ||||
| </div> | ||||
|  | ||||
| <div class="pkgdown"> | ||||
|   <p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.5.1.9000.</p> | ||||
|   <p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.6.1.</p> | ||||
| </div> | ||||
|  | ||||
|       </footer> | ||||
|   | ||||
| @@ -82,7 +82,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
| @@ -242,7 +242,7 @@ | ||||
|     <p>Calculates age in years based on a reference date, which is the sytem date at default.</p> | ||||
|     </div> | ||||
|  | ||||
|     <pre class="usage"><span class='fu'>age</span><span class='op'>(</span><span class='va'>x</span>, reference <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/Sys.time.html'>Sys.Date</a></span><span class='op'>(</span><span class='op'>)</span>, exact <span class='op'>=</span> <span class='cn'>FALSE</span>, na.rm <span class='op'>=</span> <span class='cn'>FALSE</span><span class='op'>)</span></pre> | ||||
|     <pre class="usage"><span class='fu'>age</span><span class='op'>(</span><span class='va'>x</span>, reference <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/Sys.time.html'>Sys.Date</a></span><span class='op'>(</span><span class='op'>)</span>, exact <span class='op'>=</span> <span class='cn'>FALSE</span>, na.rm <span class='op'>=</span> <span class='cn'>FALSE</span>, <span class='va'>...</span><span class='op'>)</span></pre> | ||||
|  | ||||
|     <h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2> | ||||
|     <table class="ref-arguments"> | ||||
| @@ -253,7 +253,7 @@ | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>reference</th> | ||||
|       <td><p>reference date(s) (defaults to today), will be coerced with <code><a href='https://rdrr.io/r/base/as.POSIXlt.html'>as.POSIXlt()</a></code> and cannot be lower than <code>x</code></p></td> | ||||
|       <td><p>reference date(s) (defaults to today), will be coerced with <code><a href='https://rdrr.io/r/base/as.POSIXlt.html'>as.POSIXlt()</a></code></p></td> | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>exact</th> | ||||
| @@ -263,11 +263,18 @@ | ||||
|       <th>na.rm</th> | ||||
|       <td><p>a logical to indicate whether missing values should be removed</p></td> | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>...</th> | ||||
|       <td><p>parameters passed on to <code><a href='https://rdrr.io/r/base/as.POSIXlt.html'>as.POSIXlt()</a></code>, such as <code>origin</code></p></td> | ||||
|     </tr> | ||||
|     </table> | ||||
|  | ||||
|     <h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2> | ||||
|  | ||||
|     <p>An <a href='https://rdrr.io/r/base/integer.html'>integer</a> (no decimals) if <code>exact = FALSE</code>, a <a href='https://rdrr.io/r/base/double.html'>double</a> (with decimals) otherwise</p> | ||||
|     <h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2> | ||||
|  | ||||
|     <p>Ages below 0 will be returned as <code>NA</code> with a warning. Ages above 120 will only give a warning.</p> | ||||
|     <h2 class="hasAnchor" id="stable-lifecycle"><a class="anchor" href="#stable-lifecycle"></a>Stable lifecycle</h2> | ||||
|  | ||||
|      | ||||
|   | ||||
| @@ -82,7 +82,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
| @@ -267,13 +267,13 @@ | ||||
|     <h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2> | ||||
|  | ||||
|     <p>To split ages, the input for the <code>split_at</code> parameter can be:</p><ul> | ||||
| <li><p>A numeric vector. A vector of e.g. <code><a href='https://rdrr.io/r/base/c.html'>c(10, 20)</a></code> will split on 0-9, 10-19 and 20+. A value of only <code>50</code> will split on 0-49 and 50+. | ||||
| <li><p>A numeric vector. A value of e.g. <code><a href='https://rdrr.io/r/base/c.html'>c(10, 20)</a></code> will split <code>x</code> on 0-9, 10-19 and 20+. A value of only <code>50</code> will split <code>x</code> on 0-49 and 50+. | ||||
| The default is to split on young children (0-11), youth (12-24), young adults (25-54), middle-aged adults (55-74) and elderly (75+).</p></li> | ||||
| <li><p>A character:</p><ul> | ||||
| <li><p><code>"children"</code> or <code>"kids"</code>, equivalent of: <code><a href='https://rdrr.io/r/base/c.html'>c(0, 1, 2, 4, 6, 13, 18)</a></code>. This will split on 0, 1, 2-3, 4-5, 6-12, 13-17 and 18+.</p></li> | ||||
| <li><p><code>"elderly"</code> or <code>"seniors"</code>, equivalent of: <code><a href='https://rdrr.io/r/base/c.html'>c(65, 75, 85)</a></code>. This will split on 0-64, 65-74, 75-84, 85+.</p></li> | ||||
| <li><p><code>"fives"</code>, equivalent of: <code>1:20 * 5</code>. This will split on 0-4, 5-9, 10-14, ..., 90-94, 95-99, 100+.</p></li> | ||||
| <li><p><code>"tens"</code>, equivalent of: <code>1:10 * 10</code>. This will split on 0-9, 10-19, 20-29, ..., 80-89, 90-99, 100+.</p></li> | ||||
| <li><p><code>"fives"</code>, equivalent of: <code>1:20 * 5</code>. This will split on 0-4, 5-9, ..., 95-99, 100+.</p></li> | ||||
| <li><p><code>"tens"</code>, equivalent of: <code>1:10 * 10</code>. This will split on 0-9, 10-19, ..., 90-99, 100+.</p></li> | ||||
| </ul></li> | ||||
| </ul> | ||||
|  | ||||
| @@ -311,12 +311,11 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>stable</s | ||||
| <span class='fu'>age_groups</span><span class='op'>(</span><span class='va'>ages</span>, split_at <span class='op'>=</span> <span class='st'>"fives"</span><span class='op'>)</span> | ||||
|  | ||||
| <span class='co'># split specifically for children</span> | ||||
| <span class='fu'>age_groups</span><span class='op'>(</span><span class='va'>ages</span>, <span class='st'>"children"</span><span class='op'>)</span> | ||||
| <span class='co'># same:</span> | ||||
| <span class='fu'>age_groups</span><span class='op'>(</span><span class='va'>ages</span>, <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='fl'>1</span>, <span class='fl'>2</span>, <span class='fl'>4</span>, <span class='fl'>6</span>, <span class='fl'>13</span>, <span class='fl'>17</span><span class='op'>)</span><span class='op'>)</span> | ||||
| <span class='fu'>age_groups</span><span class='op'>(</span><span class='va'>ages</span>, <span class='st'>"children"</span><span class='op'>)</span> | ||||
|  | ||||
| <span class='co'># \donttest{</span> | ||||
| <span class='co'># resistance of ciprofloxacine per age group</span> | ||||
| <span class='co'># resistance of ciprofloxacin per age group</span> | ||||
| <span class='kw'><a href='https://rdrr.io/r/base/library.html'>library</a></span><span class='op'>(</span><span class='va'><a href='https://dplyr.tidyverse.org'>dplyr</a></span><span class='op'>)</span> | ||||
| <span class='va'>example_isolates</span> <span class='op'>%>%</span> | ||||
|   <span class='fu'><a href='first_isolate.html'>filter_first_isolate</a></span><span class='op'>(</span><span class='op'>)</span> <span class='op'>%>%</span> | ||||
|   | ||||
| @@ -82,7 +82,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
| @@ -315,7 +315,7 @@ | ||||
|      | ||||
|   <span class='co'># get bug/drug combinations for only macrolides in Gram-positives:</span> | ||||
|   <span class='va'>example_isolates</span> <span class='op'>%>%</span>  | ||||
|     <span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span><span class='op'>(</span><span class='fu'><a href='mo_property.html'>mo_gramstain</a></span><span class='op'>(</span><span class='va'>mo</span><span class='op'>)</span> <span class='op'>%like%</span> <span class='st'>"pos"</span><span class='op'>)</span> <span class='op'>%>%</span>  | ||||
|     <span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span><span class='op'>(</span><span class='va'>mo</span> <span class='op'>%>%</span> <span class='fu'><a href='mo_property.html'>is_gram_positive</a></span><span class='op'>(</span><span class='op'>)</span><span class='op'>)</span> <span class='op'>%>%</span>  | ||||
|     <span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span><span class='op'>(</span><span class='va'>mo</span>, <span class='fu'>macrolides</span><span class='op'>(</span><span class='op'>)</span><span class='op'>)</span> <span class='op'>%>%</span>  | ||||
|     <span class='fu'><a href='bug_drug_combinations.html'>bug_drug_combinations</a></span><span class='op'>(</span><span class='op'>)</span> <span class='op'>%>%</span> | ||||
|     <span class='fu'><a href='https://rdrr.io/r/base/format.html'>format</a></span><span class='op'>(</span><span class='op'>)</span> | ||||
|   | ||||
| @@ -82,7 +82,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
| @@ -311,7 +311,7 @@ | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>uti</th> | ||||
|       <td><p>(Urinary Tract Infection) A vector with <a href='https://rdrr.io/r/base/logical.html'>logical</a>s (<code>TRUE</code> or <code>FALSE</code>) to specify whether a UTI specific interpretation from the guideline should be chosen. For using <code>as.rsi()</code> on a <a href='https://rdrr.io/r/base/data.frame.html'>data.frame</a>, this can also be a column containing <a href='https://rdrr.io/r/base/logical.html'>logical</a>s or when left blank, the data set will be search for a 'specimen' and rows containing 'urin' in that column will be regarded isolates from a UTI. See <em>Examples</em>.</p></td> | ||||
|       <td><p>(Urinary Tract Infection) A vector with <a href='https://rdrr.io/r/base/logical.html'>logical</a>s (<code>TRUE</code> or <code>FALSE</code>) to specify whether a UTI specific interpretation from the guideline should be chosen. For using <code>as.rsi()</code> on a <a href='https://rdrr.io/r/base/data.frame.html'>data.frame</a>, this can also be a column containing <a href='https://rdrr.io/r/base/logical.html'>logical</a>s or when left blank, the data set will be searched for a 'specimen' and rows containing 'urin' (such as 'urine', 'urina') in that column will be regarded isolates from a UTI. See <em>Examples</em>.</p></td> | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>conserve_capped_values</th> | ||||
|   | ||||
| @@ -82,7 +82,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
| @@ -272,7 +272,7 @@ | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>FUN</th> | ||||
|       <td><p>the function to call on the <code>mo</code> column to transform the microorganism IDs, defaults to <code><a href='mo_property.html'>mo_shortname()</a></code></p></td> | ||||
|       <td><p>function to call on the <code>mo</code> column to transform the microorganism IDs, defaults to <code><a href='mo_property.html'>mo_shortname()</a></code></p></td> | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>...</th> | ||||
| @@ -280,7 +280,7 @@ | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>translate_ab</th> | ||||
|       <td><p>a character of length 1 containing column names of the <a href='antibiotics.html'>antibiotics</a> data set</p></td> | ||||
|       <td><p>character of length 1 containing column names of the <a href='antibiotics.html'>antibiotics</a> data set</p></td> | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>language</th> | ||||
|   | ||||
| @@ -82,7 +82,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
| @@ -242,30 +242,30 @@ | ||||
|     <p>Produces a <code>ggplot2</code> variant of a so-called <a href='https://en.wikipedia.org/wiki/Biplot'>biplot</a> for PCA (principal component analysis), but is more flexible and more appealing than the base <span style="R">R</span> <code><a href='https://rdrr.io/r/stats/biplot.html'>biplot()</a></code> function.</p> | ||||
|     </div> | ||||
|  | ||||
|     <pre class="usage"><span class='fu'>ggplot_pca</span>( | ||||
|   <span class='kw'>x</span>, | ||||
|   choices = <span class='fl'>1</span><span class='op'>:</span><span class='fl'>2</span>, | ||||
|   scale = <span class='fl'>TRUE</span>, | ||||
|   pc.biplot = <span class='fl'>TRUE</span>, | ||||
|   labels = <span class='kw'>NULL</span>, | ||||
|   labels_textsize = <span class='fl'>3</span>, | ||||
|   labels_text_placement = <span class='fl'>1.5</span>, | ||||
|   groups = <span class='kw'>NULL</span>, | ||||
|   ellipse = <span class='fl'>TRUE</span>, | ||||
|   ellipse_prob = <span class='fl'>0.68</span>, | ||||
|   ellipse_size = <span class='fl'>0.5</span>, | ||||
|   ellipse_alpha = <span class='fl'>0.5</span>, | ||||
|   points_size = <span class='fl'>2</span>, | ||||
|   points_alpha = <span class='fl'>0.25</span>, | ||||
|   arrows = <span class='fl'>TRUE</span>, | ||||
|   arrows_colour = <span class='st'>"darkblue"</span>, | ||||
|   arrows_size = <span class='fl'>0.5</span>, | ||||
|   arrows_textsize = <span class='fl'>3</span>, | ||||
|   arrows_textangled = <span class='fl'>TRUE</span>, | ||||
|   arrows_alpha = <span class='fl'>0.75</span>, | ||||
|   base_textsize = <span class='fl'>10</span>, | ||||
|   <span class='kw'>...</span> | ||||
| )</pre> | ||||
|     <pre class="usage"><span class='fu'>ggplot_pca</span><span class='op'>(</span> | ||||
|   <span class='va'>x</span>, | ||||
|   choices <span class='op'>=</span> <span class='fl'>1</span><span class='op'>:</span><span class='fl'>2</span>, | ||||
|   scale <span class='op'>=</span> <span class='fl'>1</span>, | ||||
|   pc.biplot <span class='op'>=</span> <span class='cn'>TRUE</span>, | ||||
|   labels <span class='op'>=</span> <span class='cn'>NULL</span>, | ||||
|   labels_textsize <span class='op'>=</span> <span class='fl'>3</span>, | ||||
|   labels_text_placement <span class='op'>=</span> <span class='fl'>1.5</span>, | ||||
|   groups <span class='op'>=</span> <span class='cn'>NULL</span>, | ||||
|   ellipse <span class='op'>=</span> <span class='cn'>TRUE</span>, | ||||
|   ellipse_prob <span class='op'>=</span> <span class='fl'>0.68</span>, | ||||
|   ellipse_size <span class='op'>=</span> <span class='fl'>0.5</span>, | ||||
|   ellipse_alpha <span class='op'>=</span> <span class='fl'>0.5</span>, | ||||
|   points_size <span class='op'>=</span> <span class='fl'>2</span>, | ||||
|   points_alpha <span class='op'>=</span> <span class='fl'>0.25</span>, | ||||
|   arrows <span class='op'>=</span> <span class='cn'>TRUE</span>, | ||||
|   arrows_colour <span class='op'>=</span> <span class='st'>"darkblue"</span>, | ||||
|   arrows_size <span class='op'>=</span> <span class='fl'>0.5</span>, | ||||
|   arrows_textsize <span class='op'>=</span> <span class='fl'>3</span>, | ||||
|   arrows_textangled <span class='op'>=</span> <span class='cn'>TRUE</span>, | ||||
|   arrows_alpha <span class='op'>=</span> <span class='fl'>0.75</span>, | ||||
|   base_textsize <span class='op'>=</span> <span class='fl'>10</span>, | ||||
|   <span class='va'>...</span> | ||||
| <span class='op'>)</span></pre> | ||||
|  | ||||
|     <h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2> | ||||
|     <table class="ref-arguments"> | ||||
| @@ -375,8 +375,9 @@ | ||||
| <p>As per their GPL-2 licence that demands documentation of code changes, the changes made based on the source code were:</p><ol> | ||||
| <li><p>Rewritten code to remove the dependency on packages <code>plyr</code>, <code>scales</code> and <code>grid</code></p></li> | ||||
| <li><p>Parametrised more options, like arrow and ellipse settings</p></li> | ||||
| <li><p>Hardened all input possibilities by defining the exact type of user input for every parameter</p></li> | ||||
| <li><p>Added total amount of explained variance as a caption in the plot</p></li> | ||||
| <li><p>Cleaned all syntax based on the <code>lintr</code> package and added integrity checks</p></li> | ||||
| <li><p>Cleaned all syntax based on the <code>lintr</code> package, fixed grammatical errors and added integrity checks</p></li> | ||||
| <li><p>Updated documentation</p></li> | ||||
| </ol> | ||||
|  | ||||
| @@ -395,25 +396,25 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>maturing< | ||||
| <span class='co'># See ?example_isolates.</span> | ||||
|  | ||||
| <span class='co'># See ?pca for more info about Principal Component Analysis (PCA).</span> | ||||
| <span class='co'>if</span> (<span class='fu'><a href='https://rdrr.io/r/base/library.html'>require</a></span>(<span class='st'><a href='https://dplyr.tidyverse.org'>"dplyr"</a></span>)) { | ||||
|   <span class='kw'>pca_model</span> <span class='op'><-</span> <span class='kw'>example_isolates</span> <span class='op'>%>%</span>  | ||||
|     <span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span>(<span class='fu'><a href='mo_property.html'>mo_genus</a></span>(<span class='kw'>mo</span>) <span class='op'>==</span> <span class='st'>"Staphylococcus"</span>) <span class='op'>%>%</span>  | ||||
|     <span class='fu'><a href='https://dplyr.tidyverse.org/reference/group_by.html'>group_by</a></span>(species = <span class='fu'><a href='mo_property.html'>mo_shortname</a></span>(<span class='kw'>mo</span>)) <span class='op'>%>%</span> | ||||
|     <span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise_all.html'>summarise_if</a></span> (<span class='kw'>is.rsi</span>, <span class='kw'>resistance</span>) <span class='op'>%>%</span> | ||||
|     <span class='fu'><a href='pca.html'>pca</a></span>(<span class='kw'>FLC</span>, <span class='kw'>AMC</span>, <span class='kw'>CXM</span>, <span class='kw'>GEN</span>, <span class='kw'>TOB</span>, <span class='kw'>TMP</span>, <span class='kw'>SXT</span>, <span class='kw'>CIP</span>, <span class='kw'>TEC</span>, <span class='kw'>TCY</span>, <span class='kw'>ERY</span>) | ||||
| <span class='kw'>if</span> <span class='op'>(</span><span class='kw'><a href='https://rdrr.io/r/base/library.html'>require</a></span><span class='op'>(</span><span class='st'><a href='https://dplyr.tidyverse.org'>"dplyr"</a></span><span class='op'>)</span><span class='op'>)</span> <span class='op'>{</span> | ||||
|   <span class='va'>pca_model</span> <span class='op'><-</span> <span class='va'>example_isolates</span> <span class='op'>%>%</span>  | ||||
|     <span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span><span class='op'>(</span><span class='fu'><a href='mo_property.html'>mo_genus</a></span><span class='op'>(</span><span class='va'>mo</span><span class='op'>)</span> <span class='op'>==</span> <span class='st'>"Staphylococcus"</span><span class='op'>)</span> <span class='op'>%>%</span>  | ||||
|     <span class='fu'><a href='https://dplyr.tidyverse.org/reference/group_by.html'>group_by</a></span><span class='op'>(</span>species <span class='op'>=</span> <span class='fu'><a href='mo_property.html'>mo_shortname</a></span><span class='op'>(</span><span class='va'>mo</span><span class='op'>)</span><span class='op'>)</span> <span class='op'>%>%</span> | ||||
|     <span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise_all.html'>summarise_if</a></span> <span class='op'>(</span><span class='va'>is.rsi</span>, <span class='va'>resistance</span><span class='op'>)</span> <span class='op'>%>%</span> | ||||
|     <span class='fu'><a href='pca.html'>pca</a></span><span class='op'>(</span><span class='va'>FLC</span>, <span class='va'>AMC</span>, <span class='va'>CXM</span>, <span class='va'>GEN</span>, <span class='va'>TOB</span>, <span class='va'>TMP</span>, <span class='va'>SXT</span>, <span class='va'>CIP</span>, <span class='va'>TEC</span>, <span class='va'>TCY</span>, <span class='va'>ERY</span><span class='op'>)</span> | ||||
|      | ||||
|   <span class='co'># old (base R)</span> | ||||
|   <span class='fu'><a href='https://rdrr.io/r/stats/biplot.html'>biplot</a></span>(<span class='kw'>pca_model</span>) | ||||
|   <span class='fu'><a href='https://rdrr.io/r/stats/biplot.html'>biplot</a></span><span class='op'>(</span><span class='va'>pca_model</span><span class='op'>)</span> | ||||
|    | ||||
|   <span class='co'># new </span> | ||||
|   <span class='fu'>ggplot_pca</span>(<span class='kw'>pca_model</span>) | ||||
|   <span class='fu'>ggplot_pca</span><span class='op'>(</span><span class='va'>pca_model</span><span class='op'>)</span> | ||||
|    | ||||
|   <span class='co'>if</span> (<span class='fu'><a href='https://rdrr.io/r/base/library.html'>require</a></span>(<span class='st'><a href='http://ggplot2.tidyverse.org'>"ggplot2"</a></span>)) { | ||||
|     <span class='fu'>ggplot_pca</span>(<span class='kw'>pca_model</span>) <span class='op'>+</span> | ||||
|       <span class='fu'><a href='https://ggplot2.tidyverse.org/reference/scale_viridis.html'>scale_colour_viridis_d</a></span>() <span class='op'>+</span> | ||||
|       <span class='fu'><a href='https://ggplot2.tidyverse.org/reference/labs.html'>labs</a></span>(title = <span class='st'>"Title here"</span>) | ||||
|   } | ||||
| } | ||||
|   <span class='kw'>if</span> <span class='op'>(</span><span class='kw'><a href='https://rdrr.io/r/base/library.html'>require</a></span><span class='op'>(</span><span class='st'><a href='http://ggplot2.tidyverse.org'>"ggplot2"</a></span><span class='op'>)</span><span class='op'>)</span> <span class='op'>{</span> | ||||
|     <span class='fu'>ggplot_pca</span><span class='op'>(</span><span class='va'>pca_model</span><span class='op'>)</span> <span class='op'>+</span> | ||||
|       <span class='fu'><a href='https://ggplot2.tidyverse.org/reference/scale_viridis.html'>scale_colour_viridis_d</a></span><span class='op'>(</span><span class='op'>)</span> <span class='op'>+</span> | ||||
|       <span class='fu'><a href='https://ggplot2.tidyverse.org/reference/labs.html'>labs</a></span><span class='op'>(</span>title <span class='op'>=</span> <span class='st'>"Title here"</span><span class='op'>)</span> | ||||
|   <span class='op'>}</span> | ||||
| <span class='op'>}</span> | ||||
| </pre> | ||||
|   </div> | ||||
|   <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> | ||||
| @@ -430,7 +431,7 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>maturing< | ||||
| </div> | ||||
|  | ||||
| <div class="pkgdown"> | ||||
|   <p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.5.1.9000.</p> | ||||
|   <p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.6.1.</p> | ||||
| </div> | ||||
|  | ||||
|       </footer> | ||||
|   | ||||
| @@ -82,7 +82,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
| @@ -266,7 +266,7 @@ | ||||
|     <p>A column name of <code>x</code>, or <code>NULL</code> when no result is found.</p> | ||||
|     <h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2> | ||||
|  | ||||
|     <p>You can look for an antibiotic (trade) name or abbreviation and it will search <code>x</code> and the <a href='antibiotics.html'>antibiotics</a> data set for any column containing a name or code of that antibiotic. <strong>Longer columns names take precendence over shorter column names.</strong></p> | ||||
|     <p>You can look for an antibiotic (trade) name or abbreviation and it will search <code>x</code> and the <a href='antibiotics.html'>antibiotics</a> data set for any column containing a name or code of that antibiotic. <strong>Longer columns names take precedence over shorter column names.</strong></p> | ||||
|     <h2 class="hasAnchor" id="stable-lifecycle"><a class="anchor" href="#stable-lifecycle"></a>Stable lifecycle</h2> | ||||
|  | ||||
|      | ||||
|   | ||||
| @@ -81,7 +81,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
| @@ -361,7 +361,7 @@ | ||||
|       </tr><tr> | ||||
|          | ||||
|         <td> | ||||
|           <p><code><a href="mo_property.html">mo_name()</a></code> <code><a href="mo_property.html">mo_fullname()</a></code> <code><a href="mo_property.html">mo_shortname()</a></code> <code><a href="mo_property.html">mo_subspecies()</a></code> <code><a href="mo_property.html">mo_species()</a></code> <code><a href="mo_property.html">mo_genus()</a></code> <code><a href="mo_property.html">mo_family()</a></code> <code><a href="mo_property.html">mo_order()</a></code> <code><a href="mo_property.html">mo_class()</a></code> <code><a href="mo_property.html">mo_phylum()</a></code> <code><a href="mo_property.html">mo_kingdom()</a></code> <code><a href="mo_property.html">mo_domain()</a></code> <code><a href="mo_property.html">mo_type()</a></code> <code><a href="mo_property.html">mo_gramstain()</a></code> <code><a href="mo_property.html">mo_snomed()</a></code> <code><a href="mo_property.html">mo_ref()</a></code> <code><a href="mo_property.html">mo_authors()</a></code> <code><a href="mo_property.html">mo_year()</a></code> <code><a href="mo_property.html">mo_rank()</a></code> <code><a href="mo_property.html">mo_taxonomy()</a></code> <code><a href="mo_property.html">mo_synonyms()</a></code> <code><a href="mo_property.html">mo_info()</a></code> <code><a href="mo_property.html">mo_url()</a></code> <code><a href="mo_property.html">mo_property()</a></code> </p> | ||||
|           <p><code><a href="mo_property.html">mo_name()</a></code> <code><a href="mo_property.html">mo_fullname()</a></code> <code><a href="mo_property.html">mo_shortname()</a></code> <code><a href="mo_property.html">mo_subspecies()</a></code> <code><a href="mo_property.html">mo_species()</a></code> <code><a href="mo_property.html">mo_genus()</a></code> <code><a href="mo_property.html">mo_family()</a></code> <code><a href="mo_property.html">mo_order()</a></code> <code><a href="mo_property.html">mo_class()</a></code> <code><a href="mo_property.html">mo_phylum()</a></code> <code><a href="mo_property.html">mo_kingdom()</a></code> <code><a href="mo_property.html">mo_domain()</a></code> <code><a href="mo_property.html">mo_type()</a></code> <code><a href="mo_property.html">mo_gramstain()</a></code> <code><a href="mo_property.html">is_gram_negative()</a></code> <code><a href="mo_property.html">is_gram_positive()</a></code> <code><a href="mo_property.html">mo_snomed()</a></code> <code><a href="mo_property.html">mo_ref()</a></code> <code><a href="mo_property.html">mo_authors()</a></code> <code><a href="mo_property.html">mo_year()</a></code> <code><a href="mo_property.html">mo_rank()</a></code> <code><a href="mo_property.html">mo_taxonomy()</a></code> <code><a href="mo_property.html">mo_synonyms()</a></code> <code><a href="mo_property.html">mo_info()</a></code> <code><a href="mo_property.html">mo_url()</a></code> <code><a href="mo_property.html">mo_property()</a></code> </p> | ||||
|         </td> | ||||
|         <td><p>Get properties of a microorganism</p></td> | ||||
|       </tr><tr> | ||||
| @@ -630,9 +630,9 @@ | ||||
|       </tr><tr> | ||||
|          | ||||
|         <td> | ||||
|           <p><code><a href="p_symbol.html">p_symbol()</a></code> </p> | ||||
|           <p><code><a href="AMR-deprecated.html">p_symbol()</a></code> </p> | ||||
|         </td> | ||||
|         <td><p>Symbol of a p-value</p></td> | ||||
|         <td><p>Deprecated functions</p></td> | ||||
|       </tr> | ||||
|     </tbody> | ||||
|     </table> | ||||
|   | ||||
| @@ -82,7 +82,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
| @@ -281,7 +281,7 @@ | ||||
|     <colgroup><col class="name" /><col class="desc" /></colgroup> | ||||
|     <tr> | ||||
|       <th>x</th> | ||||
|       <td><p>table with antibiotics coloms, like <code>AMX</code> or <code>amox</code></p></td> | ||||
|       <td><p>a data.frame with antibiotics columns, like <code>AMX</code> or <code>amox</code></p></td> | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>col_mo</th> | ||||
| @@ -289,27 +289,27 @@ | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>universal_1, universal_2, universal_3, universal_4, universal_5, universal_6</th> | ||||
|       <td><p>column names of <strong>broad-spectrum</strong> antibiotics, case-insensitive. At default, the columns containing these antibiotics will be guessed with <code><a href='guess_ab_col.html'>guess_ab_col()</a></code>.</p></td> | ||||
|       <td><p>column names of <strong>broad-spectrum</strong> antibiotics, case-insensitive. See details for which antibiotics will be used at default (which are guessed with <code><a href='guess_ab_col.html'>guess_ab_col()</a></code>).</p></td> | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>GramPos_1, GramPos_2, GramPos_3, GramPos_4, GramPos_5, GramPos_6</th> | ||||
|       <td><p>column names of antibiotics for <strong>Gram-positives</strong>, case-insensitive. At default, the columns containing these antibiotics will be guessed with <code><a href='guess_ab_col.html'>guess_ab_col()</a></code>.</p></td> | ||||
|       <td><p>column names of antibiotics for <strong>Gram-positives</strong>, case-insensitive. See details for which antibiotics will be used at default (which are guessed with <code><a href='guess_ab_col.html'>guess_ab_col()</a></code>).</p></td> | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>GramNeg_1, GramNeg_2, GramNeg_3, GramNeg_4, GramNeg_5, GramNeg_6</th> | ||||
|       <td><p>column names of antibiotics for <strong>Gram-negatives</strong>, case-insensitive. At default, the columns containing these antibiotics will be guessed with <code><a href='guess_ab_col.html'>guess_ab_col()</a></code>.</p></td> | ||||
|       <td><p>column names of antibiotics for <strong>Gram-negatives</strong>, case-insensitive. See details for which antibiotics will be used at default (which are guessed with <code><a href='guess_ab_col.html'>guess_ab_col()</a></code>).</p></td> | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>warnings</th> | ||||
|       <td><p>give warning about missing antibiotic columns, they will anyway be ignored</p></td> | ||||
|       <td><p>give a warning about missing antibiotic columns (they will be ignored)</p></td> | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>...</th> | ||||
|       <td><p>other parameters passed on to function</p></td> | ||||
|       <td><p>other parameters passed on to functions</p></td> | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>y, z</th> | ||||
|       <td><p>characters to compare</p></td> | ||||
|       <td><p>character vectors to compare</p></td> | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>type</th> | ||||
|   | ||||
| @@ -82,7 +82,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
| @@ -270,6 +270,10 @@ | ||||
|  | ||||
| <span class='fu'>mo_gramstain</span><span class='op'>(</span><span class='va'>x</span>, language <span class='op'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span><span class='op'>(</span><span class='op'>)</span>, <span class='va'>...</span><span class='op'>)</span> | ||||
|  | ||||
| <span class='fu'>is_gram_negative</span><span class='op'>(</span><span class='va'>x</span>, <span class='va'>...</span><span class='op'>)</span> | ||||
|  | ||||
| <span class='fu'>is_gram_positive</span><span class='op'>(</span><span class='va'>x</span>, <span class='va'>...</span><span class='op'>)</span> | ||||
|  | ||||
| <span class='fu'>mo_snomed</span><span class='op'>(</span><span class='va'>x</span>, language <span class='op'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span><span class='op'>(</span><span class='op'>)</span>, <span class='va'>...</span><span class='op'>)</span> | ||||
|  | ||||
| <span class='fu'>mo_ref</span><span class='op'>(</span><span class='va'>x</span>, language <span class='op'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span><span class='op'>(</span><span class='op'>)</span>, <span class='va'>...</span><span class='op'>)</span> | ||||
| @@ -295,7 +299,7 @@ | ||||
|     <colgroup><col class="name" /><col class="desc" /></colgroup> | ||||
|     <tr> | ||||
|       <th>x</th> | ||||
|       <td><p>any (vector of) text that can be coerced to a valid microorganism code with <code><a href='as.mo.html'>as.mo()</a></code></p></td> | ||||
|       <td><p>any character (vector) that can be coerced to a valid microorganism code with <code><a href='as.mo.html'>as.mo()</a></code></p></td> | ||||
|     </tr> | ||||
|     <tr> | ||||
|       <th>language</th> | ||||
| @@ -336,7 +340,7 @@ | ||||
|  | ||||
| <p>The short name - <code>mo_shortname()</code> - almost always returns the first character of the genus and the full species, like <code>"E. coli"</code>. Exceptions are abbreviations of staphylococci (like <em>"CoNS"</em>, Coagulase-Negative Staphylococci) and beta-haemolytic streptococci (like <em>"GBS"</em>, Group B Streptococci). Please bear in mind that e.g. <em>E. coli</em> could mean <em>Escherichia coli</em> (kingdom of Bacteria) as well as <em>Entamoeba coli</em> (kingdom of Protozoa). Returning to the full name will be done using <code><a href='as.mo.html'>as.mo()</a></code> internally, giving priority to bacteria and human pathogens, i.e. <code>"E. coli"</code> will be considered <em>Escherichia coli</em>. In other words, <code>mo_fullname(mo_shortname("Entamoeba coli"))</code> returns <code>"Escherichia coli"</code>.</p> | ||||
| <p>Since the top-level of the taxonomy is sometimes referred to as 'kingdom' and sometimes as 'domain', the functions <code>mo_kingdom()</code> and <code>mo_domain()</code> return the exact same results.</p> | ||||
| <p>The Gram stain - <code>mo_gramstain()</code> - will be determined based on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002, <a href='https://pubmed.ncbi.nlm.nih.gov/11837318'>PMID 11837318</a>), who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value <code>NA</code>.</p> | ||||
| <p>The Gram stain - <code>mo_gramstain()</code> - will be determined based on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002, <a href='https://pubmed.ncbi.nlm.nih.gov/11837318'>PMID 11837318</a>), who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value <code>NA</code>. Functions <code>is_gram_negative()</code> and <code>is_gram_positive()</code> always return <code>TRUE</code> or <code>FALSE</code>, even for species outside the kingdom of Bacteria.</p> | ||||
| <p>All output will be <a href='translate.html'>translate</a>d where possible.</p> | ||||
| <p>The function <code>mo_url()</code> will return the direct URL to the online database entry, which also shows the scientific reference of the concerned species.</p> | ||||
|     <h2 class="hasAnchor" id="stable-lifecycle"><a class="anchor" href="#stable-lifecycle"></a>Stable lifecycle</h2> | ||||
|   | ||||
| @@ -82,7 +82,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="../index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
|   | ||||
| @@ -3,6 +3,9 @@ | ||||
|   <url> | ||||
|     <loc>https://msberends.github.io/AMR//index.html</loc> | ||||
|   </url> | ||||
|   <url> | ||||
|     <loc>https://msberends.github.io/AMR//reference/AMR-deprecated.html</loc> | ||||
|   </url> | ||||
|   <url> | ||||
|     <loc>https://msberends.github.io/AMR//reference/AMR.html</loc> | ||||
|   </url> | ||||
| @@ -129,9 +132,6 @@ | ||||
|   <url> | ||||
|     <loc>https://msberends.github.io/AMR//reference/mo_source.html</loc> | ||||
|   </url> | ||||
|   <url> | ||||
|     <loc>https://msberends.github.io/AMR//reference/p_symbol.html</loc> | ||||
|   </url> | ||||
|   <url> | ||||
|     <loc>https://msberends.github.io/AMR//reference/pca.html</loc> | ||||
|   </url> | ||||
|   | ||||
| @@ -81,7 +81,7 @@ | ||||
|       </button> | ||||
|       <span class="navbar-brand"> | ||||
|         <a class="navbar-link" href="index.html">AMR (for R)</a> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9000</span> | ||||
|         <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.4.0.9001</span> | ||||
|       </span> | ||||
|     </div> | ||||
|  | ||||
|   | ||||
							
								
								
									
										24
									
								
								man/AMR-deprecated.Rd
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										24
									
								
								man/AMR-deprecated.Rd
									
									
									
									
									
										Normal file
									
								
							| @@ -0,0 +1,24 @@ | ||||
| % Generated by roxygen2: do not edit by hand | ||||
| % Please edit documentation in R/deprecated.R | ||||
| \name{AMR-deprecated} | ||||
| \alias{AMR-deprecated} | ||||
| \alias{p_symbol} | ||||
| \title{Deprecated functions} | ||||
| \usage{ | ||||
| p_symbol(p, emptychar = " ") | ||||
| } | ||||
| \description{ | ||||
| These functions are so-called '\link{Deprecated}'. They will be removed in a future release. Using the functions will give a warning with the name of the function it has been replaced by (if there is one). | ||||
| } | ||||
| \section{Retired lifecycle}{ | ||||
|  | ||||
| \if{html}{\figure{lifecycle_retired.svg}{options: style=margin-bottom:5px} \cr} | ||||
| The \link[=lifecycle]{lifecycle} of this function is \strong{retired}. A retired function is no longer under active development, and (if appropiate) a better alternative is available. No new arguments will be added, and only the most critical bugs will be fixed. In a future version, this function will be removed. | ||||
| } | ||||
|  | ||||
| \section{Read more on our website!}{ | ||||
|  | ||||
| On our website \url{https://msberends.github.io/AMR/} you can find \href{https://msberends.github.io/AMR/articles/AMR.html}{a comprehensive tutorial} about how to conduct AMR analysis, the \href{https://msberends.github.io/AMR/reference/}{complete documentation of all functions} and \href{https://msberends.github.io/AMR/articles/WHONET.html}{an example analysis using WHONET data}. As we would like to better understand the backgrounds and needs of our users, please \href{https://msberends.github.io/AMR/survey.html}{participate in our survey}! | ||||
| } | ||||
|  | ||||
| \keyword{internal} | ||||
| @@ -4,16 +4,18 @@ | ||||
| \alias{age} | ||||
| \title{Age in years of individuals} | ||||
| \usage{ | ||||
| age(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE) | ||||
| age(x, reference = Sys.Date(), exact = FALSE, na.rm = FALSE, ...) | ||||
| } | ||||
| \arguments{ | ||||
| \item{x}{date(s), will be coerced with \code{\link[=as.POSIXlt]{as.POSIXlt()}}} | ||||
|  | ||||
| \item{reference}{reference date(s) (defaults to today), will be coerced with \code{\link[=as.POSIXlt]{as.POSIXlt()}} and cannot be lower than \code{x}} | ||||
| \item{reference}{reference date(s) (defaults to today), will be coerced with \code{\link[=as.POSIXlt]{as.POSIXlt()}}} | ||||
|  | ||||
| \item{exact}{a logical to indicate whether age calculation should be exact, i.e. with decimals. It divides the number of days of \href{https://en.wikipedia.org/wiki/Year-to-date}{year-to-date} (YTD) of \code{x} by the number of days in the year of \code{reference} (either 365 or 366).} | ||||
|  | ||||
| \item{na.rm}{a logical to indicate whether missing values should be removed} | ||||
|  | ||||
| \item{...}{parameters passed on to \code{\link[=as.POSIXlt]{as.POSIXlt()}}, such as \code{origin}} | ||||
| } | ||||
| \value{ | ||||
| An \link{integer} (no decimals) if \code{exact = FALSE}, a \link{double} (with decimals) otherwise | ||||
| @@ -21,6 +23,9 @@ An \link{integer} (no decimals) if \code{exact = FALSE}, a \link{double} (with d | ||||
| \description{ | ||||
| Calculates age in years based on a reference date, which is the sytem date at default. | ||||
| } | ||||
| \details{ | ||||
| Ages below 0 will be returned as \code{NA} with a warning. Ages above 120 will only give a warning. | ||||
| } | ||||
| \section{Stable lifecycle}{ | ||||
|  | ||||
| \if{html}{\figure{lifecycle_stable.svg}{options: style=margin-bottom:5px} \cr} | ||||
|   | ||||
| @@ -22,14 +22,14 @@ Split ages into age groups defined by the \code{split} parameter. This allows fo | ||||
| \details{ | ||||
| To split ages, the input for the \code{split_at} parameter can be: | ||||
| \itemize{ | ||||
| \item A numeric vector. A vector of e.g. \code{c(10, 20)} will split on 0-9, 10-19 and 20+. A value of only \code{50} will split on 0-49 and 50+. | ||||
| \item A numeric vector. A value of e.g. \code{c(10, 20)} will split \code{x} on 0-9, 10-19 and 20+. A value of only \code{50} will split \code{x} on 0-49 and 50+. | ||||
| The default is to split on young children (0-11), youth (12-24), young adults (25-54), middle-aged adults (55-74) and elderly (75+). | ||||
| \item A character: | ||||
| \itemize{ | ||||
| \item \code{"children"} or \code{"kids"}, equivalent of: \code{c(0, 1, 2, 4, 6, 13, 18)}. This will split on 0, 1, 2-3, 4-5, 6-12, 13-17 and 18+. | ||||
| \item \code{"elderly"} or \code{"seniors"}, equivalent of: \code{c(65, 75, 85)}. This will split on 0-64, 65-74, 75-84, 85+. | ||||
| \item \code{"fives"}, equivalent of: \code{1:20 * 5}. This will split on 0-4, 5-9, 10-14, ..., 90-94, 95-99, 100+. | ||||
| \item \code{"tens"}, equivalent of: \code{1:10 * 10}. This will split on 0-9, 10-19, 20-29, ..., 80-89, 90-99, 100+. | ||||
| \item \code{"fives"}, equivalent of: \code{1:20 * 5}. This will split on 0-4, 5-9, ..., 95-99, 100+. | ||||
| \item \code{"tens"}, equivalent of: \code{1:10 * 10}. This will split on 0-9, 10-19, ..., 90-99, 100+. | ||||
| } | ||||
| } | ||||
| } | ||||
| @@ -64,12 +64,11 @@ age_groups(ages, 1:20 * 5) | ||||
| age_groups(ages, split_at = "fives") | ||||
|  | ||||
| # split specifically for children | ||||
| age_groups(ages, "children") | ||||
| # same: | ||||
| age_groups(ages, c(1, 2, 4, 6, 13, 17)) | ||||
| age_groups(ages, "children") | ||||
|  | ||||
| \donttest{ | ||||
| # resistance of ciprofloxacine per age group | ||||
| # resistance of ciprofloxacin per age group | ||||
| library(dplyr) | ||||
| example_isolates \%>\% | ||||
|   filter_first_isolate() \%>\% | ||||
|   | ||||
| @@ -85,7 +85,7 @@ if (require("dplyr")) { | ||||
|      | ||||
|   # get bug/drug combinations for only macrolides in Gram-positives: | ||||
|   example_isolates \%>\%  | ||||
|     filter(mo_gramstain(mo) \%like\% "pos") \%>\%  | ||||
|     filter(mo \%>\% is_gram_positive()) \%>\%  | ||||
|     select(mo, macrolides()) \%>\%  | ||||
|     bug_drug_combinations() \%>\% | ||||
|     format() | ||||
|   | ||||
| @@ -60,7 +60,7 @@ is.rsi.eligible(x, threshold = 0.05) | ||||
|  | ||||
| \item{guideline}{defaults to the latest included EUCAST guideline, see Details for all options} | ||||
|  | ||||
| \item{uti}{(Urinary Tract Infection) A vector with \link{logical}s (\code{TRUE} or \code{FALSE}) to specify whether a UTI specific interpretation from the guideline should be chosen. For using \code{\link[=as.rsi]{as.rsi()}} on a \link{data.frame}, this can also be a column containing \link{logical}s or when left blank, the data set will be search for a 'specimen' and rows containing 'urin' in that column will be regarded isolates from a UTI. See \emph{Examples}.} | ||||
| \item{uti}{(Urinary Tract Infection) A vector with \link{logical}s (\code{TRUE} or \code{FALSE}) to specify whether a UTI specific interpretation from the guideline should be chosen. For using \code{\link[=as.rsi]{as.rsi()}} on a \link{data.frame}, this can also be a column containing \link{logical}s or when left blank, the data set will be searched for a 'specimen' and rows containing 'urin' (such as 'urine', 'urina') in that column will be regarded isolates from a UTI. See \emph{Examples}.} | ||||
|  | ||||
| \item{conserve_capped_values}{a logical to indicate that MIC values starting with \code{">"} (but not \code{">="}) must always return "R" , and that MIC values starting with \code{"<"} (but not \code{"<="}) must always return "S"} | ||||
|  | ||||
|   | ||||
| @@ -29,11 +29,11 @@ bug_drug_combinations(x, col_mo = NULL, FUN = mo_shortname, ...) | ||||
|  | ||||
| \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{FUN}{the function to call on the \code{mo} column to transform the microorganism IDs, defaults to \code{\link[=mo_shortname]{mo_shortname()}}} | ||||
| \item{FUN}{function to call on the \code{mo} column to transform the microorganism IDs, defaults to \code{\link[=mo_shortname]{mo_shortname()}}} | ||||
|  | ||||
| \item{...}{arguments passed on to \code{FUN}} | ||||
|  | ||||
| \item{translate_ab}{a character of length 1 containing column names of the \link{antibiotics} data set} | ||||
| \item{translate_ab}{character of length 1 containing column names of the \link{antibiotics} data set} | ||||
|  | ||||
| \item{language}{language of the returned text, defaults to system language (see \code{\link[=get_locale]{get_locale()}}) and can also be set with \code{getOption("AMR_locale")}. Use \code{language = NULL} or \code{language = ""} to prevent translation.} | ||||
|  | ||||
|   | ||||
| @@ -10,8 +10,9 @@ As per their GPL-2 licence that demands documentation of code changes, the chang | ||||
| \enumerate{ | ||||
| \item Rewritten code to remove the dependency on packages \code{plyr}, \code{scales} and \code{grid} | ||||
| \item Parametrised more options, like arrow and ellipse settings | ||||
| \item Hardened all input possibilities by defining the exact type of user input for every parameter | ||||
| \item Added total amount of explained variance as a caption in the plot | ||||
| \item Cleaned all syntax based on the \code{lintr} package and added integrity checks | ||||
| \item Cleaned all syntax based on the \code{lintr} package, fixed grammatical errors and added integrity checks | ||||
| \item Updated documentation | ||||
| } | ||||
| } | ||||
| @@ -19,7 +20,7 @@ As per their GPL-2 licence that demands documentation of code changes, the chang | ||||
| ggplot_pca( | ||||
|   x, | ||||
|   choices = 1:2, | ||||
|   scale = TRUE, | ||||
|   scale = 1, | ||||
|   pc.biplot = TRUE, | ||||
|   labels = NULL, | ||||
|   labels_textsize = 3, | ||||
|   | ||||
| @@ -20,7 +20,7 @@ A column name of \code{x}, or \code{NULL} when no result is found. | ||||
| This tries to find a column name in a data set based on information from the \link{antibiotics} data set. Also supports WHONET abbreviations. | ||||
| } | ||||
| \details{ | ||||
| You can look for an antibiotic (trade) name or abbreviation and it will search \code{x} and the \link{antibiotics} data set for any column containing a name or code of that antibiotic. \strong{Longer columns names take precendence over shorter column names.} | ||||
| You can look for an antibiotic (trade) name or abbreviation and it will search \code{x} and the \link{antibiotics} data set for any column containing a name or code of that antibiotic. \strong{Longer columns names take precedence over shorter column names.} | ||||
| } | ||||
| \section{Stable lifecycle}{ | ||||
|  | ||||
|   | ||||
| @@ -40,21 +40,21 @@ key_antibiotics_equal( | ||||
| ) | ||||
| } | ||||
| \arguments{ | ||||
| \item{x}{table with antibiotics coloms, like \code{AMX} or \code{amox}} | ||||
| \item{x}{a data.frame with antibiotics columns, like \code{AMX} or \code{amox}} | ||||
|  | ||||
| \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{universal_1, universal_2, universal_3, universal_4, universal_5, universal_6}{column names of \strong{broad-spectrum} antibiotics, case-insensitive. At default, the columns containing these antibiotics will be guessed with \code{\link[=guess_ab_col]{guess_ab_col()}}.} | ||||
| \item{universal_1, universal_2, universal_3, universal_4, universal_5, universal_6}{column names of \strong{broad-spectrum} antibiotics, case-insensitive. See details for which antibiotics will be used at default (which are guessed with \code{\link[=guess_ab_col]{guess_ab_col()}}).} | ||||
|  | ||||
| \item{GramPos_1, GramPos_2, GramPos_3, GramPos_4, GramPos_5, GramPos_6}{column names of antibiotics for \strong{Gram-positives}, case-insensitive. At default, the columns containing these antibiotics will be guessed with \code{\link[=guess_ab_col]{guess_ab_col()}}.} | ||||
| \item{GramPos_1, GramPos_2, GramPos_3, GramPos_4, GramPos_5, GramPos_6}{column names of antibiotics for \strong{Gram-positives}, case-insensitive. See details for which antibiotics will be used at default (which are guessed with \code{\link[=guess_ab_col]{guess_ab_col()}}).} | ||||
|  | ||||
| \item{GramNeg_1, GramNeg_2, GramNeg_3, GramNeg_4, GramNeg_5, GramNeg_6}{column names of antibiotics for \strong{Gram-negatives}, case-insensitive. At default, the columns containing these antibiotics will be guessed with \code{\link[=guess_ab_col]{guess_ab_col()}}.} | ||||
| \item{GramNeg_1, GramNeg_2, GramNeg_3, GramNeg_4, GramNeg_5, GramNeg_6}{column names of antibiotics for \strong{Gram-negatives}, case-insensitive. See details for which antibiotics will be used at default (which are guessed with \code{\link[=guess_ab_col]{guess_ab_col()}}).} | ||||
|  | ||||
| \item{warnings}{give warning about missing antibiotic columns, they will anyway be ignored} | ||||
| \item{warnings}{give a warning about missing antibiotic columns (they will be ignored)} | ||||
|  | ||||
| \item{...}{other parameters passed on to function} | ||||
| \item{...}{other parameters passed on to functions} | ||||
|  | ||||
| \item{y, z}{characters to compare} | ||||
| \item{y, z}{character vectors to compare} | ||||
|  | ||||
| \item{type}{type to determine weighed isolates; can be \code{"keyantibiotics"} or \code{"points"}, see Details} | ||||
|  | ||||
|   | ||||
| @@ -16,6 +16,8 @@ | ||||
| \alias{mo_domain} | ||||
| \alias{mo_type} | ||||
| \alias{mo_gramstain} | ||||
| \alias{is_gram_negative} | ||||
| \alias{is_gram_positive} | ||||
| \alias{mo_snomed} | ||||
| \alias{mo_ref} | ||||
| \alias{mo_authors} | ||||
| @@ -55,6 +57,10 @@ mo_type(x, language = get_locale(), ...) | ||||
|  | ||||
| mo_gramstain(x, language = get_locale(), ...) | ||||
|  | ||||
| is_gram_negative(x, ...) | ||||
|  | ||||
| is_gram_positive(x, ...) | ||||
|  | ||||
| mo_snomed(x, language = get_locale(), ...) | ||||
|  | ||||
| mo_ref(x, language = get_locale(), ...) | ||||
| @@ -76,7 +82,7 @@ mo_url(x, open = FALSE, language = get_locale(), ...) | ||||
| mo_property(x, property = "fullname", language = get_locale(), ...) | ||||
| } | ||||
| \arguments{ | ||||
| \item{x}{any (vector of) text that can be coerced to a valid microorganism code with \code{\link[=as.mo]{as.mo()}}} | ||||
| \item{x}{any character (vector) that can be coerced to a valid microorganism code with \code{\link[=as.mo]{as.mo()}}} | ||||
|  | ||||
| \item{language}{language of the returned text, defaults to system language (see \code{\link[=get_locale]{get_locale()}}) and can be overwritten by setting the option \code{AMR_locale}, e.g. \code{options(AMR_locale = "de")}, see \link{translate}. Use \code{language = NULL} or \code{language = ""} to prevent translation.} | ||||
|  | ||||
| @@ -110,7 +116,7 @@ The short name - \code{\link[=mo_shortname]{mo_shortname()}} - almost always ret | ||||
|  | ||||
| Since the top-level of the taxonomy is sometimes referred to as 'kingdom' and sometimes as 'domain', the functions \code{\link[=mo_kingdom]{mo_kingdom()}} and \code{\link[=mo_domain]{mo_domain()}} return the exact same results. | ||||
|  | ||||
| The Gram stain - \code{\link[=mo_gramstain]{mo_gramstain()}} - will be determined based on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002, \href{https://pubmed.ncbi.nlm.nih.gov/11837318}{PMID 11837318}), who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value \code{NA}. | ||||
| The Gram stain - \code{\link[=mo_gramstain]{mo_gramstain()}} - will be determined based on the taxonomic kingdom and phylum. According to Cavalier-Smith (2002, \href{https://pubmed.ncbi.nlm.nih.gov/11837318}{PMID 11837318}), who defined subkingdoms Negibacteria and Posibacteria, only these phyla are Posibacteria: Actinobacteria, Chloroflexi, Firmicutes and Tenericutes. These bacteria are considered Gram-positive - all other bacteria are considered Gram-negative. Species outside the kingdom of Bacteria will return a value \code{NA}. Functions \code{\link[=is_gram_negative]{is_gram_negative()}} and \code{\link[=is_gram_positive]{is_gram_positive()}} always return \code{TRUE} or \code{FALSE}, even for species outside the kingdom of Bacteria. | ||||
|  | ||||
| All output will be \link{translate}d where possible. | ||||
|  | ||||
|   | ||||
| @@ -1,33 +0,0 @@ | ||||
| % Generated by roxygen2: do not edit by hand | ||||
| % Please edit documentation in R/p_symbol.R | ||||
| \name{p_symbol} | ||||
| \alias{p_symbol} | ||||
| \title{Symbol of a p-value} | ||||
| \usage{ | ||||
| p_symbol(p, emptychar = " ") | ||||
| } | ||||
| \arguments{ | ||||
| \item{p}{p value} | ||||
|  | ||||
| \item{emptychar}{text to show when \code{p > 0.1}} | ||||
| } | ||||
| \value{ | ||||
| Text | ||||
| } | ||||
| \description{ | ||||
| Return the symbol related to the p-value: 0 '\verb{***}' 0.001 '\verb{**}' 0.01 '\code{*}' 0.05 '\code{.}' 0.1 ' ' 1. Values above \code{p = 1} will return \code{NA}. | ||||
| } | ||||
| \details{ | ||||
| \strong{NOTE}: this function will be moved to the \code{cleaner} package when a new version is being published on CRAN. | ||||
| } | ||||
| \section{Questioning lifecycle}{ | ||||
|  | ||||
| \if{html}{\figure{lifecycle_questioning.svg}{options: style=margin-bottom:5px} \cr} | ||||
| The \link[=lifecycle]{lifecycle} of this function is \strong{questioning}. This function might be no longer be optimal approach, or is it questionable whether this function should be in this \code{AMR} package at all. | ||||
| } | ||||
|  | ||||
| \section{Read more on our website!}{ | ||||
|  | ||||
| On our website \url{https://msberends.github.io/AMR/} you can find \href{https://msberends.github.io/AMR/articles/AMR.html}{a comprehensive tutorial} about how to conduct AMR analysis, the \href{https://msberends.github.io/AMR/reference/}{complete documentation of all functions} and \href{https://msberends.github.io/AMR/articles/WHONET.html}{an example analysis using WHONET data}. As we would like to better understand the backgrounds and needs of our users, please \href{https://msberends.github.io/AMR/survey.html}{participate in our survey}! | ||||
| } | ||||
|  | ||||
| @@ -27,5 +27,6 @@ context("deprecated.R") | ||||
|  | ||||
| test_that("deprecated functions work", { | ||||
|   skip_on_cran() | ||||
|   # if some functions get deprecated, put the tests here | ||||
|   expect_identical(suppressWarnings(p_symbol(c(0.001, 0.01, 0.05, 0.1, 1, NA, 3))), | ||||
|                    c("***", "**", "*", ".", " ", NA, NA)) | ||||
| }) | ||||
|   | ||||
| @@ -112,4 +112,9 @@ test_that("mo_property works", { | ||||
|                   stringsAsFactors = FALSE) | ||||
|   expect_equal(nrow(subset(x, f1 != f2)), 0) | ||||
|    | ||||
|   # is gram pos/neg (also return FALSE for all non-bacteria) | ||||
|   expect_equal(is_gram_negative(c("Escherichia coli", "Staphylococcus aureus", "Candida albicans")), | ||||
|                c(TRUE, FALSE, FALSE)) | ||||
|   expect_equal(is_gram_positive(c("Escherichia coli", "Staphylococcus aureus", "Candida albicans")), | ||||
|                c(FALSE, TRUE, FALSE)) | ||||
| }) | ||||
|   | ||||
| @@ -1,32 +0,0 @@ | ||||
| # ==================================================================== # | ||||
| # TITLE                                                                # | ||||
| # Antimicrobial Resistance (AMR) Analysis for R                        # | ||||
| #                                                                      # | ||||
| # SOURCE                                                               # | ||||
| # https://github.com/msberends/AMR                                     # | ||||
| #                                                                      # | ||||
| # LICENCE                                                              # | ||||
| # (c) 2018-2020 Berends MS, Luz CF et al.                              # | ||||
| # Developed at the University of Groningen, the Netherlands, in        # | ||||
| # collaboration with non-profit organisations Certe Medical            # | ||||
| # Diagnostics & Advice, and University Medical Center Groningen.       #  | ||||
| #                                                                      # | ||||
| # This R package is free software; you can freely use and distribute   # | ||||
| # it for both personal and commercial purposes under the terms of the  # | ||||
| # GNU General Public License version 2.0 (GNU GPL-2), as published by  # | ||||
| # the Free Software Foundation.                                        # | ||||
| # We created this package for both routine data analysis and academic  # | ||||
| # research and it was publicly released in the hope that it will be    # | ||||
| # useful, but it comes WITHOUT ANY WARRANTY OR LIABILITY.              # | ||||
| #                                                                      # | ||||
| # Visit our website for the full manual and a complete tutorial about  # | ||||
| # how to conduct AMR analysis: https://msberends.github.io/AMR/        # | ||||
| # ==================================================================== # | ||||
|  | ||||
| context("p_symbol.R") | ||||
|  | ||||
| test_that("P symbol works", { | ||||
|   skip_on_cran() | ||||
|   expect_identical(p_symbol(c(0.001, 0.01, 0.05, 0.1, 1, NA, 3)), | ||||
|                    c("***", "**", "*", ".", " ", NA, NA)) | ||||
| }) | ||||
		Reference in New Issue
	
	Block a user