1
0
mirror of https://github.com/msberends/AMR.git synced 2025-07-08 18:41:58 +02:00

(v1.6.0.9055) support codecov again

This commit is contained in:
2021-05-21 20:20:51 +02:00
parent fecc5d183c
commit b210f1327c
72 changed files with 203 additions and 216 deletions

View File

@ -41,14 +41,14 @@ expect_warning(AMR:::generate_warning_abs_missing(c("AMP", "AMX")))
expect_warning(AMR:::generate_warning_abs_missing(c("AMP", "AMX"), any = TRUE))
expect_warning(AMR:::get_column_abx(example_isolates, hard_dependencies = "FUS"))
expect_message(AMR:::get_column_abx(example_isolates, soft_dependencies = "FUS"))
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_warning(AMR:::get_column_abx(rename(example_isolates, thisone = AMX), amox = "thisone", tmp = "thisone", verbose = TRUE))
expect_warning(AMR:::get_column_abx(rename(example_isolates, thisone = AMX), amox = "thisone", tmp = "thisone", verbose = FALSE))
}
# we rely on "grouped_tbl" being a class of grouped tibbles, so implement a test that checks for this:
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_true(AMR:::is_null_or_grouped_tbl(example_isolates %>% group_by(hospital_id)))
}

View File

@ -23,9 +23,9 @@
# how to conduct AMR data analysis: https://msberends.github.io/AMR/ #
# ==================================================================== #
if (pkg_is_available("curl", also_load = FALSE) &&
pkg_is_available("rvest", also_load = FALSE) &&
pkg_is_available("xml2", also_load = FALSE) &&
if (AMR:::pkg_is_available("curl", also_load = FALSE) &&
AMR:::pkg_is_available("rvest", also_load = FALSE) &&
AMR:::pkg_is_available("xml2", also_load = FALSE) &&
tryCatch(curl::has_internet(), error = function(e) FALSE)) {
expect_true(length(atc_online_groups(ab_atc("AMX"))) >= 1)
expect_equal(atc_online_ddd(ab_atc("AMX"), administration = "O"), 1.5)

View File

@ -53,7 +53,7 @@ expect_error(count_susceptible("test", as_percent = "test"))
expect_error(count_df(c("A", "B", "C")))
expect_error(count_df(example_isolates[, "date"]))
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_equal(example_isolates %>% count_susceptible(AMC), 1433)
expect_equal(example_isolates %>% count_susceptible(AMC, GEN, only_all_tested = TRUE), 1687)
expect_equal(example_isolates %>% count_susceptible(AMC, GEN, only_all_tested = FALSE), 1764)

View File

@ -43,13 +43,13 @@ expect_silent(barplot(as.disk(c(10, 20, 40))))
expect_silent(plot(as.disk(c(10, 20, 40))))
expect_silent(plot(as.disk(c(10, 20, 40)), expand = FALSE))
expect_silent(plot(as.disk(c(10, 20, 40)), mo = "esco", ab = "cipr"))
if (pkg_is_available("ggplot2")) {
if (AMR:::pkg_is_available("ggplot2")) {
expect_inherits(ggplot(as.disk(c(10, 20, 40))), "gg")
expect_inherits(ggplot(as.disk(c(10, 20, 40)), expand = FALSE), "gg")
expect_inherits(ggplot(as.disk(c(10, 20, 40)), mo = "esco", ab = "cipr"), "gg")
}
expect_stdout(print(as.disk(12)))
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_stdout(print(tibble(d = as.disk(12))))
}

View File

@ -36,7 +36,7 @@ test_df <- rbind(
expect_equal(get_episode(test_df$date, 365),
c(1, 1, 2, 2, 2, 3, 3, 4, 1, 2, 2, 2, 3))
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_identical(test_df %>% group_by(patient_id) %>% mutate(f = is_new_episode(date, 365)) %>% pull(f),
c(TRUE, FALSE, TRUE, FALSE, FALSE, FALSE, TRUE, TRUE, TRUE, TRUE, FALSE, FALSE, TRUE))

View File

@ -71,7 +71,7 @@ b <- data.frame(mo = c("Staphylococcus aureus",
expect_equal(suppressWarnings(eucast_rules(a, "mo", info = FALSE)), b)
# piperacillin must be R in Enterobacteriaceae when tica is R
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_equal(suppressWarnings(
example_isolates %>%
filter(mo_family(mo) == "Enterobacteriaceae") %>%
@ -109,7 +109,7 @@ expect_equal(
"S")
# also test norf
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_stdout(suppressWarnings(eucast_rules(example_isolates %>% mutate(NOR = "S", NAL = "S"), info = TRUE)))
}
@ -155,4 +155,4 @@ expect_equal(nrow(eucast_rules(example_isolates,
custom_rules = x,
info = FALSE,
verbose = TRUE)),
8)
8, tolerance = 0.5)

View File

@ -110,7 +110,7 @@ expect_error(first_isolate(example_isolates,
col_date = "non-existing col",
col_mo = "mo"))
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
# if mo is not an mo class, result should be the same
expect_identical(example_isolates %>%
mutate(mo = as.character(mo)) %>%

View File

@ -23,7 +23,7 @@
# how to conduct AMR data analysis: https://msberends.github.io/AMR/ #
# ==================================================================== #
if (pkg_is_available("dplyr") & pkg_is_available("ggplot2")) {
if (AMR:::pkg_is_available("dplyr") & AMR:::pkg_is_available("ggplot2")) {
pdf(NULL) # prevent Rplots.pdf being created

View File

@ -232,7 +232,7 @@ expect_warning(mdro(example_isolates,
info = FALSE))
# print groups
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_stdout(x <- mdro(example_isolates %>% group_by(hospital_id), info = TRUE))
expect_stdout(x <- mdro(example_isolates %>% group_by(hospital_id), guideline = custom, info = TRUE))
}

View File

@ -49,7 +49,7 @@ expect_silent(barplot(as.mic(c(1, 2, 4, 8))))
expect_silent(plot(as.mic(c(1, 2, 4, 8))))
expect_silent(plot(as.mic(c(1, 2, 4, 8)), expand = FALSE))
expect_silent(plot(as.mic(c(1, 2, 4, 8)), mo = "esco", ab = "cipr"))
if (pkg_is_available("ggplot2")) {
if (AMR:::pkg_is_available("ggplot2")) {
expect_inherits(ggplot(as.mic(c(1, 2, 4, 8))), "gg")
expect_inherits(ggplot(as.mic(c(1, 2, 4, 8)), expand = FALSE), "gg")
expect_inherits(ggplot(as.mic(c(1, 2, 4, 8, 32)), mo = "esco", ab = "cipr"), "gg")
@ -58,7 +58,7 @@ expect_stdout(print(as.mic(c(1, 2, 4, 8))))
expect_inherits(summary(as.mic(c(2, 8))), c("summaryDefault", "table"))
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_stdout(print(tibble(m = as.mic(2:4))))
}
@ -85,9 +85,11 @@ suppressWarnings(expect_identical(log1p(x), log1p(x_double)))
suppressWarnings(expect_identical(cos(x), cos(x_double)))
suppressWarnings(expect_identical(sin(x), sin(x_double)))
suppressWarnings(expect_identical(tan(x), tan(x_double)))
suppressWarnings(expect_identical(cospi(x), cospi(x_double)))
suppressWarnings(expect_identical(sinpi(x), sinpi(x_double)))
suppressWarnings(expect_identical(tanpi(x), tanpi(x_double)))
if (!AMR:::current_R_older_than(3.1)) {
suppressWarnings(expect_identical(cospi(x), cospi(x_double)))
suppressWarnings(expect_identical(sinpi(x), sinpi(x_double)))
suppressWarnings(expect_identical(tanpi(x), tanpi(x_double)))
}
suppressWarnings(expect_identical(acos(x), acos(x_double)))
suppressWarnings(expect_identical(asin(x), asin(x_double)))
suppressWarnings(expect_identical(atan(x), atan(x_double)))
@ -105,7 +107,7 @@ suppressWarnings(expect_identical(cumsum(x), cumsum(x_double)))
suppressWarnings(expect_identical(cumprod(x), cumprod(x_double)))
suppressWarnings(expect_identical(cummax(x), cummax(x_double)))
suppressWarnings(expect_identical(cummin(x), cummin(x_double)))
suppressWarnings(expect_identical(!x, !(x_double)))
suppressWarnings(expect_identical(!x, !x_double))
suppressWarnings(expect_identical(all(x), all(x_double)))
suppressWarnings(expect_identical(any(x), any(x_double)))

View File

@ -144,7 +144,7 @@ expect_identical(as.character(as.mo("S. sanguinis", Lancefield = TRUE)), "B_S
expect_identical(as.character(as.mo("S. salivarius", Lancefield = FALSE)), "B_STRPT_SLVR")
expect_identical(as.character(as.mo("S. salivarius", Lancefield = TRUE)), "B_STRPT_GRPK") # group K
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
# select with one column
expect_identical(
example_isolates[1:10, ] %>%
@ -273,7 +273,7 @@ expect_equal(as.character(as.mo(c("meningococ", "gonococ", "pneumococ"))),
expect_equal(suppressWarnings(as.character(as.mo(c("yeasts", "fungi")))),
c("F_YEAST", "F_FUNGUS"))
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
# print tibble
expect_stdout(print(tibble(mo = as.mo("B_ESCHR_COLI"))))
}
@ -292,6 +292,6 @@ expect_equal(as.character(as.mo(c("E. coli", "E. coli ignorethis"), ignore_patte
c("B_ESCHR_COLI", NA))
# frequency tables
if (pkg_is_available("cleaner")) {
if (AMR:::pkg_is_available("cleaner")) {
expect_inherits(cleaner::freq(example_isolates$mo), "freq")
}

View File

@ -119,7 +119,7 @@ expect_equal(mo_is_intrinsic_resistant(c("Escherichia coli", "Staphylococcus aur
# with reference data
expect_equal(mo_name("test", reference_df = data.frame(col1 = "test", mo = "B_ESCHR_COLI")),
"Escherichia coli")
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_equal(example_isolates %>% filter(mo_is_gram_negative()) %>% nrow(),
730)
expect_equal(example_isolates %>% filter(mo_is_gram_positive()) %>% nrow(),

View File

@ -42,12 +42,12 @@ expect_inherits(pca_model, "pca")
pdf(NULL) # prevent Rplots.pdf being created
if (pkg_is_available("ggplot2")) {
if (AMR:::pkg_is_available("ggplot2")) {
ggplot_pca(pca_model, ellipse = TRUE)
ggplot_pca(pca_model, arrows_textangled = FALSE)
}
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
resistance_data <- example_isolates %>%
group_by(order = mo_order(mo),
genus = mo_genus(mo)) %>%
@ -56,7 +56,7 @@ if (pkg_is_available("dplyr")) {
pca(AMC, CXM, CTX, CAZ, GEN, TOB, TMP, "SXT")
expect_inherits(pca_result, "prcomp")
if (pkg_is_available("ggplot2")) {
if (AMR:::pkg_is_available("ggplot2")) {
ggplot_pca(pca_result, ellipse = TRUE)
ggplot_pca(pca_result, ellipse = FALSE, arrows_textangled = FALSE, scale = FALSE)
}

View File

@ -35,7 +35,7 @@ expect_equal(proportion_R(example_isolates$AMX) + proportion_I(example_isolates$
expect_equal(proportion_S(example_isolates$AMX) + proportion_I(example_isolates$AMX),
proportion_SI(example_isolates$AMX))
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_equal(example_isolates %>% proportion_SI(AMC),
0.7626397,
tolerance = 0.0001)

View File

@ -23,7 +23,7 @@
# how to conduct AMR data analysis: https://msberends.github.io/AMR/ #
# ==================================================================== #
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_stdout(AMX_R <- example_isolates %>%
filter(mo == "B_ESCHR_COLI") %>%
rsi_predict(col_ab = "AMX",
@ -43,7 +43,7 @@ expect_stdout(x <- suppressMessages(resistance_predict(example_isolates,
info = TRUE)))
pdf(NULL) # prevent Rplots.pdf being created
expect_silent(plot(x))
if (pkg_is_available("ggplot2")) {
if (AMR:::pkg_is_available("ggplot2")) {
expect_silent(ggplot_rsi_predict(x))
expect_silent(ggplot(x))
expect_error(ggplot_rsi_predict(example_isolates))

View File

@ -34,7 +34,7 @@ expect_inherits(unique(x[1], x[9]), "rsi")
pdf(NULL) # prevent Rplots.pdf being created
expect_silent(barplot(as.rsi(c("S", "I", "R"))))
expect_silent(plot(as.rsi(c("S", "I", "R"))))
if (pkg_is_available("ggplot2")) expect_inherits(ggplot(as.rsi(c("S", "I", "R"))), "gg")
if (AMR:::pkg_is_available("ggplot2")) expect_inherits(ggplot(as.rsi(c("S", "I", "R"))), "gg")
expect_stdout(print(as.rsi(c("S", "I", "R"))))
expect_equal(as.character(as.rsi(c(1:3))), c("S", "I", "R"))
expect_equal(suppressWarnings(as.logical(as.rsi("INVALID VALUE"))), NA)
@ -49,7 +49,7 @@ expect_identical(as.logical(lapply(example_isolates, is.rsi.eligible)),
expect_error(as.rsi.mic(as.mic(16)))
expect_error(as.rsi.disk(as.disk(16)))
expect_error(get_guideline("this one does not exist"))
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
# 40 rsi columns
expect_equal(example_isolates %>%
mutate_at(vars(PEN:RIF), as.character) %>%
@ -61,10 +61,10 @@ if (pkg_is_available("dplyr")) {
expect_stdout(print(tibble(ab = as.rsi("S"))))
}
if (pkg_is_available("skimr")) {
if (AMR:::pkg_is_available("skimr")) {
expect_inherits(skim(example_isolates),
"data.frame")
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_inherits(example_isolates %>%
mutate(m = as.mic(2),
d = as.disk(20)) %>%
@ -94,7 +94,7 @@ expect_equal(as.rsi(as.mic(2), "E. coli", "ampicillin", guideline = "EUCAST 2020
as.rsi("S"))
expect_equal(as.rsi(as.mic(32), "E. coli", "ampicillin", guideline = "EUCAST 2020"),
as.rsi("R"))
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_true(suppressWarnings(example_isolates %>%
mutate(amox_mic = as.mic(2)) %>%
select(mo, amox_mic) %>%
@ -121,7 +121,7 @@ expect_equal(as.character(
ab = "ERY",
guideline = "CLSI")),
"R")
if (pkg_is_available("dplyr")) {
if (AMR:::pkg_is_available("dplyr")) {
expect_true(example_isolates %>%
mutate(amox_disk = as.disk(15)) %>%
select(mo, amox_disk) %>%
@ -130,7 +130,7 @@ if (pkg_is_available("dplyr")) {
is.rsi())
}
# frequency tables
if (pkg_is_available("cleaner")) {
if (AMR:::pkg_is_available("cleaner")) {
expect_inherits(cleaner::freq(example_isolates$AMX), "freq")
}