From fa10b85d6bb964742d2c5a3e3f633a5238c43d56 Mon Sep 17 00:00:00 2001 From: jranke Date: Mon, 18 Feb 2013 22:11:49 +0000 Subject: - Completion of the multicompartment part of the mkin examples vignette - Fix to chi2 error level calculation by correctly returning backtransformed parameters as bparms.optim and bparms.fixed - Adaptations of unit tests, summary and plot functions git-svn-id: svn+ssh://svn.r-forge.r-project.org/svnroot/kinfit/pkg/mkin@67 edb9625f-4e0d-4859-8d74-9fd3b1da38cb --- DESCRIPTION | 2 +- R/endpoints.R | 2 +- R/mkinerrmin.R | 2 +- R/mkinfit.R | 22 +++++--- R/plot.mkinfit.R | 5 +- inst/unitTests/runit.mkinfit.R | 44 +++++++-------- vignettes/examples-L1_SFO_plots.pdf | Bin 6265 -> 0 bytes vignettes/examples.Rnw | 106 ++++++++++++++++++++---------------- vignettes/examples.pdf | Bin 176985 -> 281843 bytes vignettes/mkin.pdf | Bin 162839 -> 162843 bytes vignettes/run.bat | 5 -- 11 files changed, 100 insertions(+), 88 deletions(-) delete mode 100644 vignettes/examples-L1_SFO_plots.pdf delete mode 100644 vignettes/run.bat diff --git a/DESCRIPTION b/DESCRIPTION index 8db0fc85..808458cb 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -2,7 +2,7 @@ Package: mkin Type: Package Title: Routines for fitting kinetic models with one or more state variables to chemical degradation data -Version: 0.9-12 +Version: 0.9-13 Date: 2013-02-18 Author: Johannes Ranke, Katrin Lindenberger, René Lehmann Maintainer: Johannes Ranke diff --git a/R/endpoints.R b/R/endpoints.R index 98e290d0..163dc8d4 100644 --- a/R/endpoints.R +++ b/R/endpoints.R @@ -3,7 +3,7 @@ endpoints <- function(fit, pseudoDT50 = FALSE) { # fractions and SFORB eigenvalues from optimised parameters ep <- list() obs_vars <- fit$obs_vars - parms.all <- fit$parms.all + parms.all <- fit$bparms.ode ep$distimes <- data.frame(DT50 = rep(NA, length(obs_vars)), DT90 = rep(NA, length(obs_vars)), row.names = obs_vars) diff --git a/R/mkinerrmin.R b/R/mkinerrmin.R index 49538e37..8b1e9b2e 100644 --- a/R/mkinerrmin.R +++ b/R/mkinerrmin.R @@ -20,7 +20,7 @@ utils::globalVariables(c("name")) mkinerrmin <- function(fit, alpha = 0.05) { - parms.optim <- fit$parms.all + parms.optim <- fit$par kinerrmin <- function(errdata, n.parms) { means.mean <- mean(errdata$value_mean, na.rm=TRUE) df = length(errdata$value_mean) - n.parms diff --git a/R/mkinfit.R b/R/mkinfit.R index e084cf1a..3ca38990 100644 --- a/R/mkinfit.R +++ b/R/mkinfit.R @@ -191,7 +191,9 @@ mkinfit <- function(mkinmod, observed, value = c(state.ini.fixed, parms.fixed)) fit$fixed$type = c(rep("state", length(state.ini.fixed)), rep("deparm", length(parms.fixed))) - parms.all = backtransform_odeparms(c(fit$par, parms.fixed), mod_vars) + bparms.optim = backtransform_odeparms(fit$par, mod_vars) + bparms.fixed = backtransform_odeparms(c(state.ini.fixed, parms.fixed), mod_vars) + bparms.all = c(bparms.optim, bparms.fixed) # Collect observed, predicted and residuals data <- merge(fit$observed, fit$predicted, by = c("time", "name")) @@ -201,8 +203,10 @@ mkinfit <- function(mkinmod, observed, fit$data <- data[order(data$variable, data$time), ] fit$atol <- atol fit$rtol <- rtol - fit$parms.all <- parms.all # Return all backtransformed parameters for summary - fit$odeparms.final <- parms.all[mkinmod$parms] # Return ode parameters for further fitting + # Return all backtransformed parameters for summary + fit$bparms.optim <- bparms.optim + fit$bparms.fixed <- bparms.fixed + fit$bparms.ode <- bparms.all[mkinmod$parms] # Return ode parameters for further fitting fit$date <- date() class(fit) <- c("mkinfit", "modFit") @@ -231,7 +235,7 @@ summary.mkinfit <- function(object, data = TRUE, distimes = TRUE, ...) { param <- cbind(param, se) dimnames(param) <- list(pnames, c("Estimate", "Std. Error")) - bparam <- as.matrix(object$parms.all) + bparam <- as.matrix(object$bparms.optim) dimnames(bparam) <- list(pnames, c("Estimate")) ans <- list( @@ -259,9 +263,9 @@ summary.mkinfit <- function(object, data = TRUE, distimes = TRUE, ...) { ans$errmin <- mkinerrmin(object, alpha = 0.05) - ans$parms.all <- object$parms.all + ans$bparms.ode <- object$bparms.ode ep <- endpoints(object) - if (!is.null(ep$ff)) + if (length(ep$ff) != 0) ans$ff <- ep$ff if(distimes) ans$distimes <- ep$distimes if(length(ep$SFORB) != 0) ans$SFORB <- ep$SFORB @@ -305,19 +309,19 @@ print.summary.mkinfit <- function(x, digits = max(3, getOption("digits") - 3), . if(printdistimes){ cat("\nEstimated disappearance times:\n") print(x$distimes, digits=digits,...) - } + } printff <- !is.null(x$ff) if(printff & x$use_of_ff == "min"){ cat("\nEstimated formation fractions:\n") print(data.frame(ff = x$ff), digits=digits,...) - } + } printSFORB <- !is.null(x$SFORB) if(printSFORB){ cat("\nEstimated Eigenvalues of SFORB model(s):\n") print(x$SFORB, digits=digits,...) - } + } printcor <- is.numeric(x$cov.unscaled) if (printcor){ diff --git a/R/plot.mkinfit.R b/R/plot.mkinfit.R index fc8ecf74..59ef861e 100644 --- a/R/plot.mkinfit.R +++ b/R/plot.mkinfit.R @@ -30,9 +30,8 @@ plot.mkinfit <- function(x, fit = x, add = FALSE, legend = !add, ...) { solution_type = fit$solution_type - fixed <- fit$fixed$value - names(fixed) <- rownames(fit$fixed) - parms.all <- c(fit$parms.all, fixed) + parms.all <- c(fit$bparms.optim, fit$bparms.fixed) + ininames <- c( rownames(subset(fit$start, type == "state")), rownames(subset(fit$fixed, type == "state"))) diff --git a/inst/unitTests/runit.mkinfit.R b/inst/unitTests/runit.mkinfit.R index 26007e78..784054b8 100644 --- a/inst/unitTests/runit.mkinfit.R +++ b/inst/unitTests/runit.mkinfit.R @@ -30,11 +30,11 @@ test.FOCUS_2006_SFO <- function() median.A.SFO <- as.numeric(lapply(subset(FOCUS_2006_SFO_ref_A_to_F, dataset == "A", c(M0, k, DT50, DT90)), "median")) - fit.A.SFO.1.r <- as.numeric(c(fit.A.SFO.1$parms.all, endpoints(fit.A.SFO.1)$distimes)) + fit.A.SFO.1.r <- as.numeric(c(fit.A.SFO.1$bparms.optim, endpoints(fit.A.SFO.1)$distimes)) dev.A.SFO.1 <- abs(round(100 * ((median.A.SFO - fit.A.SFO.1.r)/median.A.SFO), digits=1)) checkIdentical(dev.A.SFO.1 < 1, rep(TRUE, length(dev.A.SFO.1))) - fit.A.SFO.2.r <- as.numeric(c(fit.A.SFO.2$parms.all, endpoints(fit.A.SFO.2)$distimes)) + fit.A.SFO.2.r <- as.numeric(c(fit.A.SFO.2$bparms.optim, endpoints(fit.A.SFO.2)$distimes)) dev.A.SFO.2 <- abs(round(100 * ((median.A.SFO - fit.A.SFO.2.r)/median.A.SFO), digits=1)) checkIdentical(dev.A.SFO.2 < 1, rep(TRUE, length(dev.A.SFO.2))) @@ -44,11 +44,11 @@ test.FOCUS_2006_SFO <- function() median.C.SFO <- as.numeric(lapply(subset(FOCUS_2006_SFO_ref_A_to_F, dataset == "C", c(M0, k, DT50, DT90)), "median")) - fit.C.SFO.1.r <- as.numeric(c(fit.C.SFO.1$parms.all, endpoints(fit.C.SFO.1)$distimes)) + fit.C.SFO.1.r <- as.numeric(c(fit.C.SFO.1$bparms.optim, endpoints(fit.C.SFO.1)$distimes)) dev.C.SFO.1 <- abs(round(100 * ((median.C.SFO - fit.C.SFO.1.r)/median.C.SFO), digits=1)) checkIdentical(dev.C.SFO.1 < 1, rep(TRUE, length(dev.C.SFO.1))) - fit.C.SFO.2.r <- as.numeric(c(fit.C.SFO.2$parms.all, endpoints(fit.C.SFO.2)$distimes)) + fit.C.SFO.2.r <- as.numeric(c(fit.C.SFO.2$bparms.optim, endpoints(fit.C.SFO.2)$distimes)) dev.C.SFO.2 <- abs(round(100 * ((median.C.SFO - fit.C.SFO.2.r)/median.C.SFO), digits=1)) checkIdentical(dev.C.SFO.2 < 1, rep(TRUE, length(dev.C.SFO.2))) } # }}} @@ -66,7 +66,7 @@ test.FOCUS_2006_FOMC <- function() median.A.FOMC <- as.numeric(lapply(subset(FOCUS_2006_FOMC_ref_A_to_F, dataset == "A", c(M0, alpha, beta, DT50, DT90)), "median")) - fit.A.FOMC.r <- as.numeric(c(fit.A.FOMC$parms.all, endpoints(fit.A.FOMC)$distimes)) + fit.A.FOMC.r <- as.numeric(c(fit.A.FOMC$bparms.optim, endpoints(fit.A.FOMC)$distimes)) dev.A.FOMC <- abs(round(100 * ((median.A.FOMC - fit.A.FOMC.r)/median.A.FOMC), digits=1)) dev.A.FOMC <- dev.A.FOMC[c(1, 4, 5)] checkIdentical(dev.A.FOMC < 1, rep(TRUE, length(dev.A.FOMC))) @@ -77,7 +77,7 @@ test.FOCUS_2006_FOMC <- function() median.B.FOMC <- as.numeric(lapply(subset(FOCUS_2006_FOMC_ref_A_to_F, dataset == "B", c(M0, alpha, beta, DT50, DT90)), "median")) - fit.B.FOMC.r <- as.numeric(c(fit.B.FOMC$parms.all, endpoints(fit.B.FOMC)$distimes)) + fit.B.FOMC.r <- as.numeric(c(fit.B.FOMC$bparms.optim, endpoints(fit.B.FOMC)$distimes)) dev.B.FOMC <- abs(round(100 * ((median.B.FOMC - fit.B.FOMC.r)/median.B.FOMC), digits=1)) dev.B.FOMC <- dev.B.FOMC[c(1, 4, 5)] checkIdentical(dev.B.FOMC < 1, rep(TRUE, length(dev.B.FOMC))) @@ -88,7 +88,7 @@ test.FOCUS_2006_FOMC <- function() median.C.FOMC <- as.numeric(lapply(subset(FOCUS_2006_FOMC_ref_A_to_F, dataset == "C", c(M0, alpha, beta, DT50, DT90)), "median")) - fit.C.FOMC.r <- as.numeric(c(fit.C.FOMC$parms.all, endpoints(fit.C.FOMC)$distimes)) + fit.C.FOMC.r <- as.numeric(c(fit.C.FOMC$bparms.optim, endpoints(fit.C.FOMC)$distimes)) dev.C.FOMC <- abs(round(100 * ((median.C.FOMC - fit.C.FOMC.r)/median.C.FOMC), digits=1)) dev.C.FOMC <- dev.C.FOMC[c(1, 4, 5)] checkIdentical(dev.C.FOMC < 1, rep(TRUE, length(dev.C.FOMC))) @@ -106,7 +106,7 @@ test.FOCUS_2006_DFOP <- function() median.A.DFOP <- as.numeric(lapply(subset(FOCUS_2006_DFOP_ref_A_to_B, dataset == "A", c(M0, k1, k2, f, DT50, DT90)), "median")) - fit.A.DFOP.r <- as.numeric(c(fit.A.DFOP$parms.all, endpoints(fit.A.DFOP)$distimes)) + fit.A.DFOP.r <- as.numeric(c(fit.A.DFOP$bparms.optim, endpoints(fit.A.DFOP)$distimes)) dev.A.DFOP <- abs(round(100 * ((median.A.DFOP - fit.A.DFOP.r)/median.A.DFOP), digits=1)) # about 6.7% deviation for parameter f, the others are < 0.1% checkIdentical(dev.A.DFOP < c(1, 1, 1, 10, 1, 1), rep(TRUE, length(dev.A.DFOP))) @@ -117,7 +117,7 @@ test.FOCUS_2006_DFOP <- function() median.B.DFOP <- as.numeric(lapply(subset(FOCUS_2006_DFOP_ref_A_to_B, dataset == "B", c(M0, k1, k2, f, DT50, DT90)), "median")) - fit.B.DFOP.r <- as.numeric(c(fit.B.DFOP$parms.all, endpoints(fit.B.DFOP)$distimes)) + fit.B.DFOP.r <- as.numeric(c(fit.B.DFOP$bparms.optim, endpoints(fit.B.DFOP)$distimes)) dev.B.DFOP <- abs(round(100 * ((median.B.DFOP - fit.B.DFOP.r)/median.B.DFOP), digits=1)) # about 0.6% deviation for parameter f, the others are <= 0.1% checkIdentical(dev.B.DFOP < 1, rep(TRUE, length(dev.B.DFOP))) @@ -135,7 +135,7 @@ test.FOCUS_2006_HS <- function() median.A.HS <- as.numeric(lapply(subset(FOCUS_2006_HS_ref_A_to_F, dataset == "A", c(M0, k1, k2, tb, DT50, DT90)), "median")) - fit.A.HS.r <- as.numeric(c(fit.A.HS$parms.all, endpoints(fit.A.HS)$distimes)) + fit.A.HS.r <- as.numeric(c(fit.A.HS$bparms.optim, endpoints(fit.A.HS)$distimes)) dev.A.HS <- abs(round(100 * ((median.A.HS - fit.A.HS.r)/median.A.HS), digits=1)) # about 6.7% deviation for parameter f, the others are < 0.1% checkIdentical(dev.A.HS < 1, rep(TRUE, length(dev.A.HS))) @@ -146,7 +146,7 @@ test.FOCUS_2006_HS <- function() median.B.HS <- as.numeric(lapply(subset(FOCUS_2006_HS_ref_A_to_F, dataset == "B", c(M0, k1, k2, tb, DT50, DT90)), "median")) - fit.B.HS.r <- as.numeric(c(fit.B.HS$parms.all, endpoints(fit.B.HS)$distimes)) + fit.B.HS.r <- as.numeric(c(fit.B.HS$bparms.optim, endpoints(fit.B.HS)$distimes)) dev.B.HS <- abs(round(100 * ((median.B.HS - fit.B.HS.r)/median.B.HS), digits=1)) # < 10% deviation for M0, k1, DT50 and DT90, others are problematic dev.B.HS <- dev.B.HS[c(1, 2, 5, 6)] @@ -158,7 +158,7 @@ test.FOCUS_2006_HS <- function() median.C.HS <- as.numeric(lapply(subset(FOCUS_2006_HS_ref_A_to_F, dataset == "C", c(M0, k1, k2, tb, DT50, DT90)), "median")) - fit.A.HS.r <- as.numeric(c(fit.A.HS$parms.all, endpoints(fit.A.HS)$distimes)) + fit.A.HS.r <- as.numeric(c(fit.A.HS$bparms.optim, endpoints(fit.A.HS)$distimes)) dev.A.HS <- abs(round(100 * ((median.A.HS - fit.A.HS.r)/median.A.HS), digits=1)) # deviation <= 0.1% checkIdentical(dev.A.HS < 1, rep(TRUE, length(dev.A.HS))) @@ -177,7 +177,7 @@ test.FOCUS_2006_SFORB <- function() c(M0, k1, k2, DT50, DT90)), "median")) fit.A.SFORB.1.r <- as.numeric(c( - parent_0 = fit.A.SFORB.1$parms.all[[1]], + parent_0 = fit.A.SFORB.1$bparms.optim[[1]], k1 = endpoints(fit.A.SFORB.1)$SFORB[[1]], k2 = endpoints(fit.A.SFORB.1)$SFORB[[2]], endpoints(fit.A.SFORB.1)$distimes)) @@ -188,7 +188,7 @@ test.FOCUS_2006_SFORB <- function() checkIdentical(dev.A.SFORB.1 < 1, rep(TRUE, length(dev.A.SFORB.1))) fit.A.SFORB.2.r <- as.numeric(c( - parent_0 = fit.A.SFORB.2$parms.all[[1]], + parent_0 = fit.A.SFORB.2$bparms.optim[[1]], k1 = endpoints(fit.A.SFORB.2)$SFORB[[1]], k2 = endpoints(fit.A.SFORB.2)$SFORB[[2]], endpoints(fit.A.SFORB.2)$distimes)) @@ -206,7 +206,7 @@ test.FOCUS_2006_SFORB <- function() c(M0, k1, k2, DT50, DT90)), "median")) fit.B.SFORB.1.r <- as.numeric(c( - parent_0 = fit.B.SFORB.1$parms.all[[1]], + parent_0 = fit.B.SFORB.1$bparms.optim[[1]], k1 = endpoints(fit.B.SFORB.1)$SFORB[[1]], k2 = endpoints(fit.B.SFORB.1)$SFORB[[2]], endpoints(fit.B.SFORB.1)$distimes)) @@ -214,7 +214,7 @@ test.FOCUS_2006_SFORB <- function() checkIdentical(dev.B.SFORB.1 < 1, rep(TRUE, length(dev.B.SFORB.1))) fit.B.SFORB.2.r <- as.numeric(c( - parent_0 = fit.B.SFORB.2$parms.all[[1]], + parent_0 = fit.B.SFORB.2$bparms.optim[[1]], k1 = endpoints(fit.B.SFORB.2)$SFORB[[1]], k2 = endpoints(fit.B.SFORB.2)$SFORB[[2]], endpoints(fit.B.SFORB.2)$distimes)) @@ -239,15 +239,15 @@ test.FOCUS_2006_D_SFO_SFO <- function() fit.2.d <- mkinfit(SFO_SFO.2, solution_type = "deSolve", FOCUS_2006_D) # Eigenvalue based solution with maximum use of formation fractions only # works correctly with initial parameters very close to final parameters! - fit.2.e <- mkinfit(SFO_SFO.2, parms.ini = fit.2.d$odeparms.final, FOCUS_2006_D) + fit.2.e <- mkinfit(SFO_SFO.2, parms.ini = fit.2.d$bparms.ode, FOCUS_2006_D) FOCUS_2006_D_results_schaefer07_means <- c( parent_0 = 99.65, DT50_parent = 7.04, DT50_m1 = 131.34) - r.1.e <- c(fit.1.e$parms.all[[1]], endpoints(fit.1.e)$distimes[[1]]) - r.1.d <- c(fit.1.d$parms.all[[1]], endpoints(fit.1.d)$distimes[[1]]) - r.2.e <- c(fit.2.e$parms.all[[1]], endpoints(fit.2.e)$distimes[[1]]) - r.2.d <- c(fit.2.d$parms.all[[1]], endpoints(fit.2.d)$distimes[[1]]) + r.1.e <- c(fit.1.e$bparms.optim[[1]], endpoints(fit.1.e)$distimes[[1]]) + r.1.d <- c(fit.1.d$bparms.optim[[1]], endpoints(fit.1.d)$distimes[[1]]) + r.2.e <- c(fit.2.e$bparms.optim[[1]], endpoints(fit.2.e)$distimes[[1]]) + r.2.d <- c(fit.2.d$bparms.optim[[1]], endpoints(fit.2.d)$distimes[[1]]) dev.1.e <- 100 * (r.1.e - FOCUS_2006_D_results_schaefer07_means)/r.1.e checkIdentical(as.numeric(abs(dev.1.e)) < 1, rep(TRUE, 3)) @@ -273,7 +273,7 @@ test.mkinfit.schaefer07_complex_example <- function() mkin_wide_to_long(schaefer07_complex_case, time = "time")) s <- summary(fit) r <- schaefer07_complex_results - attach(as.list(fit$parms.all)) + attach(as.list(fit$bparms.optim)) k_parent <- sum(k_parent_A1, k_parent_B1, k_parent_C1) r$mkin <- c( k_parent, diff --git a/vignettes/examples-L1_SFO_plots.pdf b/vignettes/examples-L1_SFO_plots.pdf deleted file mode 100644 index d34116fe..00000000 Binary files a/vignettes/examples-L1_SFO_plots.pdf and /dev/null differ diff --git a/vignettes/examples.Rnw b/vignettes/examples.Rnw index 340d75f7..6f3cfc9d 100644 --- a/vignettes/examples.Rnw +++ b/vignettes/examples.Rnw @@ -108,8 +108,7 @@ is checked. <>= m.L1.FOMC <- mkinfit(FOMC, FOCUS_2006_L1_mkin, quiet=TRUE) -s.m.L1.FOMC <- summary(m.L1.FOMC) -s.m.L1.FOMC$errmin +summary(m.L1.FOMC) @ Due to the higher number of parameters, and the lower number of degrees of freedom @@ -196,7 +195,6 @@ m.L2.DFOP <- mkinfit(DFOP, FOCUS_2006_L2_mkin, parms.ini = c(k1 = 1, k2 = 0.01, g = 0.8), quiet=TRUE) plot(m.L2.DFOP) -summary(m.L2.DFOP) s.m.L2.DFOP <- summary(m.L2.DFOP) s.m.L2.DFOP$errmin @ @@ -219,7 +217,7 @@ FOCUS_2006_L3_mkin <- mkin_wide_to_long(FOCUS_2006_L3) SFO model, summary and plot: <>= -m.L3.SFO <- mkinfit(SFO, FOCUS_2006_L3_mkin, quiet=TRUE) +m.L3.SFO <- mkinfit(SFO, FOCUS_2006_L3_mkin, quiet = TRUE) summary(m.L3.SFO) plot(m.L3.SFO) @ @@ -230,7 +228,7 @@ does not fit very well. The FOMC model performs better: <>= -m.L3.FOMC <- mkinfit(FOMC, FOCUS_2006_L3_mkin, quiet=TRUE) +m.L3.FOMC <- mkinfit(FOMC, FOCUS_2006_L3_mkin, quiet = TRUE) plot(m.L3.FOMC) s.m.L3.FOMC <- summary(m.L3.FOMC) s.m.L3.FOMC$errmin @@ -243,7 +241,7 @@ Fitting the four parameter DFOP model further reduces the $\chi^2$ error level considerably: <>= -m.L3.DFOP <- mkinfit(DFOP, FOCUS_2006_L3_mkin, quiet=TRUE) +m.L3.DFOP <- mkinfit(DFOP, FOCUS_2006_L3_mkin, quiet = TRUE) plot(m.L3.DFOP) s.m.L3.DFOP <- summary(m.L3.DFOP) s.m.L3.DFOP$errmin @@ -267,7 +265,7 @@ FOCUS_2006_L4_mkin <- mkin_wide_to_long(FOCUS_2006_L4) SFO model, summary and plot: <>= -m.L4.SFO <- mkinfit(SFO, FOCUS_2006_L4_mkin, quiet=TRUE) +m.L4.SFO <- mkinfit(SFO, FOCUS_2006_L4_mkin, quiet = TRUE) summary(m.L4.SFO) plot(m.L4.SFO) @ @@ -278,7 +276,7 @@ fits very well. The FOMC model for comparison <>= -m.L4.FOMC <- mkinfit(FOMC, FOCUS_2006_L4_mkin, quiet=TRUE) +m.L4.FOMC <- mkinfit(FOMC, FOCUS_2006_L4_mkin, quiet = TRUE) plot(m.L4.FOMC) s.m.L4.FOMC <- summary(m.L4.FOMC) s.m.L4.FOMC$errmin @@ -287,9 +285,6 @@ s.m.L4.FOMC$errmin The error level at which the $\chi^2$ test passes is slightly lower for the FOMC model. However, the difference appears negligible. -\bibliographystyle{plainnat} -\bibliography{references} - \section{Kinetic evaluations for parent and metabolites} \subsection{Laboratory Data for example compound Z} @@ -300,15 +295,16 @@ report, p.350 <>= LOD = 0.5 FOCUS_2006_Z = data.frame( - t = c(0, 0.04, 0.125, 0.29, 0.54, 1, 2, 3, 4, 7, 10, 14, 21, 42, 61, 96, 124), - Z0 = c(100, 81.7, 70.4, 51.1, 41.2, 6.6, 4.6, 3.9, 4.6, 4.3, 6.8, 2.9, 3.5, - 5.3, 4.4, 1.2, 0.7), - Z1 = c(0, 18.3, 29.6, 46.3, 55.1, 65.7, 39.1, 36, 15.3, 5.6, 1.1, 1.6, 0.6, - 0.5 * LOD, NA, NA, NA), - Z2 = c(0, NA, 0.5 * LOD, 2.6, 3.8, 15.3, 37.2, 31.7, 35.6, 14.5, 0.8, 2.1, - 1.9, 0.5 * LOD, NA, NA, NA), - Z3 = c(0, NA, NA, NA, NA, 0.5 * LOD, 9.2, 13.1, 22.3, 28.4, 32.5, 25.2, 17.2, - 4.8, 4.5, 2.8, 4.4)) + t = c(0, 0.04, 0.125, 0.29, 0.54, 1, 2, 3, 4, 7, 10, 14, 21, + 42, 61, 96, 124), + Z0 = c(100, 81.7, 70.4, 51.1, 41.2, 6.6, 4.6, 3.9, 4.6, 4.3, 6.8, + 2.9, 3.5, 5.3, 4.4, 1.2, 0.7), + Z1 = c(0, 18.3, 29.6, 46.3, 55.1, 65.7, 39.1, 36, 15.3, 5.6, 1.1, + 1.6, 0.6, 0.5 * LOD, NA, NA, NA), + Z2 = c(0, NA, 0.5 * LOD, 2.6, 3.8, 15.3, 37.2, 31.7, 35.6, 14.5, + 0.8, 2.1, 1.9, 0.5 * LOD, NA, NA, NA), + Z3 = c(0, NA, NA, NA, NA, 0.5 * LOD, 9.2, 13.1, 22.3, 28.4, 32.5, + 25.2, 17.2, 4.8, 4.5, 2.8, 4.4)) FOCUS_2006_Z_mkin <- mkin_wide_to_long(FOCUS_2006_Z) @ @@ -320,10 +316,9 @@ with formation and decline of metabolite Z1 and the pathway from parent directly to sink included (default in mkin). <>= -debug(mkinmod) Z.2a <- mkinmod(Z0 = list(type = "SFO", to = "Z1"), Z1 = list(type = "SFO")) -m.Z.2a <- mkinfit(Z.2a, FOCUS_2006_Z_mkin) +m.Z.2a <- mkinfit(Z.2a, FOCUS_2006_Z_mkin, quiet = TRUE) summary(m.Z.2a, data = FALSE) plot(m.Z.2a) @ @@ -340,7 +335,7 @@ A similar result can be obtained when formation fractions are used in the model Z.2a.ff <- mkinmod(Z0 = list(type = "SFO", to = "Z1"), Z1 = list(type = "SFO"), use_of_ff = "max") -m.Z.2a.ff <- mkinfit(Z.2a.ff, FOCUS_2006_Z_mkin) +m.Z.2a.ff <- mkinfit(Z.2a.ff, FOCUS_2006_Z_mkin, quiet = TRUE) summary(m.Z.2a.ff, data = FALSE) plot(m.Z.2a.ff) @ @@ -355,9 +350,11 @@ are used. <>= Z.3 <- mkinmod(Z0 = list(type = "SFO", to = "Z1", sink = FALSE), - Z1 = list(type = "SFO")) -m.Z.3 <- mkinfit(Z.3, FOCUS_2006_Z_mkin, parms.ini = c(k_Z0_Z1 = 0.5)) -m.Z.3 <- mkinfit(Z.3, FOCUS_2006_Z_mkin, solution_type = "deSolve") + Z1 = list(type = "SFO")) +m.Z.3 <- mkinfit(Z.3, FOCUS_2006_Z_mkin, parms.ini = c(k_Z0_Z1 = 0.5), + quiet = TRUE) +m.Z.3 <- mkinfit(Z.3, FOCUS_2006_Z_mkin, solution_type = "deSolve", + quiet = TRUE) summary(m.Z.3, data = FALSE) plot(m.Z.3) @ @@ -374,7 +371,8 @@ solution can be chosen, at the cost of a bit more computing time. Z.4a <- mkinmod(Z0 = list(type = "SFO", to = "Z1", sink = FALSE), Z1 = list(type = "SFO", to = "Z2"), Z2 = list(type = "SFO")) -m.Z.4a <- mkinfit(Z.4a, FOCUS_2006_Z_mkin, parms.ini = c(k_Z0_Z1 = 0.5)) +m.Z.4a <- mkinfit(Z.4a, FOCUS_2006_Z_mkin, parms.ini = c(k_Z0_Z1 = 0.5), + quiet = TRUE) summary(m.Z.4a, data = FALSE) plot(m.Z.4a) @ @@ -391,7 +389,7 @@ Z.5 <- mkinmod(Z0 = list(type = "SFO", to = "Z1", sink = FALSE), Z1 = list(type = "SFO", to = "Z2", sink = FALSE), Z2 = list(type = "SFO")) m.Z.5 <- mkinfit(Z.5, FOCUS_2006_Z_mkin, - parms.ini = c(k_Z0_Z1 = 0.5, k_Z1_Z2 = 0.2)) + parms.ini = c(k_Z0_Z1 = 0.5, k_Z1_Z2 = 0.2), quiet = TRUE) summary(m.Z.5, data = FALSE) plot(m.Z.5) @ @@ -404,7 +402,8 @@ Z.FOCUS <- mkinmod(Z0 = list(type = "SFO", to = "Z1", sink = FALSE), Z2 = list(type = "SFO", to = "Z3"), Z3 = list(type = "SFO")) m.Z.FOCUS <- mkinfit(Z.FOCUS, FOCUS_2006_Z_mkin, - parms.ini = c(k_Z0_Z1 = 0.5, k_Z1_Z2 = 0.2, k_Z2_Z3 = 0.3)) + parms.ini = c(k_Z0_Z1 = 0.5, k_Z1_Z2 = 0.2, k_Z2_Z3 = 0.3), + quiet = TRUE) summary(m.Z.FOCUS, data = FALSE) plot(m.Z.FOCUS) @ @@ -420,16 +419,14 @@ mkinresplot(m.Z.FOCUS, "Z2", lpos = "bottomright") mkinresplot(m.Z.FOCUS, "Z3", lpos = "bottomright") @ - As the FOCUS report states, there is a certain tailing of the time course of metabolite Z3. Also, the time course of the parent compound is not fitted very well using the SFO model, as residues at a certain low level remain. Therefore, an additional model is offered here, using the single first-order -reversible binding (SFORB) model for metabolite Z3. However, the $\chi^2$ error -level is higher for metabolite Z3 using this model, the covariance matrix is -not returned, and graphically the fit is not significantly improved. Therefore, -this appears to be a case of overparamterisation. +reversible binding (SFORB) model for metabolite Z3. As expected, the $\chi^2$ +error level is lower for metabolite Z3 using this model and the graphical +fit for Z3 is improved. However, the covariance matrix is not returned. <>= Z.mkin.1 <- mkinmod(Z0 = list(type = "SFO", to = "Z1", sink = FALSE), @@ -437,18 +434,20 @@ Z.mkin.1 <- mkinmod(Z0 = list(type = "SFO", to = "Z1", sink = FALSE), Z2 = list(type = "SFO", to = "Z3"), Z3 = list(type = "SFORB")) m.Z.mkin.1 <- mkinfit(Z.mkin.1, FOCUS_2006_Z_mkin, - parms.ini = c(k_Z0_Z1 = 0.5, k_Z1_Z2 = 0.3, k_Z2_Z3 = 0.2)) + parms.ini = c(k_Z0_Z1 = 0.5, k_Z1_Z2 = 0.3, k_Z2_Z3 = 0.2), + quiet = TRUE) summary(m.Z.mkin.1, data = FALSE) plot(m.Z.mkin.1) @ -On the other hand, the model fit for the parent compound can be improved by -using the SFORB model. +Therefore, a further stepwise model building is performed starting from the +stage of parent and one metabolite, starting from the assumption that the model +fit for the parent compound can be improved by using the SFORB model. <>= Z.mkin.2 <- mkinmod(Z0 = list(type = "SFORB", to = "Z1", sink = FALSE), Z1 = list(type = "SFO")) -m.Z.mkin.2 <- mkinfit(Z.mkin.2, FOCUS_2006_Z_mkin) +m.Z.mkin.2 <- mkinfit(Z.mkin.2, FOCUS_2006_Z_mkin, quiet = TRUE) summary(m.Z.mkin.2, data = FALSE) plot(m.Z.mkin.2) @ @@ -460,7 +459,7 @@ Then, metabolite Z2 is added. Z.mkin.3 <- mkinmod(Z0 = list(type = "SFORB", to = "Z1", sink = FALSE), Z1 = list(type = "SFO", to = "Z2"), Z2 = list(type = "SFO")) -m.Z.mkin.3 <- mkinfit(Z.mkin.3, FOCUS_2006_Z_mkin) +m.Z.mkin.3 <- mkinfit(Z.mkin.3, FOCUS_2006_Z_mkin, quiet = TRUE) summary(m.Z.mkin.3, data = FALSE) plot(m.Z.mkin.3) @ @@ -474,18 +473,33 @@ Z.mkin.4 <- mkinmod(Z0 = list(type = "SFORB", to = "Z1", sink = FALSE), Z2 = list(type = "SFO", to = "Z3"), Z3 = list(type = "SFO")) m.Z.mkin.4 <- mkinfit(Z.mkin.4, FOCUS_2006_Z_mkin, - parms.ini = c(k_Z1_Z2 = 0.05)) + parms.ini = c(k_Z1_Z2 = 0.05), quiet = TRUE) summary(m.Z.mkin.4, data = FALSE) plot(m.Z.mkin.4) @ -The error level of the fit, but especially of metabolite Z3, can -be improved if the SFORB model is chosen for this metabolite, as this -model is capable of representing the tailing of the metabolite -decline phase. +The error level of the fit, but especially of metabolite Z3, can be improved if +the SFORB model is chosen for this metabolite, as this model is capable of +representing the tailing of the metabolite decline phase. + +Using the SFORB additionally for Z1 or Z2 did not further improve the result. +Therefore, the model \texttt{Z.mkin.5} is proposed as the best-fit model +for the dataset from Appendix 7 of the FOCUS report. + +<>= +Z.mkin.5 <- mkinmod(Z0 = list(type = "SFORB", to = "Z1", sink = FALSE), + Z1 = list(type = "SFO", to = "Z2", sink = FALSE), + Z2 = list(type = "SFO", to = "Z3"), + Z3 = list(type = "SFORB")) +m.Z.mkin.5 <- mkinfit(Z.mkin.5, FOCUS_2006_Z_mkin, + parms.ini = c(k_Z1_Z2 = 0.2), quiet = TRUE) +summary(m.Z.mkin.5, data = FALSE) +plot(m.Z.mkin.5) +@ + +\bibliographystyle{plainnat} +\bibliography{references} -Using the SFORB additionally for Z1 or Z2 did not further improve -the result. \end{document} % vim: set foldmethod=syntax: diff --git a/vignettes/examples.pdf b/vignettes/examples.pdf index 92375460..3bd0c37e 100644 Binary files a/vignettes/examples.pdf and b/vignettes/examples.pdf differ diff --git a/vignettes/mkin.pdf b/vignettes/mkin.pdf index 9738230e..073e3610 100644 Binary files a/vignettes/mkin.pdf and b/vignettes/mkin.pdf differ diff --git a/vignettes/run.bat b/vignettes/run.bat deleted file mode 100644 index c28c6663..00000000 --- a/vignettes/run.bat +++ /dev/null @@ -1,5 +0,0 @@ -R.exe -e "Sweave('mkin.Rnw', stylepath=FALSE)" -pdflatex.exe mkin -bibtex.exe mkin -pdflatex.exe mkin -pdflatex.exe mkin -- cgit v1.2.1