From 42171ba55222383a0d47e5aacd46a972819e7812 Mon Sep 17 00:00:00 2001
From: Johannes Ranke
Date: Wed, 15 Apr 2020 18:13:04 +0200
Subject: 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
---
NAMESPACE | 3 +
R/nlme.R | 88 ++++--------------
R/nlme.mmkin.R | 100 +++++++++++++++++++-
R/plot.nlme.mmkin.R | 22 ++++-
docs/reference/index.html | 2 +-
docs/reference/nlme.html | 80 ++++------------
docs/reference/nlme.mmkin-1.png | Bin 0 -> 69863 bytes
docs/reference/nlme.mmkin-2.png | Bin 0 -> 70426 bytes
docs/reference/nlme.mmkin-3.png | Bin 0 -> 70519 bytes
docs/reference/nlme.mmkin-4.png | Bin 0 -> 72803 bytes
docs/reference/nlme.mmkin-5.png | Bin 0 -> 72587 bytes
docs/reference/nlme.mmkin-6.png | Bin 0 -> 71892 bytes
docs/reference/nlme.mmkin-7.png | Bin 0 -> 72316 bytes
docs/reference/nlme.mmkin.html | 172 ++++++++++++++++++++++++++++++++---
docs/reference/plot.mmkin-3.png | Bin 25550 -> 32259 bytes
docs/reference/plot.mmkin-4.png | Bin 38129 -> 25550 bytes
docs/reference/plot.mmkin-5.png | Bin 0 -> 38129 bytes
docs/reference/plot.mmkin.html | 8 +-
docs/reference/plot.nlme.mmkin-1.png | Bin 32297 -> 35382 bytes
docs/reference/plot.nlme.mmkin-2.png | Bin 0 -> 35313 bytes
docs/reference/plot.nlme.mmkin.html | 22 ++++-
man/nlme.Rd | 78 +++-------------
man/nlme.mmkin.Rd | 63 ++++++++++++-
man/plot.mmkin.Rd | 3 +-
man/plot.nlme.mmkin.Rd | 15 ++-
25 files changed, 420 insertions(+), 236 deletions(-)
create mode 100644 docs/reference/nlme.mmkin-1.png
create mode 100644 docs/reference/nlme.mmkin-2.png
create mode 100644 docs/reference/nlme.mmkin-3.png
create mode 100644 docs/reference/nlme.mmkin-4.png
create mode 100644 docs/reference/nlme.mmkin-5.png
create mode 100644 docs/reference/nlme.mmkin-6.png
create mode 100644 docs/reference/nlme.mmkin-7.png
create mode 100644 docs/reference/plot.mmkin-5.png
create mode 100644 docs/reference/plot.nlme.mmkin-2.png
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
- nlme(<mmkin>)
+ nlme(<mmkin>) print(<nlme.mmkin>) update(<nlme.mmkin>)
|
Create an nlme model for an mmkin row object |
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.
nlme_function(object)
-mean_degparms(object)
+mean_degparms(object, random = FALSE)
nlme_data(object)
@@ -155,13 +155,23 @@ datasets.
object |
An mmkin row object containing several fits of the same model to different datasets |
+
+ 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 groupedData
object
+ See also
+
+
Examples
#> Successfully compiled differential equation model from auto-generated C code.
#> Successfully compiled differential equation model from auto-generated C code.
#> Successfully compiled differential equation model from auto-generated C code.
#> Successfully compiled differential equation model from auto-generated C code.
#> Successfully compiled differential equation model from auto-generated C code.
#> 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
#> Model df AIC BIC logLik Test L.Ratio p-value
-#> f_nlme_fomc_sfo 1 11 932.5817 967.0755 -455.2909
-#> f_nlme_sfo_sfo 2 9 1089.2492 1117.4714 -535.6246 1 vs 2 160.6675 <.0001
# }
+#> Number of Groups: 3
# augPred does not seem to work on fits with more than one state
+# variable
+
#> Nonlinear mixed-effects model fit by maximum likelihood
+
print(
f_nlme)
#> Nonlinear mixed-effects model fit by maximum likelihood
#> Model: value ~ deg_func(name, time, parent_0, log_k_parent_sink)
-#> 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)
-#> Log-likelihood: -394.4901
+#> Data: "Not shown"
+#> Log-likelihood: -307.5269
#> Fixed: list(parent_0 ~ 1, log_k_parent_sink ~ 1)
#> parent_0 log_k_parent_sink
-#> 73.985522 -3.869079
+#> 85.541149 -3.229596
#>
#> Random effects:
-#> Formula: parent_0 ~ 1 | ds
-#> parent_0 Residual
-#> StdDev: 18.6134 18.22029
+#> Formula: list(parent_0 ~ 1, log_k_parent_sink ~ 1)
+#> Level: ds
+#> Structure: Diagonal
+#> parent_0 log_k_parent_sink Residual
+#> StdDev: 1.30857 1.288591 6.304906
#>
#> Number of Observations: 90
-#> Number of Groups: 5
#> Nonlinear mixed-effects model fit by maximum likelihood
+#> Number of Groups: 5
#> Nonlinear mixed-effects model fit by maximum likelihood
#> Model: value ~ deg_func(name, time, parent_0, log_k_parent_sink)
-#> 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)
+#> Data: "Not shown"
#> Log-likelihood: -404.3729
#> Fixed: list(parent_0 ~ 1, log_k_parent_sink ~ 1)
#> parent_0 log_k_parent_sink
@@ -265,7 +285,133 @@ parameters taken from the mmkin object are used
#> StdDev: 0.002416792 21.63027
#>
#> Number of Observations: 90
-#> Number of Groups: 5
+#> Number of Groups: 5 


