From f606838c5310f365eea1c0d6421f5c3636a4dc79 Mon Sep 17 00:00:00 2001 From: Johannes Ranke Date: Tue, 8 Dec 2020 22:08:38 +0100 Subject: mixed.mmkin and test coverage --- tests/testthat/setup_script.R | 64 +++++++++++++++++++++ tests/testthat/test_AIC.R | 1 + tests/testthat/test_confidence.R | 17 +++++- tests/testthat/test_mixed.R | 35 ++++++++++++ tests/testthat/test_nafta.R | 2 - tests/testthat/test_plot.R | 10 +++- tests/testthat/test_saem.R | 118 +++++++++++++++++++++++++++++++++++++++ 7 files changed, 242 insertions(+), 5 deletions(-) create mode 100644 tests/testthat/test_mixed.R create mode 100644 tests/testthat/test_saem.R (limited to 'tests/testthat') diff --git a/tests/testthat/setup_script.R b/tests/testthat/setup_script.R index 8d8ba3e9..9ec91425 100644 --- a/tests/testthat/setup_script.R +++ b/tests/testthat/setup_script.R @@ -100,3 +100,67 @@ fit_obs_1 <- mkinfit(m_synth_SFO_lin, SFO_lin_a, error_model = "obs", quiet = TR # We know threestep is OK, and threestep (and IRLS) is faster here fit_tc_1 <- mkinfit(m_synth_SFO_lin, SFO_lin_a, error_model = "tc", quiet = TRUE, error_model_algorithm = "threestep") + +# Mixed models data +set.seed(123456) +sampling_times = c(0, 1, 3, 7, 14, 28, 60, 90, 120) +n <- n_biphasic <- 15 +log_sd <- 0.3 +err_1 = list(const = 1, prop = 0.05) +tc <- function(value) sigma_twocomp(value, err_1$const, err_1$prop) +const <- function(value) 2 + +SFO <- mkinmod(parent = mkinsub("SFO")) +k_parent = rlnorm(n, log(0.03), log_sd) +ds_sfo <- lapply(1:n, function(i) { + ds_mean <- mkinpredict(SFO, c(k_parent = k_parent[i]), + c(parent = 100), sampling_times) + add_err(ds_mean, tc, n = 1)[[1]] +}) + +DFOP <- mkinmod(parent = mkinsub("DFOP")) +dfop_pop <- list(parent_0 = 100, k1 = 0.06, k2 = 0.015, g = 0.4) +dfop_parms <- as.matrix(data.frame( + k1 = rlnorm(n, log(dfop_pop$k1), log_sd), + k2 = rlnorm(n, log(dfop_pop$k2), log_sd), + g = plogis(rnorm(n, qlogis(dfop_pop$g), log_sd)))) +ds_dfop <- lapply(1:n, function(i) { + ds_mean <- mkinpredict(DFOP, dfop_parms[i, ], + c(parent = dfop_pop$parent_0), sampling_times) + add_err(ds_mean, const, n = 1)[[1]] +}) + +set.seed(123456) +DFOP_SFO <- mkinmod( + parent = mkinsub("DFOP", "m1"), + m1 = mkinsub("SFO"), + quiet = TRUE) +dfop_sfo_pop <- list(parent_0 = 100, + k_m1 = 0.002, f_parent_to_m1 = 0.5, + k1 = 0.05, k2 = 0.01, g = 0.5) +syn_biphasic_parms <- as.matrix(data.frame( + k1 = rlnorm(n_biphasic, log(dfop_sfo_pop$k1), log_sd), + k2 = rlnorm(n_biphasic, log(dfop_sfo_pop$k2), log_sd), + g = plogis(rnorm(n_biphasic, qlogis(dfop_sfo_pop$g), log_sd)), + f_parent_to_m1 = plogis(rnorm(n_biphasic, + qlogis(dfop_sfo_pop$f_parent_to_m1), log_sd)), + k_m1 = rlnorm(n_biphasic, log(dfop_sfo_pop$k_m1), log_sd))) +ds_biphasic_mean <- lapply(1:n_biphasic, + function(i) { + mkinpredict(DFOP_SFO, syn_biphasic_parms[i, ], + c(parent = 100, m1 = 0), sampling_times) + } +) +ds_biphasic <- lapply(ds_biphasic_mean, function(ds) { + add_err(ds, + sdfunc = function(value) sqrt(err_1$const^2 + value^2 * err_1$prop^2), + n = 1, secondary = "m1")[[1]] +}) + +# Mixed model fits +mmkin_sfo_1 <- mmkin("SFO", ds_sfo, quiet = TRUE, error_model = "tc") +sfo_saemix_1 <- saem(mmkin_sfo_1, quiet = TRUE, transformations = "saemix") +mmkin_biphasic <- mmkin(list("DFOP-SFO" = DFOP_SFO), ds_biphasic, quiet = TRUE) +nlme_biphasic <- nlme(mmkin_biphasic) +saem_biphasic_m <- saem(mmkin_biphasic, transformations = "mkin", quiet = TRUE) +saem_biphasic_s <- saem(mmkin_biphasic, transformations = "saemix", quiet = TRUE) diff --git a/tests/testthat/test_AIC.R b/tests/testthat/test_AIC.R index e9698f7c..57b9a673 100644 --- a/tests/testthat/test_AIC.R +++ b/tests/testthat/test_AIC.R @@ -6,6 +6,7 @@ test_that("The AIC is reproducible", { data.frame(df = c(3, 4, 5, 5), AIC = c(59.3, 44.7, 29.0, 39.2)), scale = 1, tolerance = 0.1) expect_error(AIC(fits["SFO", ]), "column object") + expect_error(BIC(fits["SFO", ]), "column object") expect_equivalent(BIC(fits[, "FOCUS_C"]), data.frame(df = c(3, 4, 5, 5), AIC = c(59.9, 45.5, 30.0, 40.2)), scale = 1, tolerance = 0.1) diff --git a/tests/testthat/test_confidence.R b/tests/testthat/test_confidence.R index 3fdd3f2c..54be675c 100644 --- a/tests/testthat/test_confidence.R +++ b/tests/testthat/test_confidence.R @@ -1,6 +1,19 @@ context("Confidence intervals and p-values") +test_that("Some special cases of confidence interval calculation work", { + + tmp <- expect_warning(mkinfit("FOMC", FOCUS_2006_A, quiet = TRUE), "not converge") + + expect_equivalent( + confint(tmp, transform = FALSE), + matrix(rep(NA, 8), nrow = 4)) +}) + test_that("The confint method 'quadratic' is consistent with the summary", { + expect_equivalent( + confint(fit_nw_1, parm = "parent_0", method = "quadratic"), + summary(fit_nw_1)$bpar["parent_0", c("Lower", "Upper")]) + expect_equivalent( confint(fit_nw_1, method = "quadratic"), summary(fit_nw_1)$bpar[, c("Lower", "Upper")]) @@ -74,8 +87,8 @@ test_that("Likelihood profile based confidence intervals work", { } f_mle <- stats4::mle(f_nll, start = as.list(parms(f)), nobs = nrow(FOCUS_2006_C)) - ci_mkin_1_p_0.95 <- confint(f, method = "profile", level = 0.95, - cores = n_cores, quiet = TRUE) + ci_mkin_1_p_0.95 <- expect_message(confint(f, method = "profile", level = 0.95, + cores = n_cores, quiet = FALSE), "Profiling the likelihood") # Magically, we get very similar boundaries as stats4::mle # (we need to capture the output to avoid printing this while testing as diff --git a/tests/testthat/test_mixed.R b/tests/testthat/test_mixed.R new file mode 100644 index 00000000..2d69e13e --- /dev/null +++ b/tests/testthat/test_mixed.R @@ -0,0 +1,35 @@ +context("Fitting of nonlinear mixed effects models") + +sampling_times = c(0, 1, 3, 7, 14, 28, 60, 90, 120) +n_biphasic <- 8 +err_1 = list(const = 1, prop = 0.07) + +DFOP_SFO <- mkinmod( + parent = mkinsub("DFOP", "m1"), + m1 = mkinsub("SFO"), + quiet = TRUE) + +set.seed(123456) +log_sd <- 0.3 +syn_biphasic_parms <- as.matrix(data.frame( + k1 = rlnorm(n_biphasic, log(0.05), log_sd), + k2 = rlnorm(n_biphasic, log(0.01), log_sd), + g = plogis(rnorm(n_biphasic, 0, log_sd)), + f_parent_to_m1 = plogis(rnorm(n_biphasic, 0, log_sd)), + k_m1 = rlnorm(n_biphasic, log(0.002), log_sd))) + +ds_biphasic_mean <- lapply(1:n_biphasic, + function(i) { + mkinpredict(DFOP_SFO, syn_biphasic_parms[i, ], + c(parent = 100, m1 = 0), sampling_times) + } +) + +set.seed(123456L) +ds_biphasic <- lapply(ds_biphasic_mean, function(ds) { + add_err(ds, + sdfunc = function(value) sqrt(err_1$const^2 + value^2 * err_1$prop^2), + n = 1, secondary = "m1")[[1]] +}) + +f_mmkin <- mmkin(list("DFOP-SFO" = DFOP_SFO), ds_biphasic, quiet = TRUE) diff --git a/tests/testthat/test_nafta.R b/tests/testthat/test_nafta.R index fcab4ffb..62c88983 100644 --- a/tests/testthat/test_nafta.R +++ b/tests/testthat/test_nafta.R @@ -20,7 +20,6 @@ test_that("Test data from Appendix B are correctly evaluated", { expect_known_output(print(res), "NAFTA_SOP_Appendix_B.txt") - skip_on_travis() plot_nafta <- function() plot(res) if(requireNamespace("vdiffr", quietly = TRUE)) { skip_if(getRversion() < "4.1.0") @@ -49,7 +48,6 @@ test_that("Test data from Appendix D are correctly evaluated", { expect_known_output(print(res), "NAFTA_SOP_Appendix_D.txt") - skip_on_travis() plot_nafta <- function() plot(res) if(requireNamespace("vdiffr", quietly = TRUE)) { skip_if(getRversion() < "4.1.0") diff --git a/tests/testthat/test_plot.R b/tests/testthat/test_plot.R index 587ec02e..72f1020c 100644 --- a/tests/testthat/test_plot.R +++ b/tests/testthat/test_plot.R @@ -2,7 +2,6 @@ context("Plotting") test_that("Plotting mkinfit and mmkin objects is reproducible", { skip_on_cran() - skip_on_travis() plot_default_FOCUS_C_SFO <- function() plot(fits[["SFO", "FOCUS_C"]]) plot_res_FOCUS_C_SFO <- function() plot(fits[["SFO", "FOCUS_C"]], show_residuals = TRUE) plot_res_FOCUS_C_SFO_2 <- function() plot_res(fits[["SFO", "FOCUS_C"]]) @@ -17,6 +16,11 @@ test_that("Plotting mkinfit and mmkin objects is reproducible", { plot_errmod_fit_D_obs_eigen <- function() plot_err(fit_D_obs_eigen, sep_obs = FALSE) plot_errmod_fit_C_tc <- function() plot_err(fit_C_tc) + plot_biphasic_mmkin <- function() plot(mixed(mmkin_biphasic)) + plot_biphasic_nlme <- function() plot(nlme_biphasic) + plot_biphasic_saem_s <- function() plot(saem_biphasic_s) + plot_biphasic_saem_m <- function() plot(saem_biphasic_m) + plot_res_sfo_sfo <- function() plot_res(f_sfo_sfo_desolve) plot_err_sfo_sfo <- function() plot_err(f_sfo_sfo_desolve) plot_errmod_fit_obs_1 <- function() plot_err(fit_obs_1, sep_obs = FALSE) @@ -32,6 +36,10 @@ test_that("Plotting mkinfit and mmkin objects is reproducible", { vdiffr::expect_doppelganger("mmkin plot for FOCUS C", mmkin_FOCUS_C) vdiffr::expect_doppelganger("mmkin plot for SFO (FOCUS C and D)", mmkin_SFO) vdiffr::expect_doppelganger("plot_errmod with FOCUS C tc", plot_errmod_fit_C_tc) + vdiffr::expect_doppelganger("mixed model fit for mmkin object", plot_biphasic_mmkin) + vdiffr::expect_doppelganger("mixed model fit for nlme object", plot_biphasic_nlme) + vdiffr::expect_doppelganger("mixed model fit for saem object with saemix transformations", plot_biphasic_saem_s) + vdiffr::expect_doppelganger("mixed model fit for saem object with mkin transformations", plot_biphasic_saem_m) skip_on_travis() # Still not working on Travis, maybe because of deSolve producing # different results when not working with a compiled model or eigenvalues vdiffr::expect_doppelganger("plot_errmod with FOCUS D obs eigen", plot_errmod_fit_D_obs_eigen) diff --git a/tests/testthat/test_saem.R b/tests/testthat/test_saem.R new file mode 100644 index 00000000..0b6d4531 --- /dev/null +++ b/tests/testthat/test_saem.R @@ -0,0 +1,118 @@ +context("Nonlinear mixed effects models fitted with SAEM from saemix") + +set.seed(123456) +sampling_times = c(0, 1, 3, 7, 14, 28, 60, 90, 120) +n <- n_biphasic <- 15 +log_sd <- 0.3 +err_1 = list(const = 1, prop = 0.05) +tc <- function(value) sigma_twocomp(value, err_1$const, err_1$prop) +const <- function(value) 2 + +SFO <- mkinmod(parent = mkinsub("SFO")) +k_parent = rlnorm(n, log(0.03), log_sd) +ds_sfo <- lapply(1:n, function(i) { + ds_mean <- mkinpredict(SFO, c(k_parent = k_parent[i]), + c(parent = 100), sampling_times) + add_err(ds_mean, tc, n = 1)[[1]] +}) + +DFOP <- mkinmod(parent = mkinsub("DFOP")) +dfop_pop <- list(parent_0 = 100, k1 = 0.06, k2 = 0.015, g = 0.4) +dfop_parms <- as.matrix(data.frame( + k1 = rlnorm(n, log(dfop_pop$k1), log_sd), + k2 = rlnorm(n, log(dfop_pop$k2), log_sd), + g = plogis(rnorm(n, qlogis(dfop_pop$g), log_sd)))) +ds_dfop <- lapply(1:n, function(i) { + ds_mean <- mkinpredict(DFOP, dfop_parms[i, ], + c(parent = dfop_pop$parent_0), sampling_times) + add_err(ds_mean, const, n = 1)[[1]] +}) + +set.seed(123456) +DFOP_SFO <- mkinmod( + parent = mkinsub("DFOP", "m1"), + m1 = mkinsub("SFO"), + quiet = TRUE) +syn_biphasic_parms <- as.matrix(data.frame( + k1 = rlnorm(n_biphasic, log(0.05), log_sd), + k2 = rlnorm(n_biphasic, log(0.01), log_sd), + g = plogis(rnorm(n_biphasic, 0, log_sd)), + f_parent_to_m1 = plogis(rnorm(n_biphasic, 0, log_sd)), + k_m1 = rlnorm(n_biphasic, log(0.002), log_sd))) +ds_biphasic_mean <- lapply(1:n_biphasic, + function(i) { + mkinpredict(DFOP_SFO, syn_biphasic_parms[i, ], + c(parent = 100, m1 = 0), sampling_times) + } +) +ds_biphasic <- lapply(ds_biphasic_mean, function(ds) { + add_err(ds, + sdfunc = function(value) sqrt(err_1$const^2 + value^2 * err_1$prop^2), + n = 1, secondary = "m1")[[1]] +}) + +test_that("Parent only models can be fitted with saemix", { + # Some fits were done in the setup script + mmkin_sfo_2 <- mmkin("SFO", ds_sfo, fixed_initials = c(parent = 100), quiet = TRUE) + + sfo_saemix_2 <- saem(mmkin_sfo_1, quiet = TRUE, transformations = "mkin") + sfo_saemix_3 <- expect_error(saem(mmkin_sfo_2, quiet = TRUE), "at least two parameters") + s_sfo_s1 <- summary(sfo_saemix_1) + s_sfo_s2 <- summary(sfo_saemix_2) + + sfo_nlme_1 <- expect_warning(nlme(mmkin_sfo_1), "not converge") + s_sfo_n <- summary(sfo_nlme_1) + + # Compare with input + expect_equal(round(s_sfo_s2$confint_ranef["SD.log_k_parent", "est."], 1), 0.3) + # k_parent is a bit different from input 0.03 here + expect_equal(round(s_sfo_s1$confint_back["k_parent", "est."], 3), 0.035) + expect_equal(round(s_sfo_s2$confint_back["k_parent", "est."], 3), 0.035) + + # But the result is pretty unanimous between methods + expect_equal(round(s_sfo_s1$confint_back["k_parent", "est."], 3), + round(s_sfo_s2$confint_back["k_parent", "est."], 3)) + expect_equal(round(s_sfo_s1$confint_back["k_parent", "est."], 3), + round(s_sfo_n$confint_back["k_parent", "est."], 3)) + + mmkin_dfop_1 <- mmkin("DFOP", ds_dfop, quiet = TRUE) + + dfop_saemix_1 <- saem(mmkin_dfop_1, quiet = TRUE, transformations = "mkin") + dfop_saemix_2 <- saem(mmkin_dfop_1, quiet = TRUE, transformations = "saemix") + dfop_nlme_1 <- nlme(mmkin_dfop_1) + s_dfop_s1 <- summary(dfop_saemix_1) + s_dfop_s2 <- summary(dfop_saemix_2) + s_dfop_n <- summary(dfop_nlme_1) + + dfop_pop <- as.numeric(dfop_pop) + expect_true(all(s_dfop_s1$confint_back[, "lower"] < dfop_pop)) + expect_true(all(s_dfop_s1$confint_back[, "upper"] > dfop_pop)) + expect_true(all(s_dfop_s2$confint_back[, "lower"] < dfop_pop)) + expect_true(all(s_dfop_s2$confint_back[, "upper"] > dfop_pop)) + + + # We get < 20% deviations with transformations made in mkin + rel_diff_1 <- (s_dfop_s1$confint_back[, "est."] - dfop_pop) / dfop_pop + expect_true(all(rel_diff_1 < 0.2)) + + # We get < 8% deviations with transformations made in saemix + rel_diff_2 <- (s_dfop_s2$confint_back[, "est."] - dfop_pop) / dfop_pop + expect_true(all(rel_diff_2 < 0.08)) +}) + +test_that("Simple models with metabolite can be fitted with saemix", { + + dfop_sfo_pop <- as.numeric(dfop_sfo_pop) + ci_dfop_sfo_s_s <- summary(saem_biphasic_s)$confint_back + expect_true(all(ci_dfop_sfo_s_s[, "lower"] < dfop_sfo_pop)) + expect_true(all(ci_dfop_sfo_s_s[, "upper"] > dfop_sfo_pop)) + + # The following does not work, the k1 and k2 are not fitted well + ci_dfop_sfo_s_m <- summary(saem_biphasic_m)$confint_back + # expect_true(all(ci_dfop_sfo_s_m[, "lower"] < dfop_sfo_pop)) + #expect_true(all(ci_dfop_sfo_s_m[, "upper"] > dfop_sfo_pop)) + + # Somehow this does not work at the moment. But it took forever (~ 10 min) anyways... + #saem_biphasic_2 <- saem(mmkin_biphasic, solution_type = "deSolve", quiet = TRUE) + +}) -- cgit v1.2.1