diff options
| -rw-r--r-- | R/mkinfit.R | 15 | ||||
| -rw-r--r-- | R/mkinplot.R | 82 | ||||
| -rw-r--r-- | TODO | 6 | ||||
| -rw-r--r-- | inst/unitTests/runit.mkinfit.R | 75 | 
4 files changed, 95 insertions, 83 deletions
| diff --git a/R/mkinfit.R b/R/mkinfit.R index 6e455e18..cb0396f7 100644 --- a/R/mkinfit.R +++ b/R/mkinfit.R @@ -170,13 +170,11 @@ mkinfit <- function(mkinmod, observed,    # We need to return some more data for summary and plotting
    fit$solution_type <- solution_type
 -  if (solution_type == "eigen") {
 -    fit$coefmat <- mkinmod$coefmat
 -  } 
 -  # We also need various other information for summary and plotting
 -  fit$map <- mkinmod$map
 -  fit$diffs <- mkinmod$diffs
 +  # We also need the model for summary and plotting
 +  fit$mkinmod <- mkinmod
 +
 +  # We need data and predictions for summary and plotting
    fit$observed <- mkin_long_to_wide(observed)
    predicted_long <- mkin_wide_to_long(out_predicted, time = "time")
    fit$predicted <- out_predicted
 @@ -348,6 +346,7 @@ summary.mkinfit <- function(object, data = TRUE, distimes = TRUE, ...) {            Rversion = paste(R.version$major, R.version$minor, sep="."),
  	  date.fit = object$date,
  	  date.summary = date(),
 +	  use_of_ff = object$mkinmod$use_of_ff,
            residuals = object$residuals,
            residualVariance = resvar,
            sigma = sqrt(resvar),
 @@ -358,7 +357,7 @@ summary.mkinfit <- function(object, data = TRUE, distimes = TRUE, ...) {            stopmess = message,
            par = param)
 -  ans$diffs <- object$diffs
 +  ans$diffs <- object$mkinmod$diffs
    if(data) ans$data <- object$data
    ans$start <- object$start
 @@ -411,7 +410,7 @@ print.summary.mkinfit <- function(x, digits = max(3, getOption("digits") - 3), .    }    
    printff <- !is.null(x$ff)
 -  if(printff){
 +  if(printff & x$use_of_ff == "min"){
      cat("\nEstimated formation fractions:\n")
      print(data.frame(ff = x$ff), digits=digits,...)
    }    
 diff --git a/R/mkinplot.R b/R/mkinplot.R index d665bc23..789a6f98 100644 --- a/R/mkinplot.R +++ b/R/mkinplot.R @@ -1,14 +1,14 @@  mkinplot <- function(fit, xlab = "Time", ylab = "Observed", xlim = range(fit$data$time), ylim = range(fit$data$observed, na.rm = TRUE), legend = TRUE, ...)  { -  solution = fit$solution +  solution_type = fit$solution_type    fixed <- fit$fixed$value    names(fixed) <- rownames(fit$fixed) -  parms.all <- c(fit$par, fixed) +  parms.all <- c(fit$parms.all, fixed)    ininames <- c(      rownames(subset(fit$start, type == "state")),      rownames(subset(fit$fixed, type == "state")))    odeini <- parms.all[ininames] -  names(odeini) <- names(fit$diffs) +  names(odeini) <- names(fit$mkinmod$diffs)    outtimes <- seq(xlim[1], xlim[2], length.out=100) @@ -17,84 +17,22 @@ mkinplot <- function(fit, xlab = "Time", ylab = "Observed", xlim = range(fit$dat      rownames(subset(fit$fixed, type == "deparm")))    odeparms <- parms.all[odenames] -  # Solve the system -  evalparse <- function(string) -  { -    eval(parse(text=string), as.list(c(odeparms, odeini))) -  } -  if (solution == "analytical") { -    parent.type = names(fit$map[[1]])[1]   -    parent.name = names(fit$diffs)[[1]] -    o <- switch(parent.type, -      SFO = SFO.solution(outtimes,  -          evalparse(parent.name), -          evalparse(paste("k", parent.name, "sink", sep="_"))), -      FOMC = FOMC.solution(outtimes, -          evalparse(parent.name), -          evalparse("alpha"), evalparse("beta")), -      DFOP = DFOP.solution(outtimes, -          evalparse(parent.name), -          evalparse("k1"), evalparse("k2"), -          evalparse("g")), -      HS = HS.solution(outtimes, -          evalparse(parent.name), -          evalparse("k1"), evalparse("k2"), -          evalparse("tb")), -      SFORB = SFORB.solution(outtimes, -          evalparse(parent.name), -          evalparse(paste("k", parent.name, "free_bound", sep="_")), -          evalparse(paste("k", parent.name, "bound_free", sep="_")), -          evalparse(paste("k", parent.name, "free_sink", sep="_"))) -    ) -    out <- cbind(outtimes, o) -    dimnames(out) <- list(outtimes, c("time", parent.name)) -  } -  if (solution == "eigen") { -    coefmat.num <- matrix(sapply(as.vector(fit$coefmat), evalparse),  -      nrow = length(odeini)) -    e <- eigen(coefmat.num) -    c <- solve(e$vectors, odeini) -    f.out <- function(t) { -      e$vectors %*% diag(exp(e$values * t), nrow=length(odeini)) %*% c -    } -    o <- matrix(mapply(f.out, outtimes),  -      nrow = length(odeini), ncol = length(outtimes)) -    dimnames(o) <- list(names(odeini), NULL) -    out <- cbind(time = outtimes, t(o)) -  }  -  if (solution == "deSolve") { -    out <- ode( -      y = odeini, -      times = outtimes, -      func = fit$mkindiff,  -      parms = odeparms, -      atol = fit$atol -    ) -  } -     -  # Output transformation for models with unobserved compartments like SFORB -  out_transformed <- data.frame(time = out[,"time"]) -  for (var in names(fit$map)) { -    if(length(fit$map[[var]]) == 1) { -      out_transformed[var] <- out[, var] -    } else { -      out_transformed[var] <- rowSums(out[, fit$map[[var]]]) -    } -  }     +  out <- mkinpredict(fit$mkinmod, odeparms, odeini, outtimes,  +          solution_type = solution_type, ...)    # Plot the data and model output    plot(0, type="n",       xlim = xlim, ylim = ylim,      xlab = xlab, ylab = ylab, ...) -  col_obs <- pch_obs <- 1:length(fit$map) -  names(col_obs) <- names(pch_obs) <- names(fit$map) -  for (obs_var in names(fit$map)) { +  col_obs <- pch_obs <- 1:length(fit$mkinmod$map) +  names(col_obs) <- names(pch_obs) <- names(fit$mkinmod$map) +  for (obs_var in names(fit$mkinmod$map)) {      points(subset(fit$data, variable == obs_var, c(time, observed)),       pch = pch_obs[obs_var], col = col_obs[obs_var])    } -  matlines(out_transformed$time, out_transformed[-1]) +  matlines(out$time, out[-1])    if (legend == TRUE) { -    legend("topright", inset=c(0.05, 0.05), legend=names(fit$map), +    legend("topright", inset=c(0.05, 0.05), legend=names(fit$mkinmod$map),        col=col_obs, pch=pch_obs, lty=1:length(pch_obs))    }  } @@ -1,11 +1,11 @@  Must have: -- Adapt mkinplot function +- Some more testing with coupled models with FOMC, DFOP, HS and SFORB for parent +- Some testing with SFORB for metabolites  Nice to have: -- Fix remaining problem with the schaefer complex test data (test.R: fit.2.eigen)  - Calculate confidence intervals for parameters assuming normal distribution  - Calculate confidence intervals for DT50 and DT90 values when only one parameter is involved -- Add unit tests for mkinfit +- Add more unit tests for mkinfit  - Document validation against fits documented in chapter 13 of FOCUS (2006)  - Reproduce example anaylses (L1, L2, ...) in FOCUS (2006)  - Generate confidence intervals for DT50 and DT90 values for other cases diff --git a/inst/unitTests/runit.mkinfit.R b/inst/unitTests/runit.mkinfit.R index 2030f852..e2fc8c3f 100644 --- a/inst/unitTests/runit.mkinfit.R +++ b/inst/unitTests/runit.mkinfit.R @@ -222,6 +222,43 @@ test.FOCUS_2006_SFORB <- function()    checkIdentical(dev.B.SFORB.2 < 1, rep(TRUE, length(dev.B.SFORB.2)))
  } # }}}
 +# Test SFO_SFO model with FOCUS_2006_D against Schaefer 2007 paper, tolerance = 1% # {{{
 +test.FOCUS_2006_D_SFO_SFO <- function()
 +{
 +  SFO_SFO.1 <- mkinmod(parent = list(type = "SFO", to = "m1"),
 +         m1 = list(type = "SFO"), use_of_ff = "min")
 +  SFO_SFO.2 <- mkinmod(parent = list(type = "SFO", to = "m1"),
 +         m1 = list(type = "SFO"), use_of_ff = "max")
 +
 +  fit.1.e <- mkinfit(SFO_SFO.1, FOCUS_2006_D)
 +  fit.1.d <- mkinfit(SFO_SFO.1, solution_type = "deSolve", FOCUS_2006_D)
 +  #fit.2.e <- mkinfit(SFO_SFO.2, FOCUS_2006_D, plot=TRUE)
 +  SFO <- mkinmod(parent = list(type = "SFO"))
 +  f.SFO <- mkinfit(SFO, FOCUS_2006_D)
 +  #fit.2.e <- mkinfit(SFO_SFO.2, parms.ini = f.SFO$odeparms.final, FOCUS_2006_D)
 +  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)
 +
 +  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]], fit.1.e$distimes[[1]])
 +  r.1.d <- c(fit.1.d$parms.all[[1]], fit.1.d$distimes[[1]])
 +  r.2.e <- c(fit.2.e$parms.all[[1]], fit.2.e$distimes[[1]])
 +  r.2.d <- c(fit.2.d$parms.all[[1]], 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))
 +  dev.1.d <- 100 * (r.1.d - FOCUS_2006_D_results_schaefer07_means)/r.1.d 
 +  checkIdentical(as.numeric(abs(dev.1.d)) < 1, rep(TRUE, 3))
 +  dev.2.e <- 100 * (r.2.e - FOCUS_2006_D_results_schaefer07_means)/r.2.e 
 +  checkIdentical(as.numeric(abs(dev.2.e)) < 1, rep(TRUE, 3))
 +  dev.2.d <- 100 * (r.2.d - FOCUS_2006_D_results_schaefer07_means)/r.2.d 
 +  checkIdentical(as.numeric(abs(dev.2.d)) < 1, rep(TRUE, 3))
 +} # }}}
 +
  # Test eigenvalue based fit to Schaefer 2007 data against solution from conference paper {{{
  test.mkinfit.schaefer07_complex_example <- function()
  {
 @@ -258,4 +295,42 @@ test.mkinfit.schaefer07_complex_example <- function()    checkIdentical(r$mkin.deviation < 10, rep(TRUE, length(r$mkin.deviation)))
  } # }}}
 +# Test deSolve based fit to Schaefer 2007 data against solution from conference paper {{{
 +test.mkinfit.schaefer07_complex_example <- function()
 +{
 +  schaefer07_complex_model <- mkinmod(
 +    parent = list(type = "SFO", to = c("A1", "B1", "C1"), sink = FALSE),
 +    A1 = list(type = "SFO", to = "A2"),
 +    B1 = list(type = "SFO"),
 +    C1 = list(type = "SFO"),
 +    A2 = list(type = "SFO"))
 +  
 +  # Works fine with n.outtimes = 1000 but takes too much time
 +  #   fit <- mkinfit(schaefer07_complex_model, 
 +  #     mkin_wide_to_long(schaefer07_complex_case, time = "time"), 
 +  #     n.outtimes = 1000, solution_type = "deSolve")
 +  #   s <- summary(fit)
 +  #   r <- schaefer07_complex_results
 +  #   attach(as.list(fit$parms.all))
 +  #   k_parent <- sum(k_parent_A1, k_parent_B1, k_parent_C1)
 +  #   r$mkin <- c(
 +  #     k_parent,
 +  #     s$distimes["parent", "DT50"],
 +  #     s$ff["parent_A1"],
 +  #     sum(k_A1_sink, k_A1_A2),
 +  #     s$distimes["A1", "DT50"],
 +  #     s$ff["parent_B1"],
 +  #     k_B1_sink,
 +  #     s$distimes["B1", "DT50"],
 +  #     s$ff["parent_C1"],
 +  #     k_C1_sink,
 +  #     s$distimes["C1", "DT50"],
 +  #     s$ff["A1_A2"],
 +  #     k_A2_sink,
 +  #     s$distimes["A2", "DT50"])
 +  #   r$means <- (r$KinGUI + r$ModelMaker)/2
 +  #   r$mkin.deviation <- abs(round(100 * ((r$mkin - r$means)/r$means), digits=1))
 +  #   checkIdentical(r$mkin.deviation < 10, rep(TRUE, length(r$mkin.deviation)))
 +} # }}}
 +
  # vim: set foldmethod=marker ts=2 sw=2 expandtab:
 | 