#>
+#> **Iteration 1
+#> LME step: Loglik: -394.1603, nlminb iterations: 2
+#> reStruct parameters:
+#> ds1 ds2 ds3 ds4 ds5
+#> -0.2079984 0.8563873 1.7454146 1.0917723 1.2756924
+#> Beginning PNLS step: .. completed fit_nlme() step.
+#> PNLS step: RSS = 643.8786
+#> fixed effects: 94.17379 -5.473199 -0.6970239 -0.2025094 2.103883
+#> iterations: 100
+#> Convergence crit. (must all become <= tolerance = 0.0001):
+#> fixed reStruct
+#> 0.7865373 0.1448077
+#>
+#> **Iteration 2
+#> LME step: Loglik: -396.3824, nlminb iterations: 7
+#> reStruct parameters:
+#> ds1 ds2 ds3 ds4 ds5
+#> -1.712408e-01 -2.680989e-05 1.842119e+00 1.073975e+00 1.322924e+00
+#> Beginning PNLS step: .. completed fit_nlme() step.
+#> PNLS step: RSS = 643.8022
+#> fixed effects: 94.17385 -5.473491 -0.6970405 -0.202514 2.103871
+#> iterations: 100
+#> Convergence crit. (must all become <= tolerance = 0.0001):
+#> fixed reStruct
+#> 5.341904e-05 1.227073e-03
+#>
+#> **Iteration 3
+#> LME step: Loglik: -396.3825, nlminb iterations: 7
+#> reStruct parameters:
+#> ds1 ds2 ds3 ds4 ds5
+#> -0.1712484347 -0.0001513555 1.8420964843 1.0739800649 1.3229176990
+#> Beginning PNLS step: .. completed fit_nlme() step.
+#> PNLS step: RSS = 643.7947
+#> fixed effects: 94.17386 -5.473522 -0.6970423 -0.2025142 2.10387
+#> iterations: 100
+#> Convergence crit. (must all become <= tolerance = 0.0001):
+#> fixed reStruct
+#> 5.568186e-06 1.276609e-04
+#>
+#> **Iteration 4
+#> LME step: Loglik: -396.3825, nlminb iterations: 7
+#> reStruct parameters:
+#> ds1 ds2 ds3 ds4 ds5
+#> -0.171251200 -0.000164506 1.842095097 1.073980200 1.322916184
+#> Beginning PNLS step: .. completed fit_nlme() step.
+#> PNLS step: RSS = 643.7934
+#> fixed effects: 94.17386 -5.473526 -0.6970426 -0.2025146 2.103869
+#> iterations: 100
+#> Convergence crit. (must all become <= tolerance = 0.0001):
+#> fixed reStruct
+#> 2.332100e-06 1.979007e-05
#>
+#> **Iteration 1
+#> LME step: Loglik: -404.9591, nlminb iterations: 1
+#> reStruct parameters:
+#> ds1 ds2 ds3 ds4 ds5 ds6
+#> -0.4114594 0.9798456 1.6990016 0.7293119 0.3353829 1.7112922
+#> Beginning PNLS step: .. completed fit_nlme() step.
+#> PNLS step: RSS = 630.391
+#> fixed effects: 93.82265 -5.455841 -0.6788837 -1.862191 -4.199654 0.05531046
+#> iterations: 120
+#> Convergence crit. (must all become <= tolerance = 0.0005):
+#> fixed reStruct
+#> 0.7872619 0.5811683
+#>
+#> **Iteration 2
+#> LME step: Loglik: -407.7755, nlminb iterations: 11
+#> reStruct parameters:
+#> ds1 ds2 ds3 ds4 ds5 ds6
+#> -0.371222832 0.003084754 1.789952290 0.724634064 0.301559136 1.754244638
+#> Beginning PNLS step: .. completed fit_nlme() step.
+#> PNLS step: RSS = 630.359
+#> fixed effects: 93.82269 -5.456014 -0.6788967 -1.862202 -4.199678 0.05534118
+#> iterations: 120
+#> Convergence crit. (must all become <= tolerance = 0.0005):
+#> fixed reStruct
+#> 0.0005550885 0.0007749418
+#>
+#> **Iteration 3
+#> LME step: Loglik: -407.7756, nlminb iterations: 11
+#> reStruct parameters:
+#> ds1 ds2 ds3 ds4 ds5 ds6
+#> -0.371217033 0.003064156 1.789935045 0.724683005 0.301622307 1.754234135
+#> Beginning PNLS step: .. completed fit_nlme() step.
+#> PNLS step: RSS = 630.358
+#> fixed effects: 93.82269 -5.456017 -0.6788969 -1.862197 -4.199677 0.05532978
+#> iterations: 120
+#> Convergence crit. (must all become <= tolerance = 0.0005):
+#> fixed reStruct
+#> 2.059533e-04 4.860085e-05
#> Model df AIC BIC logLik Test L.Ratio p-value
+#> f_nlme_dfop_sfo 1 13 843.8541 884.6194 -408.9270
+#> f_nlme_fomc_sfo 2 11 818.5149 853.0087 -398.2575 1 vs 2 21.33913 <.0001
+#> f_nlme_sfo_sfo 3 9 1085.1821 1113.4042 -533.5910 2 vs 3 270.66712 <.0001
#> Model df AIC BIC logLik Test L.Ratio p-value
+#> f_nlme_dfop_sfo 1 13 843.8541 884.6194 -408.927
+#> f_nlme_sfo_sfo 2 9 1085.1821 1113.4042 -533.591 1 vs 2 249.328 <.0001
# }
+