aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohannes Ranke <jranke@uni-bremen.de>2020-04-15 18:13:04 +0200
committerJohannes Ranke <jranke@uni-bremen.de>2020-04-15 19:00:06 +0200
commit42171ba55222383a0d47e5aacd46a972819e7812 (patch)
tree190320919fe83aece30b654bfeb7687241e36f99
parent637bd14fed5ab8a615f0d879012f12c59e1532a4 (diff)
Include random effects in starting parameters
- mean_degparms() now optionally returns starting values for fixed and random effects, which makes it possible to obtain acceptable fits also in more difficult cases (with more parameters) - Fix the anova method, as it is currently not enough to inherit from lme: https://bugs.r-project.org/bugzilla/show_bug.cgi?id=17761 - Show fit information, and per default also errmin information in plot.nlme.mmkin() - Examples for nlme.mmkin: Decrease tolerance and increase the number of iterations in the PNLS step in order to be able to fit FOMC-SFO and DFOP-SFO
-rw-r--r--NAMESPACE3
-rw-r--r--R/nlme.R88
-rw-r--r--R/nlme.mmkin.R100
-rw-r--r--R/plot.nlme.mmkin.R22
-rw-r--r--docs/reference/index.html2
-rw-r--r--docs/reference/nlme.html80
-rw-r--r--docs/reference/nlme.mmkin-1.pngbin0 -> 69863 bytes
-rw-r--r--docs/reference/nlme.mmkin-2.pngbin0 -> 70426 bytes
-rw-r--r--docs/reference/nlme.mmkin-3.pngbin0 -> 70519 bytes
-rw-r--r--docs/reference/nlme.mmkin-4.pngbin0 -> 72803 bytes
-rw-r--r--docs/reference/nlme.mmkin-5.pngbin0 -> 72587 bytes
-rw-r--r--docs/reference/nlme.mmkin-6.pngbin0 -> 71892 bytes
-rw-r--r--docs/reference/nlme.mmkin-7.pngbin0 -> 72316 bytes
-rw-r--r--docs/reference/nlme.mmkin.html172
-rw-r--r--docs/reference/plot.mmkin-3.pngbin25550 -> 32259 bytes
-rw-r--r--docs/reference/plot.mmkin-4.pngbin38129 -> 25550 bytes
-rw-r--r--docs/reference/plot.mmkin-5.pngbin0 -> 38129 bytes
-rw-r--r--docs/reference/plot.mmkin.html8
-rw-r--r--docs/reference/plot.nlme.mmkin-1.pngbin32297 -> 35382 bytes
-rw-r--r--docs/reference/plot.nlme.mmkin-2.pngbin0 -> 35313 bytes
-rw-r--r--docs/reference/plot.nlme.mmkin.html22
-rw-r--r--man/nlme.Rd78
-rw-r--r--man/nlme.mmkin.Rd63
-rw-r--r--man/plot.mmkin.Rd3
-rw-r--r--man/plot.nlme.mmkin.Rd15
25 files changed, 420 insertions, 236 deletions
diff --git a/NAMESPACE b/NAMESPACE
index fce1c5f7..ef610857 100644
--- a/NAMESPACE
+++ b/NAMESPACE
@@ -3,6 +3,7 @@
S3method("[",mmkin)
S3method(AIC,mmkin)
S3method(BIC,mmkin)
+S3method(anova,nlme.mmkin)
S3method(aw,mkinfit)
S3method(aw,mmkin)
S3method(confint,mkinfit)
@@ -22,10 +23,12 @@ S3method(plot,nlme.mmkin)
S3method(print,mkinds)
S3method(print,mkinmod)
S3method(print,nafta)
+S3method(print,nlme.mmkin)
S3method(print,summary.mkinfit)
S3method(residuals,mkinfit)
S3method(summary,mkinfit)
S3method(update,mkinfit)
+S3method(update,nlme.mmkin)
export(CAKE_export)
export(DFOP.solution)
export(FOMC.solution)
diff --git a/R/nlme.R b/R/nlme.R
index fafaa7b6..ef93327c 100644
--- a/R/nlme.R
+++ b/R/nlme.R
@@ -8,6 +8,7 @@
#' @param object An mmkin row object containing several fits of the same model to different datasets
#' @import nlme
#' @rdname nlme
+#' @seealso \code{\link{nlme.mmkin}}
#' @examples
#' sampling_times = c(0, 1, 3, 7, 14, 28, 60, 90, 120)
#' m_SFO <- mkinmod(parent = mkinsub("SFO"))
@@ -47,73 +48,9 @@
#' start = mean_dp)
#' summary(m_nlme)
#' plot(augPred(m_nlme, level = 0:1), layout = c(3, 1))
+#' # augPred does not seem to work on fits with more than one state
+#' # variable
#'
-#' \dontrun{
-#' # Test on some real data
-#' ds_2 <- lapply(experimental_data_for_UBA_2019[6:10],
-#' function(x) x$data[c("name", "time", "value")])
-#' m_sfo_sfo <- mkinmod(parent = mkinsub("SFO", "A1"),
-#' A1 = mkinsub("SFO"), use_of_ff = "min")
-#' m_sfo_sfo_ff <- mkinmod(parent = mkinsub("SFO", "A1"),
-#' A1 = mkinsub("SFO"), use_of_ff = "max")
-#' m_fomc_sfo <- mkinmod(parent = mkinsub("FOMC", "A1"),
-#' A1 = mkinsub("SFO"))
-#' m_dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "A1"),
-#' A1 = mkinsub("SFO"))
-#' m_sforb_sfo <- mkinmod(parent = mkinsub("SFORB", "A1"),
-#' A1 = mkinsub("SFO"))
-#'
-#' f_2 <- mmkin(list("SFO-SFO" = m_sfo_sfo,
-#' "SFO-SFO-ff" = m_sfo_sfo_ff,
-#' "FOMC-SFO" = m_fomc_sfo,
-#' "DFOP-SFO" = m_dfop_sfo,
-#' "SFORB-SFO" = m_sforb_sfo),
-#' ds_2)
-#'
-#' grouped_data_2 <- nlme_data(f_2["SFO-SFO", ])
-#'
-#' mean_dp_sfo_sfo <- mean_degparms(f_2["SFO-SFO", ])
-#' mean_dp_sfo_sfo_ff <- mean_degparms(f_2["SFO-SFO-ff", ])
-#' mean_dp_fomc_sfo <- mean_degparms(f_2["FOMC-SFO", ])
-#' mean_dp_dfop_sfo <- mean_degparms(f_2["DFOP-SFO", ])
-#' mean_dp_sforb_sfo <- mean_degparms(f_2["SFORB-SFO", ])
-#'
-#' nlme_f_sfo_sfo <- nlme_function(f_2["SFO-SFO", ])
-#' nlme_f_sfo_sfo_ff <- nlme_function(f_2["SFO-SFO-ff", ])
-#' nlme_f_fomc_sfo <- nlme_function(f_2["FOMC-SFO", ])
-#' assign("nlme_f_sfo_sfo", nlme_f_sfo_sfo, globalenv())
-#' assign("nlme_f_sfo_sfo_ff", nlme_f_sfo_sfo_ff, globalenv())
-#' assign("nlme_f_fomc_sfo", nlme_f_fomc_sfo, globalenv())
-#'
-#' # Allowing for correlations between random effects (not shown)
-#' # leads to non-convergence
-#' f_nlme_sfo_sfo <- nlme(value ~ nlme_f_sfo_sfo(name, time,
-#' parent_0, log_k_parent_sink, log_k_parent_A1, log_k_A1_sink),
-#' data = grouped_data_2,
-#' fixed = parent_0 + log_k_parent_sink + log_k_parent_A1 + log_k_A1_sink ~ 1,
-#' random = pdDiag(parent_0 + log_k_parent_sink + log_k_parent_A1 + log_k_A1_sink ~ 1),
-#' start = mean_dp_sfo_sfo)
-#' # augPred does not see to work on this object, so no plot is shown
-#'
-#' # The same model fitted with transformed formation fractions does not converge
-#' f_nlme_sfo_sfo_ff <- nlme(value ~ nlme_f_sfo_sfo_ff(name, time,
-#' parent_0, log_k_parent, log_k_A1, f_parent_ilr_1),
-#' data = grouped_data_2,
-#' fixed = parent_0 + log_k_parent + log_k_A1 + f_parent_ilr_1 ~ 1,
-#' random = pdDiag(parent_0 + log_k_parent + log_k_A1 + f_parent_ilr_1 ~ 1),
-#' start = mean_dp_sfo_sfo_ff)
-#'
-#' f_nlme_fomc_sfo <- nlme(value ~ nlme_f_fomc_sfo(name, time,
-#' parent_0, log_alpha, log_beta, log_k_A1, f_parent_ilr_1),
-#' data = grouped_data_2,
-#' fixed = parent_0 + log_alpha + log_beta + log_k_A1 + f_parent_ilr_1 ~ 1,
-#' random = pdDiag(parent_0 + log_alpha + log_beta + log_k_A1 + f_parent_ilr_1 ~ 1),
-#' start = mean_dp_fomc_sfo)
-#'
-#' # DFOP-SFO and SFORB-SFO did not converge with full random effects
-#'
-#' anova(f_nlme_fomc_sfo, f_nlme_sfo_sfo)
-#' }
#' @return A function that can be used with nlme
#' @export
nlme_function <- function(object) {
@@ -185,14 +122,25 @@ nlme_function <- function(object) {
}
#' @rdname nlme
-#' @return A named vector containing mean values of the fitted degradation model parameters
+#' @return If random is FALSE (default), a named vector containing mean values
+#' of the fitted degradation model parameters. If random is TRUE, a list with
+#' fixed and random effects, in the format required by the start argument of
+#' nlme for the case of a single grouping variable ds?
+#' @param random Should a list with fixed and random effects be returned?
#' @export
-mean_degparms <- function(object) {
+mean_degparms <- function(object, random = FALSE) {
if (nrow(object) > 1) stop("Only row objects allowed")
degparm_mat_trans <- sapply(object, parms, transformed = TRUE)
mean_degparm_names <- setdiff(rownames(degparm_mat_trans), names(object[[1]]$errparms))
- res <- apply(degparm_mat_trans[mean_degparm_names, ], 1, mean)
- return(res)
+ fixed <- apply(degparm_mat_trans[mean_degparm_names, ], 1, mean)
+ if (random) {
+ degparm_mat_trans[mean_degparm_names, ]
+ random <- t(apply(degparm_mat_trans[mean_degparm_names, ], 2, function(column) column - fixed))
+ rownames(random) <- as.character(1:nrow(random))
+ return(list(fixed = fixed, random = list(ds = random)))
+ } else {
+ return(fixed)
+ }
}
#' @rdname nlme
diff --git a/R/nlme.mmkin.R b/R/nlme.mmkin.R
index 2ee46f33..6e3467ed 100644
--- a/R/nlme.mmkin.R
+++ b/R/nlme.mmkin.R
@@ -32,9 +32,52 @@
#' f <- mmkin("SFO", ds, quiet = TRUE, cores = 1)
#' library(nlme)
#' f_nlme <- nlme(f)
-#' nlme(f, random = parent_0 ~ 1)
-#' f_nlme <- nlme(f, start = c(parent_0 = 100, log_k_parent_sink = 0.1))
-#' update(f_nlme, random = parent_0 ~ 1)
+#' print(f_nlme)
+#' f_nlme_2 <- nlme(f, start = c(parent_0 = 100, log_k_parent_sink = 0.1))
+#' update(f_nlme_2, random = parent_0 ~ 1)
+#' \dontrun{
+#' # Test on some real data
+#' ds_2 <- lapply(experimental_data_for_UBA_2019[6:10],
+#' function(x) x$data[c("name", "time", "value")])
+#' m_sfo_sfo <- mkinmod(parent = mkinsub("SFO", "A1"),
+#' A1 = mkinsub("SFO"), use_of_ff = "min", quiet = TRUE)
+#' m_sfo_sfo_ff <- mkinmod(parent = mkinsub("SFO", "A1"),
+#' A1 = mkinsub("SFO"), use_of_ff = "max", quiet = TRUE)
+#' m_fomc_sfo <- mkinmod(parent = mkinsub("FOMC", "A1"),
+#' A1 = mkinsub("SFO"), quiet = TRUE)
+#' m_dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "A1"),
+#' A1 = mkinsub("SFO"), quiet = TRUE)
+#'
+#' f_2 <- mmkin(list("SFO-SFO" = m_sfo_sfo,
+#' "SFO-SFO-ff" = m_sfo_sfo_ff,
+#' "FOMC-SFO" = m_fomc_sfo,
+#' "DFOP-SFO" = m_dfop_sfo),
+#' ds_2, quiet = TRUE)
+#' plot(f_2["SFO-SFO", 3:4]) # Separate fits for datasets 3 and 4
+#'
+#' f_nlme_sfo_sfo <- nlme(f_2["SFO-SFO", ])
+#' # plot(f_nlme_sfo_sfo) # not feasible with pkgdown figures
+#' plot(f_nlme_sfo_sfo, 3:4) # Global mixed model: Fits for datasets 3 and 4
+#'
+#' # With formation fractions
+#' f_nlme_sfo_sfo_ff <- nlme(f_2["SFO-SFO-ff", ])
+#' plot(f_nlme_sfo_sfo_ff, 3:4) # chi2 different due to different df attribution
+#'
+#' # For more parameters, we need to increase pnlsMaxIter and the tolerance
+#' # to get convergence
+#' f_nlme_fomc_sfo <- nlme(f_2["FOMC-SFO", ],
+#' control = list(pnlsMaxIter = 100, tolerance = 1e-4), verbose = TRUE)
+#' f_nlme_dfop_sfo <- nlme(f_2["DFOP-SFO", ],
+#' control = list(pnlsMaxIter = 120, tolerance = 5e-4), verbose = TRUE)
+#' plot(f_2["FOMC-SFO", 3:4])
+#' plot(f_nlme_fomc_sfo, 3:4)
+#'
+#' plot(f_2["DFOP-SFO", 3:4])
+#' plot(f_nlme_dfop_sfo, 3:4)
+#'
+#' anova(f_nlme_dfop_sfo, f_nlme_fomc_sfo, f_nlme_sfo_sfo)
+#' anova(f_nlme_dfop_sfo, f_nlme_sfo_sfo) # if we ignore FOMC
+#' }
# Code inspired by nlme.nlsList
nlme.mmkin <- function(model, data = sys.frame(sys.parent()),
fixed, random = fixed,
@@ -68,7 +111,7 @@ nlme.mmkin <- function(model, data = sys.frame(sys.parent()),
thisCall[["data"]] <- nlme_data(model)
if (missing(start)) {
- thisCall[["start"]] <- mean_dp
+ thisCall[["start"]] <- mean_degparms(model, random = TRUE)
}
thisCall[["fixed"]] <- lapply(as.list(dp_names), function(el)
@@ -84,3 +127,52 @@ nlme.mmkin <- function(model, data = sys.frame(sys.parent()),
return(val)
}
+#' @export
+#' @rdname nlme.mmkin
+#' @param x An nlme.mmkin object to print
+#' @param data Should the data be printed?
+#' @param ... Further arguments as in the generic
+print.nlme.mmkin <- function(x, ...) {
+ x$call$data <- "Not shown"
+ NextMethod("print", x)
+}
+
+#' @export
+#' @rdname nlme.mmkin
+#' @param object An nlme.mmkin object to update
+#' @param ... Update specifications passed to update.nlme
+update.nlme.mmkin <- function(object, ...) {
+ res <- NextMethod()
+ res$mmkin_orig <- object$mmkin_orig
+ class(res) <- c("nlme.mmkin", "nlme", "lme")
+ return(res)
+}
+
+# The following is necessary as long as R bug 17761 is not fixed
+# https://bugs.r-project.org/bugzilla/show_bug.cgi?id=17761
+#' @export
+anova.nlme.mmkin <- function(object, ...) {
+ thisCall <- as.list(match.call())[-1]
+ object_name <- as.character(thisCall[[1]])
+ other_object_names <- sapply(thisCall[-1], as.character)
+
+ remove_class <- function(object, classname) {
+ old_class <- class(object)
+ class(object) <- setdiff(old_class, classname)
+ return(object)
+ }
+ object <- remove_class(object, "nlme.mmkin")
+ other_objects <- list(...)
+ other_objects <- lapply(other_objects, remove_class, "nlme.mmkin")
+
+ env <- new.env()
+ assign(object_name, object, env)
+ for (i in seq_along(other_objects)) {
+ assign(other_object_names[i], other_objects[[i]], env)
+ }
+ res <- eval(parse(text = paste0("anova.lme(", object_name, ", ",
+ paste(other_object_names, collapse = ", "), ")")),
+ envir = env)
+
+ return(res)
+}
diff --git a/R/plot.nlme.mmkin.R b/R/plot.nlme.mmkin.R
index ef6d100a..0f3ad715 100644
--- a/R/plot.nlme.mmkin.R
+++ b/R/plot.nlme.mmkin.R
@@ -11,6 +11,12 @@
#' @param standardized Should the residuals be standardized? This option
#' is passed to \code{\link{mkinresplot}}, it only takes effect if
#' `resplot = "time"`.
+#' @param show_errmin Should the chi2 error level be shown on top of the plots
+#' to the left?
+#' @param errmin_var The variable for which the FOCUS chi2 error value should
+#' be shown.
+#' @param errmin_digits The number of significant digits for rounding the FOCUS
+#' chi2 error percentage.
#' @param cex Passed to the plot functions and \code{\link{mtext}}.
#' @param rel.height.middle The relative height of the middle plot, if more
#' than two rows of plots are shown.
@@ -25,16 +31,19 @@
#' function(x) subset(x$data[c("name", "time", "value")], name == "parent"))
#' f <- mmkin("SFO", ds, quiet = TRUE, cores = 1)
#' #plot(f) # too many panels for pkgdown
+#' plot(f[, 3:4])
#' library(nlme)
#' f_nlme <- nlme(f)
#'
#' #plot(f_nlme) # too many panels for pkgdown
-#' plot(f_nlme, 1:2)
+#' plot(f_nlme, 3:4)
#' @export
plot.nlme.mmkin <- function(x, i = 1:ncol(x$mmkin_orig),
main = "auto", legends = 1,
resplot = c("time", "errmod"),
standardized = FALSE,
+ show_errmin = TRUE,
+ errmin_var = "All data", errmin_digits = 3,
cex = 0.7, rel.height.middle = 0.9,
ymax = "auto", ...)
{
@@ -79,13 +88,14 @@ plot.nlme.mmkin <- function(x, i = 1:ncol(x$mmkin_orig),
state_ini[names(odeini_optim)] <- odeini_optim
odeparms <- fit_a$bparms.ode
- odeparms[names(odeparms)] <- odeparms_optim
+ odeparms[names(odeparms_optim)] <- odeparms_optim
mkinfit_call[["observed"]] <- ds[[a]]
mkinfit_call[["parms.ini"]] <- odeparms
mkinfit_call[["state.ini"]] <- state_ini
- mkinfit_call[["control"]] <- list(iter.max = 1)
+ mkinfit_call[["control"]] <- list(iter.max = 0)
+ mkinfit_call[["quiet"]] <- TRUE
res <- suppressWarnings(do.call("mkinfit", mkinfit_call))
return(res)
@@ -94,9 +104,11 @@ plot.nlme.mmkin <- function(x, i = 1:ncol(x$mmkin_orig),
# Set dimensions with names and the class (mmkin)
attributes(mmkin_nlme) <- attributes(x$mmkin_orig[, i])
- plot(mmkin_nlme[, i], main = main, legends = legends,
+ plot(mmkin_nlme, main = main, legends = legends,
resplot = resplot, standardized = standardized,
- show_errmin = FALSE, cex = cex,
+ show_errmin = show_errmin,
+ errmin_var = errmin_var, errmin_digits = errmin_digits,
+ cex = cex,
rel.height.middle = rel.height.middle,
ymax = ymax, ...)
diff --git a/docs/reference/index.html b/docs/reference/index.html
index 3c5f1b38..f4de5bd8 100644
--- a/docs/reference/index.html
+++ b/docs/reference/index.html
@@ -281,7 +281,7 @@ of an mmkin object</p></td>
<tr>
<td>
- <p><code><a href="nlme.mmkin.html">nlme(<i>&lt;mmkin&gt;</i>)</a></code> </p>
+ <p><code><a href="nlme.mmkin.html">nlme(<i>&lt;mmkin&gt;</i>)</a></code> <code><a href="nlme.mmkin.html">print(<i>&lt;nlme.mmkin&gt;</i>)</a></code> <code><a href="nlme.mmkin.html">update(<i>&lt;nlme.mmkin&gt;</i>)</a></code> </p>
</td>
<td><p>Create an nlme model for an mmkin row object</p></td>
</tr><tr>
diff --git a/docs/reference/nlme.html b/docs/reference/nlme.html
index 981845fe..70c6b63c 100644
--- a/docs/reference/nlme.html
+++ b/docs/reference/nlme.html
@@ -144,7 +144,7 @@ datasets.</p>
<pre class="usage"><span class='fu'>nlme_function</span>(<span class='no'>object</span>)
-<span class='fu'>mean_degparms</span>(<span class='no'>object</span>)
+<span class='fu'>mean_degparms</span>(<span class='no'>object</span>, <span class='kw'>random</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>nlme_data</span>(<span class='no'>object</span>)</pre>
@@ -155,13 +155,23 @@ datasets.</p>
<th>object</th>
<td><p>An mmkin row object containing several fits of the same model to different datasets</p></td>
</tr>
+ <tr>
+ <th>random</th>
+ <td><p>Should a list with fixed and random effects be returned?</p></td>
+ </tr>
</table>
<h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2>
<p>A function that can be used with nlme</p>
-<p>A named vector containing mean values of the fitted degradation model parameters</p>
+<p>If random is FALSE (default), a named vector containing mean values
+ of the fitted degradation model parameters. If random is TRUE, a list with
+ fixed and random effects, in the format required by the start argument of
+ nlme for the case of a single grouping variable ds?</p>
<p>A <code><a href='https://rdrr.io/pkg/nlme/man/groupedData.html'>groupedData</a></code> object</p>
+ <h2 class="hasAnchor" id="see-also"><a class="anchor" href="#see-also"></a>See also</h2>
+
+ <div class='dont-index'><p><code><a href='nlme.mmkin.html'>nlme.mmkin</a></code></p></div>
<h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2>
<pre class="examples"><div class='input'><span class='no'>sampling_times</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='fl'>0</span>, <span class='fl'>1</span>, <span class='fl'>3</span>, <span class='fl'>7</span>, <span class='fl'>14</span>, <span class='fl'>28</span>, <span class='fl'>60</span>, <span class='fl'>90</span>, <span class='fl'>120</span>)
@@ -226,68 +236,9 @@ datasets.</p>
#&gt; -2.6169360 -0.2185329 0.0574070 0.5720937 3.0459868
#&gt;
#&gt; Number of Observations: 49
-#&gt; Number of Groups: 3 </div><div class='input'><span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='fu'><a href='https://rdrr.io/pkg/nlme/man/augPred.html'>augPred</a></span>(<span class='no'>m_nlme</span>, <span class='kw'>level</span> <span class='kw'>=</span> <span class='fl'>0</span>:<span class='fl'>1</span>), <span class='kw'>layout</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='fl'>3</span>, <span class='fl'>1</span>))</div><div class='img'><img src='nlme-1.png' alt='' width='700' height='433' /></div><div class='input'>
-<span class='co'># \dontrun{</span>
- <span class='co'># Test on some real data</span>
- <span class='no'>ds_2</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/r/base/lapply.html'>lapply</a></span>(<span class='no'>experimental_data_for_UBA_2019</span>[<span class='fl'>6</span>:<span class='fl'>10</span>],
- <span class='kw'>function</span>(<span class='no'>x</span>) <span class='no'>x</span>$<span class='no'>data</span>[<span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='st'>"name"</span>, <span class='st'>"time"</span>, <span class='st'>"value"</span>)])
- <span class='no'>m_sfo_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span>(<span class='kw'>parent</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFO"</span>, <span class='st'>"A1"</span>),
- <span class='kw'>A1</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFO"</span>), <span class='kw'>use_of_ff</span> <span class='kw'>=</span> <span class='st'>"min"</span>)</div><div class='output co'>#&gt; <span class='message'>Successfully compiled differential equation model from auto-generated C code.</span></div><div class='input'> <span class='no'>m_sfo_sfo_ff</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span>(<span class='kw'>parent</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFO"</span>, <span class='st'>"A1"</span>),
- <span class='kw'>A1</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFO"</span>), <span class='kw'>use_of_ff</span> <span class='kw'>=</span> <span class='st'>"max"</span>)</div><div class='output co'>#&gt; <span class='message'>Successfully compiled differential equation model from auto-generated C code.</span></div><div class='input'> <span class='no'>m_fomc_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span>(<span class='kw'>parent</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"FOMC"</span>, <span class='st'>"A1"</span>),
- <span class='kw'>A1</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFO"</span>))</div><div class='output co'>#&gt; <span class='message'>Successfully compiled differential equation model from auto-generated C code.</span></div><div class='input'> <span class='no'>m_dfop_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span>(<span class='kw'>parent</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"DFOP"</span>, <span class='st'>"A1"</span>),
- <span class='kw'>A1</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFO"</span>))</div><div class='output co'>#&gt; <span class='message'>Successfully compiled differential equation model from auto-generated C code.</span></div><div class='input'> <span class='no'>m_sforb_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span>(<span class='kw'>parent</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFORB"</span>, <span class='st'>"A1"</span>),
- <span class='kw'>A1</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFO"</span>))</div><div class='output co'>#&gt; <span class='message'>Successfully compiled differential equation model from auto-generated C code.</span></div><div class='input'>
- <span class='no'>f_2</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mmkin.html'>mmkin</a></span>(<span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='st'>"SFO-SFO"</span> <span class='kw'>=</span> <span class='no'>m_sfo_sfo</span>,
- <span class='st'>"SFO-SFO-ff"</span> <span class='kw'>=</span> <span class='no'>m_sfo_sfo_ff</span>,
- <span class='st'>"FOMC-SFO"</span> <span class='kw'>=</span> <span class='no'>m_fomc_sfo</span>,
- <span class='st'>"DFOP-SFO"</span> <span class='kw'>=</span> <span class='no'>m_dfop_sfo</span>,
- <span class='st'>"SFORB-SFO"</span> <span class='kw'>=</span> <span class='no'>m_sforb_sfo</span>),
- <span class='no'>ds_2</span>)
-
- <span class='no'>grouped_data_2</span> <span class='kw'>&lt;-</span> <span class='fu'>nlme_data</span>(<span class='no'>f_2</span>[<span class='st'>"SFO-SFO"</span>, ])
-
- <span class='no'>mean_dp_sfo_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'>mean_degparms</span>(<span class='no'>f_2</span>[<span class='st'>"SFO-SFO"</span>, ])
- <span class='no'>mean_dp_sfo_sfo_ff</span> <span class='kw'>&lt;-</span> <span class='fu'>mean_degparms</span>(<span class='no'>f_2</span>[<span class='st'>"SFO-SFO-ff"</span>, ])
- <span class='no'>mean_dp_fomc_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'>mean_degparms</span>(<span class='no'>f_2</span>[<span class='st'>"FOMC-SFO"</span>, ])
- <span class='no'>mean_dp_dfop_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'>mean_degparms</span>(<span class='no'>f_2</span>[<span class='st'>"DFOP-SFO"</span>, ])
- <span class='no'>mean_dp_sforb_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'>mean_degparms</span>(<span class='no'>f_2</span>[<span class='st'>"SFORB-SFO"</span>, ])
-
- <span class='no'>nlme_f_sfo_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'>nlme_function</span>(<span class='no'>f_2</span>[<span class='st'>"SFO-SFO"</span>, ])
- <span class='no'>nlme_f_sfo_sfo_ff</span> <span class='kw'>&lt;-</span> <span class='fu'>nlme_function</span>(<span class='no'>f_2</span>[<span class='st'>"SFO-SFO-ff"</span>, ])
- <span class='no'>nlme_f_fomc_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'>nlme_function</span>(<span class='no'>f_2</span>[<span class='st'>"FOMC-SFO"</span>, ])
- <span class='fu'><a href='https://rdrr.io/r/base/assign.html'>assign</a></span>(<span class='st'>"nlme_f_sfo_sfo"</span>, <span class='no'>nlme_f_sfo_sfo</span>, <span class='fu'><a href='https://rdrr.io/r/base/environment.html'>globalenv</a></span>())
- <span class='fu'><a href='https://rdrr.io/r/base/assign.html'>assign</a></span>(<span class='st'>"nlme_f_sfo_sfo_ff"</span>, <span class='no'>nlme_f_sfo_sfo_ff</span>, <span class='fu'><a href='https://rdrr.io/r/base/environment.html'>globalenv</a></span>())
- <span class='fu'><a href='https://rdrr.io/r/base/assign.html'>assign</a></span>(<span class='st'>"nlme_f_fomc_sfo"</span>, <span class='no'>nlme_f_fomc_sfo</span>, <span class='fu'><a href='https://rdrr.io/r/base/environment.html'>globalenv</a></span>())
-
- <span class='co'># Allowing for correlations between random effects (not shown)</span>
- <span class='co'># leads to non-convergence</span>
- <span class='no'>f_nlme_sfo_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span>(<span class='no'>value</span> ~ <span class='fu'>nlme_f_sfo_sfo</span>(<span class='no'>name</span>, <span class='no'>time</span>,
- <span class='no'>parent_0</span>, <span class='no'>log_k_parent_sink</span>, <span class='no'>log_k_parent_A1</span>, <span class='no'>log_k_A1_sink</span>),
- <span class='kw'>data</span> <span class='kw'>=</span> <span class='no'>grouped_data_2</span>,
- <span class='kw'>fixed</span> <span class='kw'>=</span> <span class='no'>parent_0</span> + <span class='no'>log_k_parent_sink</span> + <span class='no'>log_k_parent_A1</span> + <span class='no'>log_k_A1_sink</span> ~ <span class='fl'>1</span>,
- <span class='kw'>random</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/pdDiag.html'>pdDiag</a></span>(<span class='no'>parent_0</span> + <span class='no'>log_k_parent_sink</span> + <span class='no'>log_k_parent_A1</span> + <span class='no'>log_k_A1_sink</span> ~ <span class='fl'>1</span>),
- <span class='kw'>start</span> <span class='kw'>=</span> <span class='no'>mean_dp_sfo_sfo</span>)
- <span class='co'># augPred does not see to work on this object, so no plot is shown</span>
-
- <span class='co'># The same model fitted with transformed formation fractions does not converge</span>
- <span class='no'>f_nlme_sfo_sfo_ff</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span>(<span class='no'>value</span> ~ <span class='fu'>nlme_f_sfo_sfo_ff</span>(<span class='no'>name</span>, <span class='no'>time</span>,
- <span class='no'>parent_0</span>, <span class='no'>log_k_parent</span>, <span class='no'>log_k_A1</span>, <span class='no'>f_parent_ilr_1</span>),
- <span class='kw'>data</span> <span class='kw'>=</span> <span class='no'>grouped_data_2</span>,
- <span class='kw'>fixed</span> <span class='kw'>=</span> <span class='no'>parent_0</span> + <span class='no'>log_k_parent</span> + <span class='no'>log_k_A1</span> + <span class='no'>f_parent_ilr_1</span> ~ <span class='fl'>1</span>,
- <span class='kw'>random</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/pdDiag.html'>pdDiag</a></span>(<span class='no'>parent_0</span> + <span class='no'>log_k_parent</span> + <span class='no'>log_k_A1</span> + <span class='no'>f_parent_ilr_1</span> ~ <span class='fl'>1</span>),
- <span class='kw'>start</span> <span class='kw'>=</span> <span class='no'>mean_dp_sfo_sfo_ff</span>)</div><div class='output co'>#&gt; <span class='error'>Error in nlme.formula(value ~ nlme_f_sfo_sfo_ff(name, time, parent_0, log_k_parent, log_k_A1, f_parent_ilr_1), data = grouped_data_2, fixed = parent_0 + log_k_parent + log_k_A1 + f_parent_ilr_1 ~ 1, random = pdDiag(parent_0 + log_k_parent + log_k_A1 + f_parent_ilr_1 ~ 1), start = mean_dp_sfo_sfo_ff): step halving factor reduced below minimum in PNLS step</span></div><div class='input'>
- <span class='no'>f_nlme_fomc_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span>(<span class='no'>value</span> ~ <span class='fu'>nlme_f_fomc_sfo</span>(<span class='no'>name</span>, <span class='no'>time</span>,
- <span class='no'>parent_0</span>, <span class='no'>log_alpha</span>, <span class='no'>log_beta</span>, <span class='no'>log_k_A1</span>, <span class='no'>f_parent_ilr_1</span>),
- <span class='kw'>data</span> <span class='kw'>=</span> <span class='no'>grouped_data_2</span>,
- <span class='kw'>fixed</span> <span class='kw'>=</span> <span class='no'>parent_0</span> + <span class='no'>log_alpha</span> + <span class='no'>log_beta</span> + <span class='no'>log_k_A1</span> + <span class='no'>f_parent_ilr_1</span> ~ <span class='fl'>1</span>,
- <span class='kw'>random</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/pdDiag.html'>pdDiag</a></span>(<span class='no'>parent_0</span> + <span class='no'>log_alpha</span> + <span class='no'>log_beta</span> + <span class='no'>log_k_A1</span> + <span class='no'>f_parent_ilr_1</span> ~ <span class='fl'>1</span>),
- <span class='kw'>start</span> <span class='kw'>=</span> <span class='no'>mean_dp_fomc_sfo</span>)
-
- <span class='co'># DFOP-SFO and SFORB-SFO did not converge with full random effects</span>
-
- <span class='fu'><a href='https://rdrr.io/r/stats/anova.html'>anova</a></span>(<span class='no'>f_nlme_fomc_sfo</span>, <span class='no'>f_nlme_sfo_sfo</span>)</div><div class='output co'>#&gt; Model df AIC BIC logLik Test L.Ratio p-value
-#&gt; f_nlme_fomc_sfo 1 11 932.5817 967.0755 -455.2909
-#&gt; f_nlme_sfo_sfo 2 9 1089.2492 1117.4714 -535.6246 1 vs 2 160.6675 &lt;.0001</div><div class='input'># }
+#&gt; Number of Groups: 3 </div><div class='input'><span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='fu'><a href='https://rdrr.io/pkg/nlme/man/augPred.html'>augPred</a></span>(<span class='no'>m_nlme</span>, <span class='kw'>level</span> <span class='kw'>=</span> <span class='fl'>0</span>:<span class='fl'>1</span>), <span class='kw'>layout</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='fl'>3</span>, <span class='fl'>1</span>))</div><div class='img'><img src='nlme-1.png' alt='' width='700' height='433' /></div><div class='input'># augPred does not seem to work on fits with more than one state
+# variable
+
</div></pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="sidebar">
@@ -295,6 +246,7 @@ datasets.</p>
<ul class="nav nav-pills nav-stacked">
<li><a href="#arguments">Arguments</a></li>
<li><a href="#value">Value</a></li>
+ <li><a href="#see-also">See also</a></li>
<li><a href="#examples">Examples</a></li>
</ul>
diff --git a/docs/reference/nlme.mmkin-1.png b/docs/reference/nlme.mmkin-1.png
new file mode 100644
index 00000000..67bd07de
--- /dev/null
+++ b/docs/reference/nlme.mmkin-1.png
Binary files differ
diff --git a/docs/reference/nlme.mmkin-2.png b/docs/reference/nlme.mmkin-2.png
new file mode 100644
index 00000000..ee6bb2e4
--- /dev/null
+++ b/docs/reference/nlme.mmkin-2.png
Binary files differ
diff --git a/docs/reference/nlme.mmkin-3.png b/docs/reference/nlme.mmkin-3.png
new file mode 100644
index 00000000..1d5569e9
--- /dev/null
+++ b/docs/reference/nlme.mmkin-3.png
Binary files differ
diff --git a/docs/reference/nlme.mmkin-4.png b/docs/reference/nlme.mmkin-4.png
new file mode 100644
index 00000000..7249bd1e
--- /dev/null
+++ b/docs/reference/nlme.mmkin-4.png
Binary files differ
diff --git a/docs/reference/nlme.mmkin-5.png b/docs/reference/nlme.mmkin-5.png
new file mode 100644
index 00000000..26781b85
--- /dev/null
+++ b/docs/reference/nlme.mmkin-5.png
Binary files differ
diff --git a/docs/reference/nlme.mmkin-6.png b/docs/reference/nlme.mmkin-6.png
new file mode 100644
index 00000000..5f5a759a
--- /dev/null
+++ b/docs/reference/nlme.mmkin-6.png
Binary files differ
diff --git a/docs/reference/nlme.mmkin-7.png b/docs/reference/nlme.mmkin-7.png
new file mode 100644
index 00000000..1d4fa8ea
--- /dev/null
+++ b/docs/reference/nlme.mmkin-7.png
Binary files differ
diff --git a/docs/reference/nlme.mmkin.html b/docs/reference/nlme.mmkin.html
index e1b1ff77..01287dda 100644
--- a/docs/reference/nlme.mmkin.html
+++ b/docs/reference/nlme.mmkin.html
@@ -156,7 +156,13 @@ have been obtained by fitting the same model to a list of datasets.</p>
<span class='no'>naPattern</span>,
<span class='kw'>control</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(),
<span class='kw'>verbose</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>
-)</pre>
+)
+
+<span class='co'># S3 method for nlme.mmkin</span>
+<span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span>(<span class='no'>x</span>, <span class='no'>...</span>)
+
+<span class='co'># S3 method for nlme.mmkin</span>
+<span class='fu'><a href='https://rdrr.io/r/stats/update.html'>update</a></span>(<span class='no'>object</span>, <span class='no'>...</span>)</pre>
<h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2>
<table class="ref-arguments">
@@ -167,7 +173,7 @@ have been obtained by fitting the same model to a list of datasets.</p>
</tr>
<tr>
<th>data</th>
- <td><p>Ignored, data are taken from the mmkin model</p></td>
+ <td><p>Should the data be printed?</p></td>
</tr>
<tr>
<th>fixed</th>
@@ -220,6 +226,18 @@ parameters taken from the mmkin object are used</p></td>
<th>verbose</th>
<td><p>passed to nlme</p></td>
</tr>
+ <tr>
+ <th>x</th>
+ <td><p>An nlme.mmkin object to print</p></td>
+ </tr>
+ <tr>
+ <th>...</th>
+ <td><p>Update specifications passed to update.nlme</p></td>
+ </tr>
+ <tr>
+ <th>object</th>
+ <td><p>An nlme.mmkin object to update</p></td>
+ </tr>
</table>
<h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2>
@@ -236,24 +254,26 @@ parameters taken from the mmkin object are used</p></td>
<span class='no'>f</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mmkin.html'>mmkin</a></span>(<span class='st'>"SFO"</span>, <span class='no'>ds</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='kw'>cores</span> <span class='kw'>=</span> <span class='fl'>1</span>)
<span class='fu'><a href='https://rdrr.io/r/base/library.html'>library</a></span>(<span class='no'>nlme</span>)
<span class='no'>f_nlme</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span>(<span class='no'>f</span>)
-<span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span>(<span class='no'>f</span>, <span class='kw'>random</span> <span class='kw'>=</span> <span class='no'>parent_0</span> ~ <span class='fl'>1</span>)</div><div class='output co'>#&gt; Nonlinear mixed-effects model fit by maximum likelihood
+<span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span>(<span class='no'>f_nlme</span>)</div><div class='output co'>#&gt; Nonlinear mixed-effects model fit by maximum likelihood
#&gt; Model: value ~ deg_func(name, time, parent_0, log_k_parent_sink)
-#&gt; Data: structure(list(ds = structure(c(1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L), .Label = c("1", "2", "3", "4", "5"), class = c("ordered", "factor")), name = c("parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent"), time = c(0, 0, 3, 3, 6, 6, 10, 10, 20, 20, 34, 34, 55, 55, 90, 90, 112, 112, 132, 132, 0, 0, 3, 3, 7, 7, 14, 14, 30, 30, 60, 60, 90, 90, 120, 120, 180, 180, 0, 0, 1, 1, 3, 3, 8, 8, 14, 14, 27, 27, 48, 48, 70, 70, 0, 0, 1, 1, 3, 3, 8, 8, 14, 14, 27, 27, 48, 48, 70, 70, 91, 91, 120, 120, 0, 0, 8, 8, 14, 14, 21, 21, 41, 41, 63, 63, 91, 91, 120, 120), value = c(97.2, 96.4, 71.1, 69.2, 58.1, 56.6, 44.4, 43.4, 33.3, 29.2, 17.6, 18, 10.5, 9.3, 4.5, 4.7, 3, 3.4, 2.3, 2.7, 93.6, 92.3, 87, 82.2, 74, 73.9, 64.2, 69.5, 54, 54.6, 41.1, 38.4, 32.5, 35.5, 28.1, 29, 26.5, 27.6, 91.9, 90.8, 64.9, 66.2, 43.5, 44.1, 18.3, 18.1, 10.2, 10.8, 4.9, 3.3, 1.6, 1.5, 1.1, 0.9, 99.8, 98.3, 77.1, 77.2, 59, 58.1, 27.4, 29.2, 19.1, 29.6, 10.1, 18.2, 4.5, 9.1, 2.3, 2.9, 2, 1.8, 2, 2.2, 96.1, 94.3, 73.9, 73.9, 69.4, 73.1, 65.6, 65.3, 55.9, 54.4, 47, 49.3, 44.7, 46.7, 42.1, 41.3)), row.names = c(NA, -90L), class = c("nfnGroupedData", "nfGroupedData", "groupedData", "data.frame"), formula = value ~ time | ds, FUN = function (x) max(x, na.rm = TRUE), order.groups = FALSE)
-#&gt; Log-likelihood: -394.4901
+#&gt; Data: "Not shown"
+#&gt; Log-likelihood: -307.5269
#&gt; Fixed: list(parent_0 ~ 1, log_k_parent_sink ~ 1)
#&gt; parent_0 log_k_parent_sink
-#&gt; 73.985522 -3.869079
+#&gt; 85.541149 -3.229596
#&gt;
#&gt; Random effects:
-#&gt; Formula: parent_0 ~ 1 | ds
-#&gt; parent_0 Residual
-#&gt; StdDev: 18.6134 18.22029
+#&gt; Formula: list(parent_0 ~ 1, log_k_parent_sink ~ 1)
+#&gt; Level: ds
+#&gt; Structure: Diagonal
+#&gt; parent_0 log_k_parent_sink Residual
+#&gt; StdDev: 1.30857 1.288591 6.304906
#&gt;
#&gt; Number of Observations: 90
-#&gt; Number of Groups: 5 </div><div class='input'><span class='no'>f_nlme</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span>(<span class='no'>f</span>, <span class='kw'>start</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='kw'>parent_0</span> <span class='kw'>=</span> <span class='fl'>100</span>, <span class='kw'>log_k_parent_sink</span> <span class='kw'>=</span> <span class='fl'>0.1</span>))
-<span class='fu'><a href='https://rdrr.io/r/stats/update.html'>update</a></span>(<span class='no'>f_nlme</span>, <span class='kw'>random</span> <span class='kw'>=</span> <span class='no'>parent_0</span> ~ <span class='fl'>1</span>)</div><div class='output co'>#&gt; Nonlinear mixed-effects model fit by maximum likelihood
+#&gt; Number of Groups: 5 </div><div class='input'><span class='no'>f_nlme_2</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span>(<span class='no'>f</span>, <span class='kw'>start</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='kw'>parent_0</span> <span class='kw'>=</span> <span class='fl'>100</span>, <span class='kw'>log_k_parent_sink</span> <span class='kw'>=</span> <span class='fl'>0.1</span>))
+<span class='fu'><a href='https://rdrr.io/r/stats/update.html'>update</a></span>(<span class='no'>f_nlme_2</span>, <span class='kw'>random</span> <span class='kw'>=</span> <span class='no'>parent_0</span> ~ <span class='fl'>1</span>)</div><div class='output co'>#&gt; Nonlinear mixed-effects model fit by maximum likelihood
#&gt; Model: value ~ deg_func(name, time, parent_0, log_k_parent_sink)
-#&gt; Data: structure(list(ds = structure(c(1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L), .Label = c("1", "2", "3", "4", "5"), class = c("ordered", "factor")), name = c("parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent", "parent"), time = c(0, 0, 3, 3, 6, 6, 10, 10, 20, 20, 34, 34, 55, 55, 90, 90, 112, 112, 132, 132, 0, 0, 3, 3, 7, 7, 14, 14, 30, 30, 60, 60, 90, 90, 120, 120, 180, 180, 0, 0, 1, 1, 3, 3, 8, 8, 14, 14, 27, 27, 48, 48, 70, 70, 0, 0, 1, 1, 3, 3, 8, 8, 14, 14, 27, 27, 48, 48, 70, 70, 91, 91, 120, 120, 0, 0, 8, 8, 14, 14, 21, 21, 41, 41, 63, 63, 91, 91, 120, 120), value = c(97.2, 96.4, 71.1, 69.2, 58.1, 56.6, 44.4, 43.4, 33.3, 29.2, 17.6, 18, 10.5, 9.3, 4.5, 4.7, 3, 3.4, 2.3, 2.7, 93.6, 92.3, 87, 82.2, 74, 73.9, 64.2, 69.5, 54, 54.6, 41.1, 38.4, 32.5, 35.5, 28.1, 29, 26.5, 27.6, 91.9, 90.8, 64.9, 66.2, 43.5, 44.1, 18.3, 18.1, 10.2, 10.8, 4.9, 3.3, 1.6, 1.5, 1.1, 0.9, 99.8, 98.3, 77.1, 77.2, 59, 58.1, 27.4, 29.2, 19.1, 29.6, 10.1, 18.2, 4.5, 9.1, 2.3, 2.9, 2, 1.8, 2, 2.2, 96.1, 94.3, 73.9, 73.9, 69.4, 73.1, 65.6, 65.3, 55.9, 54.4, 47, 49.3, 44.7, 46.7, 42.1, 41.3)), row.names = c(NA, -90L), class = c("nfnGroupedData", "nfGroupedData", "groupedData", "data.frame"), formula = value ~ time | ds, FUN = function (x) max(x, na.rm = TRUE), order.groups = FALSE)
+#&gt; Data: "Not shown"
#&gt; Log-likelihood: -404.3729
#&gt; Fixed: list(parent_0 ~ 1, log_k_parent_sink ~ 1)
#&gt; parent_0 log_k_parent_sink
@@ -265,7 +285,133 @@ parameters taken from the mmkin object are used</p></td>
#&gt; StdDev: 0.002416792 21.63027
#&gt;
#&gt; Number of Observations: 90
-#&gt; Number of Groups: 5 </div></pre>
+#&gt; Number of Groups: 5 </div><div class='input'><span class='co'># \dontrun{</span>
+ <span class='co'># Test on some real data</span>
+ <span class='no'>ds_2</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/r/base/lapply.html'>lapply</a></span>(<span class='no'>experimental_data_for_UBA_2019</span>[<span class='fl'>6</span>:<span class='fl'>10</span>],
+ <span class='kw'>function</span>(<span class='no'>x</span>) <span class='no'>x</span>$<span class='no'>data</span>[<span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='st'>"name"</span>, <span class='st'>"time"</span>, <span class='st'>"value"</span>)])
+ <span class='no'>m_sfo_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span>(<span class='kw'>parent</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFO"</span>, <span class='st'>"A1"</span>),
+ <span class='kw'>A1</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFO"</span>), <span class='kw'>use_of_ff</span> <span class='kw'>=</span> <span class='st'>"min"</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>)
+ <span class='no'>m_sfo_sfo_ff</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span>(<span class='kw'>parent</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFO"</span>, <span class='st'>"A1"</span>),
+ <span class='kw'>A1</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFO"</span>), <span class='kw'>use_of_ff</span> <span class='kw'>=</span> <span class='st'>"max"</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>)
+ <span class='no'>m_fomc_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span>(<span class='kw'>parent</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"FOMC"</span>, <span class='st'>"A1"</span>),
+ <span class='kw'>A1</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFO"</span>), <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>)
+ <span class='no'>m_dfop_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span>(<span class='kw'>parent</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"DFOP"</span>, <span class='st'>"A1"</span>),
+ <span class='kw'>A1</span> <span class='kw'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span>(<span class='st'>"SFO"</span>), <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>)
+
+ <span class='no'>f_2</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mmkin.html'>mmkin</a></span>(<span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='st'>"SFO-SFO"</span> <span class='kw'>=</span> <span class='no'>m_sfo_sfo</span>,
+ <span class='st'>"SFO-SFO-ff"</span> <span class='kw'>=</span> <span class='no'>m_sfo_sfo_ff</span>,
+ <span class='st'>"FOMC-SFO"</span> <span class='kw'>=</span> <span class='no'>m_fomc_sfo</span>,
+ <span class='st'>"DFOP-SFO"</span> <span class='kw'>=</span> <span class='no'>m_dfop_sfo</span>),
+ <span class='no'>ds_2</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>)
+ <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>f_2</span>[<span class='st'>"SFO-SFO"</span>, <span class='fl'>3</span>:<span class='fl'>4</span>]) <span class='co'># Separate fits for datasets 3 and 4</span></div><div class='img'><img src='nlme.mmkin-1.png' alt='' width='700' height='433' /></div><div class='input'>
+ <span class='no'>f_nlme_sfo_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span>(<span class='no'>f_2</span>[<span class='st'>"SFO-SFO"</span>, ])
+ <span class='co'># plot(f_nlme_sfo_sfo) # not feasible with pkgdown figures</span>
+ <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>f_nlme_sfo_sfo</span>, <span class='fl'>3</span>:<span class='fl'>4</span>) <span class='co'># Global mixed model: Fits for datasets 3 and 4</span></div><div class='img'><img src='nlme.mmkin-2.png' alt='' width='700' height='433' /></div><div class='input'>
+ <span class='co'># With formation fractions</span>
+ <span class='no'>f_nlme_sfo_sfo_ff</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span>(<span class='no'>f_2</span>[<span class='st'>"SFO-SFO-ff"</span>, ])
+ <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>f_nlme_sfo_sfo_ff</span>, <span class='fl'>3</span>:<span class='fl'>4</span>) <span class='co'># chi2 different due to different df attribution</span></div><div class='img'><img src='nlme.mmkin-3.png' alt='' width='700' height='433' /></div><div class='input'>
+ <span class='co'># For more parameters, we need to increase pnlsMaxIter and the tolerance</span>
+ <span class='co'># to get convergence</span>
+ <span class='no'>f_nlme_fomc_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span>(<span class='no'>f_2</span>[<span class='st'>"FOMC-SFO"</span>, ],
+ <span class='kw'>control</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='kw'>pnlsMaxIter</span> <span class='kw'>=</span> <span class='fl'>100</span>, <span class='kw'>tolerance</span> <span class='kw'>=</span> <span class='fl'>1e-4</span>), <span class='kw'>verbose</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>)</div><div class='output co'>#&gt;
+#&gt; **Iteration 1
+#&gt; LME step: Loglik: -394.1603, nlminb iterations: 2
+#&gt; reStruct parameters:
+#&gt; ds1 ds2 ds3 ds4 ds5
+#&gt; -0.2079984 0.8563873 1.7454146 1.0917723 1.2756924
+#&gt; Beginning PNLS step: .. completed fit_nlme() step.
+#&gt; PNLS step: RSS = 643.8786
+#&gt; fixed effects: 94.17379 -5.473199 -0.6970239 -0.2025094 2.103883
+#&gt; iterations: 100
+#&gt; Convergence crit. (must all become &lt;= tolerance = 0.0001):
+#&gt; fixed reStruct
+#&gt; 0.7865373 0.1448077
+#&gt;
+#&gt; **Iteration 2
+#&gt; LME step: Loglik: -396.3824, nlminb iterations: 7
+#&gt; reStruct parameters:
+#&gt; ds1 ds2 ds3 ds4 ds5
+#&gt; -1.712408e-01 -2.680989e-05 1.842119e+00 1.073975e+00 1.322924e+00
+#&gt; Beginning PNLS step: .. completed fit_nlme() step.
+#&gt; PNLS step: RSS = 643.8022
+#&gt; fixed effects: 94.17385 -5.473491 -0.6970405 -0.202514 2.103871
+#&gt; iterations: 100
+#&gt; Convergence crit. (must all become &lt;= tolerance = 0.0001):
+#&gt; fixed reStruct
+#&gt; 5.341904e-05 1.227073e-03
+#&gt;
+#&gt; **Iteration 3
+#&gt; LME step: Loglik: -396.3825, nlminb iterations: 7
+#&gt; reStruct parameters:
+#&gt; ds1 ds2 ds3 ds4 ds5
+#&gt; -0.1712484347 -0.0001513555 1.8420964843 1.0739800649 1.3229176990
+#&gt; Beginning PNLS step: .. completed fit_nlme() step.
+#&gt; PNLS step: RSS = 643.7947
+#&gt; fixed effects: 94.17386 -5.473522 -0.6970423 -0.2025142 2.10387
+#&gt; iterations: 100
+#&gt; Convergence crit. (must all become &lt;= tolerance = 0.0001):
+#&gt; fixed reStruct
+#&gt; 5.568186e-06 1.276609e-04
+#&gt;
+#&gt; **Iteration 4
+#&gt; LME step: Loglik: -396.3825, nlminb iterations: 7
+#&gt; reStruct parameters:
+#&gt; ds1 ds2 ds3 ds4 ds5
+#&gt; -0.171251200 -0.000164506 1.842095097 1.073980200 1.322916184
+#&gt; Beginning PNLS step: .. completed fit_nlme() step.
+#&gt; PNLS step: RSS = 643.7934
+#&gt; fixed effects: 94.17386 -5.473526 -0.6970426 -0.2025146 2.103869
+#&gt; iterations: 100
+#&gt; Convergence crit. (must all become &lt;= tolerance = 0.0001):
+#&gt; fixed reStruct
+#&gt; 2.332100e-06 1.979007e-05 </div><div class='input'> <span class='no'>f_nlme_dfop_sfo</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span>(<span class='no'>f_2</span>[<span class='st'>"DFOP-SFO"</span>, ],
+ <span class='kw'>control</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='kw'>pnlsMaxIter</span> <span class='kw'>=</span> <span class='fl'>120</span>, <span class='kw'>tolerance</span> <span class='kw'>=</span> <span class='fl'>5e-4</span>), <span class='kw'>verbose</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>)</div><div class='output co'>#&gt;
+#&gt; **Iteration 1
+#&gt; LME step: Loglik: -404.9591, nlminb iterations: 1
+#&gt; reStruct parameters:
+#&gt; ds1 ds2 ds3 ds4 ds5 ds6
+#&gt; -0.4114594 0.9798456 1.6990016 0.7293119 0.3353829 1.7112922
+#&gt; Beginning PNLS step: .. completed fit_nlme() step.
+#&gt; PNLS step: RSS = 630.391
+#&gt; fixed effects: 93.82265 -5.455841 -0.6788837 -1.862191 -4.199654 0.05531046
+#&gt; iterations: 120
+#&gt; Convergence crit. (must all become &lt;= tolerance = 0.0005):
+#&gt; fixed reStruct
+#&gt; 0.7872619 0.5811683
+#&gt;
+#&gt; **Iteration 2
+#&gt; LME step: Loglik: -407.7755, nlminb iterations: 11
+#&gt; reStruct parameters:
+#&gt; ds1 ds2 ds3 ds4 ds5 ds6
+#&gt; -0.371222832 0.003084754 1.789952290 0.724634064 0.301559136 1.754244638
+#&gt; Beginning PNLS step: .. completed fit_nlme() step.
+#&gt; PNLS step: RSS = 630.359
+#&gt; fixed effects: 93.82269 -5.456014 -0.6788967 -1.862202 -4.199678 0.05534118
+#&gt; iterations: 120
+#&gt; Convergence crit. (must all become &lt;= tolerance = 0.0005):
+#&gt; fixed reStruct
+#&gt; 0.0005550885 0.0007749418
+#&gt;
+#&gt; **Iteration 3
+#&gt; LME step: Loglik: -407.7756, nlminb iterations: 11
+#&gt; reStruct parameters:
+#&gt; ds1 ds2 ds3 ds4 ds5 ds6
+#&gt; -0.371217033 0.003064156 1.789935045 0.724683005 0.301622307 1.754234135
+#&gt; Beginning PNLS step: .. completed fit_nlme() step.
+#&gt; PNLS step: RSS = 630.358
+#&gt; fixed effects: 93.82269 -5.456017 -0.6788969 -1.862197 -4.199677 0.05532978
+#&gt; iterations: 120
+#&gt; Convergence crit. (must all become &lt;= tolerance = 0.0005):
+#&gt; fixed reStruct
+#&gt; 2.059533e-04 4.860085e-05 </div><div class='input'> <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>f_2</span>[<span class='st'>"FOMC-SFO"</span>, <span class='fl'>3</span>:<span class='fl'>4</span>])</div><div class='img'><img src='nlme.mmkin-4.png' alt='' width='700' height='433' /></div><div class='input'> <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>f_nlme_fomc_sfo</span>, <span class='fl'>3</span>:<span class='fl'>4</span>)</div><div class='img'><img src='nlme.mmkin-5.png' alt='' width='700' height='433' /></div><div class='input'>
+ <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>f_2</span>[<span class='st'>"DFOP-SFO"</span>, <span class='fl'>3</span>:<span class='fl'>4</span>])</div><div class='img'><img src='nlme.mmkin-6.png' alt='' width='700' height='433' /></div><div class='input'> <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>f_nlme_dfop_sfo</span>, <span class='fl'>3</span>:<span class='fl'>4</span>)</div><div class='img'><img src='nlme.mmkin-7.png' alt='' width='700' height='433' /></div><div class='input'>
+ <span class='fu'><a href='https://rdrr.io/r/stats/anova.html'>anova</a></span>(<span class='no'>f_nlme_dfop_sfo</span>, <span class='no'>f_nlme_fomc_sfo</span>, <span class='no'>f_nlme_sfo_sfo</span>)</div><div class='output co'>#&gt; Model df AIC BIC logLik Test L.Ratio p-value
+#&gt; f_nlme_dfop_sfo 1 13 843.8541 884.6194 -408.9270
+#&gt; f_nlme_fomc_sfo 2 11 818.5149 853.0087 -398.2575 1 vs 2 21.33913 &lt;.0001
+#&gt; f_nlme_sfo_sfo 3 9 1085.1821 1113.4042 -533.5910 2 vs 3 270.66712 &lt;.0001</div><div class='input'> <span class='fu'><a href='https://rdrr.io/r/stats/anova.html'>anova</a></span>(<span class='no'>f_nlme_dfop_sfo</span>, <span class='no'>f_nlme_sfo_sfo</span>) <span class='co'># if we ignore FOMC</span></div><div class='output co'>#&gt; Model df AIC BIC logLik Test L.Ratio p-value
+#&gt; f_nlme_dfop_sfo 1 13 843.8541 884.6194 -408.927
+#&gt; f_nlme_sfo_sfo 2 9 1085.1821 1113.4042 -533.591 1 vs 2 249.328 &lt;.0001</div><div class='input'># }
+</div></pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="sidebar">
<h2>Contents</h2>
diff --git a/docs/reference/plot.mmkin-3.png b/docs/reference/plot.mmkin-3.png
index 47cd7eec..c58b371a 100644
--- a/docs/reference/plot.mmkin-3.png
+++ b/docs/reference/plot.mmkin-3.png
Binary files differ
diff --git a/docs/reference/plot.mmkin-4.png b/docs/reference/plot.mmkin-4.png
index 44037bb4..47cd7eec 100644
--- a/docs/reference/plot.mmkin-4.png
+++ b/docs/reference/plot.mmkin-4.png
Binary files differ
diff --git a/docs/reference/plot.mmkin-5.png b/docs/reference/plot.mmkin-5.png
new file mode 100644
index 00000000..44037bb4
--- /dev/null
+++ b/docs/reference/plot.mmkin-5.png
Binary files differ
diff --git a/docs/reference/plot.mmkin.html b/docs/reference/plot.mmkin.html
index a513756b..ef5718e5 100644
--- a/docs/reference/plot.mmkin.html
+++ b/docs/reference/plot.mmkin.html
@@ -184,7 +184,7 @@ values, with the error model, using <code><a href='mkinerrplot.html'>mkinerrplot
<tr>
<th>standardized</th>
<td><p>Should the residuals be standardized? This option
-is passed to <code><a href='mkinresplot.html'>mkinresplot</a></code>, it only takes effect if
+is passed to <code><a href='mkinresplot.html'>mkinresplot</a></code>, it only takes effect if
`resplot = "time"`.</p></td>
</tr>
<tr>
@@ -237,13 +237,13 @@ latex is being used for the formatting of the chi2 error level.</p>
<span class='no'>fits</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mmkin.html'>mmkin</a></span>(<span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='st'>"FOMC"</span>, <span class='st'>"HS"</span>),
<span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='st'>"FOCUS B"</span> <span class='kw'>=</span> <span class='no'>FOCUS_2006_B</span>, <span class='st'>"FOCUS C"</span> <span class='kw'>=</span> <span class='no'>FOCUS_2006_C</span>), <span class='co'># named list for titles</span>
<span class='kw'>cores</span> <span class='kw'>=</span> <span class='fl'>1</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='kw'>error_model</span> <span class='kw'>=</span> <span class='st'>"tc"</span>)</div><div class='output co'>#&gt; <span class='warning'>Warning: Optimisation did not converge:</span>
-#&gt; <span class='warning'>iteration limit reached without convergence (10)</span></div><div class='input'> <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>fits</span>[, <span class='st'>"FOCUS C"</span>])</div><div class='img'><img src='plot.mmkin-1.png' alt='' width='700' height='433' /></div><div class='input'> <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>fits</span>[<span class='st'>"FOMC"</span>, ])</div><div class='img'><img src='plot.mmkin-2.png' alt='' width='700' height='433' /></div><div class='input'>
+#&gt; <span class='warning'>iteration limit reached without convergence (10)</span></div><div class='input'> <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>fits</span>[, <span class='st'>"FOCUS C"</span>])</div><div class='img'><img src='plot.mmkin-1.png' alt='' width='700' height='433' /></div><div class='input'> <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>fits</span>[<span class='st'>"FOMC"</span>, ])</div><div class='img'><img src='plot.mmkin-2.png' alt='' width='700' height='433' /></div><div class='input'> <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>fits</span>[<span class='st'>"FOMC"</span>, ], <span class='kw'>show_errmin</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)</div><div class='img'><img src='plot.mmkin-3.png' alt='' width='700' height='433' /></div><div class='input'>
<span class='co'># We can also plot a single fit, if we like the way plot.mmkin works, but then the plot</span>
<span class='co'># height should be smaller than the plot width (this is not possible for the html pages</span>
<span class='co'># generated by pkgdown, as far as I know).</span>
- <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>fits</span>[<span class='st'>"FOMC"</span>, <span class='st'>"FOCUS C"</span>]) <span class='co'># same as plot(fits[1, 2])</span></div><div class='img'><img src='plot.mmkin-3.png' alt='' width='700' height='433' /></div><div class='input'>
+ <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>fits</span>[<span class='st'>"FOMC"</span>, <span class='st'>"FOCUS C"</span>]) <span class='co'># same as plot(fits[1, 2])</span></div><div class='img'><img src='plot.mmkin-4.png' alt='' width='700' height='433' /></div><div class='input'>
<span class='co'># Show the error models</span>
- <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>fits</span>[<span class='st'>"FOMC"</span>, ], <span class='kw'>resplot</span> <span class='kw'>=</span> <span class='st'>"errmod"</span>)</div><div class='img'><img src='plot.mmkin-4.png' alt='' width='700' height='433' /></div><div class='input'> # }
+ <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>fits</span>[<span class='st'>"FOMC"</span>, ], <span class='kw'>resplot</span> <span class='kw'>=</span> <span class='st'>"errmod"</span>)</div><div class='img'><img src='plot.mmkin-5.png' alt='' width='700' height='433' /></div><div class='input'> # }
</div></pre>
</div>
diff --git a/docs/reference/plot.nlme.mmkin-1.png b/docs/reference/plot.nlme.mmkin-1.png
index 0717f30d..fe2ef7d3 100644
--- a/docs/reference/plot.nlme.mmkin-1.png
+++ b/docs/reference/plot.nlme.mmkin-1.png
Binary files differ
diff --git a/docs/reference/plot.nlme.mmkin-2.png b/docs/reference/plot.nlme.mmkin-2.png
new file mode 100644
index 00000000..27c09796
--- /dev/null
+++ b/docs/reference/plot.nlme.mmkin-2.png
Binary files differ
diff --git a/docs/reference/plot.nlme.mmkin.html b/docs/reference/plot.nlme.mmkin.html
index d5b7c00c..256739eb 100644
--- a/docs/reference/plot.nlme.mmkin.html
+++ b/docs/reference/plot.nlme.mmkin.html
@@ -144,6 +144,9 @@
<span class='kw'>legends</span> <span class='kw'>=</span> <span class='fl'>1</span>,
<span class='kw'>resplot</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='st'>"time"</span>, <span class='st'>"errmod"</span>),
<span class='kw'>standardized</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>,
+ <span class='kw'>show_errmin</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>,
+ <span class='kw'>errmin_var</span> <span class='kw'>=</span> <span class='st'>"All data"</span>,
+ <span class='kw'>errmin_digits</span> <span class='kw'>=</span> <span class='fl'>3</span>,
<span class='kw'>cex</span> <span class='kw'>=</span> <span class='fl'>0.7</span>,
<span class='kw'>rel.height.middle</span> <span class='kw'>=</span> <span class='fl'>0.9</span>,
<span class='kw'>ymax</span> <span class='kw'>=</span> <span class='st'>"auto"</span>,
@@ -183,6 +186,21 @@ is passed to <code><a href='mkinresplot.html'>mkinresplot</a></code>, it only ta
`resplot = "time"`.</p></td>
</tr>
<tr>
+ <th>show_errmin</th>
+ <td><p>Should the chi2 error level be shown on top of the plots
+to the left?</p></td>
+ </tr>
+ <tr>
+ <th>errmin_var</th>
+ <td><p>The variable for which the FOCUS chi2 error value should
+be shown.</p></td>
+ </tr>
+ <tr>
+ <th>errmin_digits</th>
+ <td><p>The number of significant digits for rounding the FOCUS
+chi2 error percentage.</p></td>
+ </tr>
+ <tr>
<th>cex</th>
<td><p>Passed to the plot functions and <code><a href='https://rdrr.io/r/graphics/mtext.html'>mtext</a></code>.</p></td>
</tr>
@@ -211,11 +229,11 @@ than two rows of plots are shown.</p></td>
<span class='kw'>function</span>(<span class='no'>x</span>) <span class='fu'><a href='https://rdrr.io/r/base/subset.html'>subset</a></span>(<span class='no'>x</span>$<span class='no'>data</span>[<span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='st'>"name"</span>, <span class='st'>"time"</span>, <span class='st'>"value"</span>)], <span class='no'>name</span> <span class='kw'>==</span> <span class='st'>"parent"</span>))
<span class='no'>f</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='mmkin.html'>mmkin</a></span>(<span class='st'>"SFO"</span>, <span class='no'>ds</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='kw'>cores</span> <span class='kw'>=</span> <span class='fl'>1</span>)
<span class='co'>#plot(f) # too many panels for pkgdown</span>
-<span class='fu'><a href='https://rdrr.io/r/base/library.html'>library</a></span>(<span class='no'>nlme</span>)
+<span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>f</span>[, <span class='fl'>3</span>:<span class='fl'>4</span>])</div><div class='img'><img src='plot.nlme.mmkin-1.png' alt='' width='700' height='433' /></div><div class='input'><span class='fu'><a href='https://rdrr.io/r/base/library.html'>library</a></span>(<span class='no'>nlme</span>)
<span class='no'>f_nlme</span> <span class='kw'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span>(<span class='no'>f</span>)
<span class='co'>#plot(f_nlme) # too many panels for pkgdown</span>
-<span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>f_nlme</span>, <span class='fl'>1</span>:<span class='fl'>2</span>)</div><div class='img'><img src='plot.nlme.mmkin-1.png' alt='' width='700' height='433' /></div></pre>
+<span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>f_nlme</span>, <span class='fl'>3</span>:<span class='fl'>4</span>)</div><div class='img'><img src='plot.nlme.mmkin-2.png' alt='' width='700' height='433' /></div></pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="sidebar">
<h2>Contents</h2>
diff --git a/man/nlme.Rd b/man/nlme.Rd
index f31c7a4f..4a668ac0 100644
--- a/man/nlme.Rd
+++ b/man/nlme.Rd
@@ -8,17 +8,22 @@
\usage{
nlme_function(object)
-mean_degparms(object)
+mean_degparms(object, random = FALSE)
nlme_data(object)
}
\arguments{
\item{object}{An mmkin row object containing several fits of the same model to different datasets}
+
+\item{random}{Should a list with fixed and random effects be returned?}
}
\value{
A function that can be used with nlme
-A named vector containing mean values of the fitted degradation model parameters
+If random is FALSE (default), a named vector containing mean values
+ of the fitted degradation model parameters. If random is TRUE, a list with
+ fixed and random effects, in the format required by the start argument of
+ nlme for the case of a single grouping variable ds?
A \code{\link{groupedData}} object
}
@@ -67,71 +72,10 @@ m_nlme <- nlme(value ~ nlme_f(name, time, parent_0, log_k_parent_sink),
start = mean_dp)
summary(m_nlme)
plot(augPred(m_nlme, level = 0:1), layout = c(3, 1))
+# augPred does not seem to work on fits with more than one state
+# variable
-\dontrun{
- # Test on some real data
- ds_2 <- lapply(experimental_data_for_UBA_2019[6:10],
- function(x) x$data[c("name", "time", "value")])
- m_sfo_sfo <- mkinmod(parent = mkinsub("SFO", "A1"),
- A1 = mkinsub("SFO"), use_of_ff = "min")
- m_sfo_sfo_ff <- mkinmod(parent = mkinsub("SFO", "A1"),
- A1 = mkinsub("SFO"), use_of_ff = "max")
- m_fomc_sfo <- mkinmod(parent = mkinsub("FOMC", "A1"),
- A1 = mkinsub("SFO"))
- m_dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "A1"),
- A1 = mkinsub("SFO"))
- m_sforb_sfo <- mkinmod(parent = mkinsub("SFORB", "A1"),
- A1 = mkinsub("SFO"))
-
- f_2 <- mmkin(list("SFO-SFO" = m_sfo_sfo,
- "SFO-SFO-ff" = m_sfo_sfo_ff,
- "FOMC-SFO" = m_fomc_sfo,
- "DFOP-SFO" = m_dfop_sfo,
- "SFORB-SFO" = m_sforb_sfo),
- ds_2)
-
- grouped_data_2 <- nlme_data(f_2["SFO-SFO", ])
-
- mean_dp_sfo_sfo <- mean_degparms(f_2["SFO-SFO", ])
- mean_dp_sfo_sfo_ff <- mean_degparms(f_2["SFO-SFO-ff", ])
- mean_dp_fomc_sfo <- mean_degparms(f_2["FOMC-SFO", ])
- mean_dp_dfop_sfo <- mean_degparms(f_2["DFOP-SFO", ])
- mean_dp_sforb_sfo <- mean_degparms(f_2["SFORB-SFO", ])
-
- nlme_f_sfo_sfo <- nlme_function(f_2["SFO-SFO", ])
- nlme_f_sfo_sfo_ff <- nlme_function(f_2["SFO-SFO-ff", ])
- nlme_f_fomc_sfo <- nlme_function(f_2["FOMC-SFO", ])
- assign("nlme_f_sfo_sfo", nlme_f_sfo_sfo, globalenv())
- assign("nlme_f_sfo_sfo_ff", nlme_f_sfo_sfo_ff, globalenv())
- assign("nlme_f_fomc_sfo", nlme_f_fomc_sfo, globalenv())
-
- # Allowing for correlations between random effects (not shown)
- # leads to non-convergence
- f_nlme_sfo_sfo <- nlme(value ~ nlme_f_sfo_sfo(name, time,
- parent_0, log_k_parent_sink, log_k_parent_A1, log_k_A1_sink),
- data = grouped_data_2,
- fixed = parent_0 + log_k_parent_sink + log_k_parent_A1 + log_k_A1_sink ~ 1,
- random = pdDiag(parent_0 + log_k_parent_sink + log_k_parent_A1 + log_k_A1_sink ~ 1),
- start = mean_dp_sfo_sfo)
- # augPred does not see to work on this object, so no plot is shown
-
- # The same model fitted with transformed formation fractions does not converge
- f_nlme_sfo_sfo_ff <- nlme(value ~ nlme_f_sfo_sfo_ff(name, time,
- parent_0, log_k_parent, log_k_A1, f_parent_ilr_1),
- data = grouped_data_2,
- fixed = parent_0 + log_k_parent + log_k_A1 + f_parent_ilr_1 ~ 1,
- random = pdDiag(parent_0 + log_k_parent + log_k_A1 + f_parent_ilr_1 ~ 1),
- start = mean_dp_sfo_sfo_ff)
-
- f_nlme_fomc_sfo <- nlme(value ~ nlme_f_fomc_sfo(name, time,
- parent_0, log_alpha, log_beta, log_k_A1, f_parent_ilr_1),
- data = grouped_data_2,
- fixed = parent_0 + log_alpha + log_beta + log_k_A1 + f_parent_ilr_1 ~ 1,
- random = pdDiag(parent_0 + log_alpha + log_beta + log_k_A1 + f_parent_ilr_1 ~ 1),
- start = mean_dp_fomc_sfo)
-
- # DFOP-SFO and SFORB-SFO did not converge with full random effects
-
- anova(f_nlme_fomc_sfo, f_nlme_sfo_sfo)
}
+\seealso{
+\code{\link{nlme.mmkin}}
}
diff --git a/man/nlme.mmkin.Rd b/man/nlme.mmkin.Rd
index 1fecb5dd..26dcce66 100644
--- a/man/nlme.mmkin.Rd
+++ b/man/nlme.mmkin.Rd
@@ -2,6 +2,8 @@
% Please edit documentation in R/nlme.mmkin.R
\name{nlme.mmkin}
\alias{nlme.mmkin}
+\alias{print.nlme.mmkin}
+\alias{update.nlme.mmkin}
\title{Create an nlme model for an mmkin row object}
\usage{
\method{nlme}{mmkin}(
@@ -20,11 +22,15 @@
control = list(),
verbose = FALSE
)
+
+\method{print}{nlme.mmkin}(x, ...)
+
+\method{update}{nlme.mmkin}(object, ...)
}
\arguments{
\item{model}{An \code{\link{mmkin}} row object.}
-\item{data}{Ignored, data are taken from the mmkin model}
+\item{data}{Should the data be printed?}
\item{fixed}{Ignored, all degradation parameters fitted in the
mmkin model are used as fixed parameters}
@@ -52,6 +58,12 @@ parameters taken from the mmkin object are used}
\item{control}{passed to nlme}
\item{verbose}{passed to nlme}
+
+\item{x}{An nlme.mmkin object to print}
+
+\item{...}{Update specifications passed to update.nlme}
+
+\item{object}{An nlme.mmkin object to update}
}
\value{
Upon success, a fitted nlme.mmkin object, which is an nlme object
@@ -68,9 +80,52 @@ ds <- lapply(experimental_data_for_UBA_2019[6:10],
f <- mmkin("SFO", ds, quiet = TRUE, cores = 1)
library(nlme)
f_nlme <- nlme(f)
-nlme(f, random = parent_0 ~ 1)
-f_nlme <- nlme(f, start = c(parent_0 = 100, log_k_parent_sink = 0.1))
-update(f_nlme, random = parent_0 ~ 1)
+print(f_nlme)
+f_nlme_2 <- nlme(f, start = c(parent_0 = 100, log_k_parent_sink = 0.1))
+update(f_nlme_2, random = parent_0 ~ 1)
+\dontrun{
+ # Test on some real data
+ ds_2 <- lapply(experimental_data_for_UBA_2019[6:10],
+ function(x) x$data[c("name", "time", "value")])
+ m_sfo_sfo <- mkinmod(parent = mkinsub("SFO", "A1"),
+ A1 = mkinsub("SFO"), use_of_ff = "min", quiet = TRUE)
+ m_sfo_sfo_ff <- mkinmod(parent = mkinsub("SFO", "A1"),
+ A1 = mkinsub("SFO"), use_of_ff = "max", quiet = TRUE)
+ m_fomc_sfo <- mkinmod(parent = mkinsub("FOMC", "A1"),
+ A1 = mkinsub("SFO"), quiet = TRUE)
+ m_dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "A1"),
+ A1 = mkinsub("SFO"), quiet = TRUE)
+
+ f_2 <- mmkin(list("SFO-SFO" = m_sfo_sfo,
+ "SFO-SFO-ff" = m_sfo_sfo_ff,
+ "FOMC-SFO" = m_fomc_sfo,
+ "DFOP-SFO" = m_dfop_sfo),
+ ds_2, quiet = TRUE)
+ plot(f_2["SFO-SFO", 3:4]) # Separate fits for datasets 3 and 4
+
+ f_nlme_sfo_sfo <- nlme(f_2["SFO-SFO", ])
+ # plot(f_nlme_sfo_sfo) # not feasible with pkgdown figures
+ plot(f_nlme_sfo_sfo, 3:4) # Global mixed model: Fits for datasets 3 and 4
+
+ # With formation fractions
+ f_nlme_sfo_sfo_ff <- nlme(f_2["SFO-SFO-ff", ])
+ plot(f_nlme_sfo_sfo_ff, 3:4) # chi2 different due to different df attribution
+
+ # For more parameters, we need to increase pnlsMaxIter and the tolerance
+ # to get convergence
+ f_nlme_fomc_sfo <- nlme(f_2["FOMC-SFO", ],
+ control = list(pnlsMaxIter = 100, tolerance = 1e-4), verbose = TRUE)
+ f_nlme_dfop_sfo <- nlme(f_2["DFOP-SFO", ],
+ control = list(pnlsMaxIter = 120, tolerance = 5e-4), verbose = TRUE)
+ plot(f_2["FOMC-SFO", 3:4])
+ plot(f_nlme_fomc_sfo, 3:4)
+
+ plot(f_2["DFOP-SFO", 3:4])
+ plot(f_nlme_dfop_sfo, 3:4)
+
+ anova(f_nlme_dfop_sfo, f_nlme_fomc_sfo, f_nlme_sfo_sfo)
+ anova(f_nlme_dfop_sfo, f_nlme_sfo_sfo) # if we ignore FOMC
+}
}
\seealso{
\code{\link{nlme_function}}
diff --git a/man/plot.mmkin.Rd b/man/plot.mmkin.Rd
index 982e8db6..600881ea 100644
--- a/man/plot.mmkin.Rd
+++ b/man/plot.mmkin.Rd
@@ -33,7 +33,7 @@ column.}
values, with the error model, using \code{\link{mkinerrplot}}.}
\item{standardized}{Should the residuals be standardized? This option
-is passed to \code{\link{mkinresplot}}, it only takes effect if
+is passed to \code{\link{mkinresplot}}, it only takes effect if
`resplot = "time"`.}
\item{show_errmin}{Should the chi2 error level be shown on top of the plots
@@ -76,6 +76,7 @@ latex is being used for the formatting of the chi2 error level.
cores = 1, quiet = TRUE, error_model = "tc")
plot(fits[, "FOCUS C"])
plot(fits["FOMC", ])
+ plot(fits["FOMC", ], show_errmin = FALSE)
# We can also plot a single fit, if we like the way plot.mmkin works, but then the plot
# height should be smaller than the plot width (this is not possible for the html pages
diff --git a/man/plot.nlme.mmkin.Rd b/man/plot.nlme.mmkin.Rd
index c0e749aa..9bea7013 100644
--- a/man/plot.nlme.mmkin.Rd
+++ b/man/plot.nlme.mmkin.Rd
@@ -11,6 +11,9 @@
legends = 1,
resplot = c("time", "errmod"),
standardized = FALSE,
+ show_errmin = TRUE,
+ errmin_var = "All data",
+ errmin_digits = 3,
cex = 0.7,
rel.height.middle = 0.9,
ymax = "auto",
@@ -35,6 +38,15 @@ values, with the error model, using \code{\link{mkinerrplot}}.}
is passed to \code{\link{mkinresplot}}, it only takes effect if
`resplot = "time"`.}
+\item{show_errmin}{Should the chi2 error level be shown on top of the plots
+to the left?}
+
+\item{errmin_var}{The variable for which the FOCUS chi2 error value should
+be shown.}
+
+\item{errmin_digits}{The number of significant digits for rounding the FOCUS
+chi2 error percentage.}
+
\item{cex}{Passed to the plot functions and \code{\link{mtext}}.}
\item{rel.height.middle}{The relative height of the middle plot, if more
@@ -56,11 +68,12 @@ ds <- lapply(experimental_data_for_UBA_2019[6:10],
function(x) subset(x$data[c("name", "time", "value")], name == "parent"))
f <- mmkin("SFO", ds, quiet = TRUE, cores = 1)
#plot(f) # too many panels for pkgdown
+plot(f[, 3:4])
library(nlme)
f_nlme <- nlme(f)
#plot(f_nlme) # too many panels for pkgdown
-plot(f_nlme, 1:2)
+plot(f_nlme, 3:4)
}
\author{
Johannes Ranke

Contact - Imprint