diff options
| author | Johannes Ranke <jranke@uni-bremen.de> | 2020-11-09 17:24:53 +0100 | 
|---|---|---|
| committer | Johannes Ranke <jranke@uni-bremen.de> | 2020-11-09 17:24:53 +0100 | 
| commit | aa74f5a30853fb0a15c99c283e072f08ee819149 (patch) | |
| tree | 988ec89e22b48fff4544653a4c3443356bab3071 | |
| parent | a1631098acfc3352e19c331e568bd6f5766b3c3d (diff) | |
saemix.mmkin and nlme.mmkin inherit from mixed.mmkin
With a plot method. The class mixed.mmkin is currently only a virtual
class created to unify the plotting method.
25 files changed, 450 insertions, 213 deletions
| @@ -16,11 +16,10 @@ S3method(nlme,mmkin)  S3method(nobs,mkinfit)  S3method(parms,mkinfit)  S3method(parms,mmkin) +S3method(plot,mixed.mmkin)  S3method(plot,mkinfit)  S3method(plot,mmkin)  S3method(plot,nafta) -S3method(plot,nlme.mmkin) -S3method(plot,saem.mmkin)  S3method(print,mkinds)  S3method(print,mkinmod)  S3method(print,mmkin) @@ -1,6 +1,8 @@  # mkin 0.9.50.4 (unreleased) -- 'saem' generic function to fit saemix models, with a method 'saem.mmkin' and a corresponding 'summary.saem.mmkin' +- 'plot.mixed.mmkin' method used for 'nlme.mmkin' and 'saem.mmkin', both inheriting from 'mixed.mmkin' (currently virtual) + +- 'saem' generic function to fit saemix models, with a generator 'saem.mmkin', summary and plot methods  - 'transform_odeparms', 'backtransform_odeparms': Use logit transformation for solitary fractions like the g parameter of the DFOP model, or formation fractions for a pathway to only one target variable diff --git a/R/nlme.mmkin.R b/R/nlme.mmkin.R index 695c63e9..8d875fee 100644 --- a/R/nlme.mmkin.R +++ b/R/nlme.mmkin.R @@ -43,13 +43,14 @@ get_deg_func <- function() {  #' @param control passed to nlme  #' @param verbose passed to nlme  #' @importFrom stats na.fail as.formula -#' @return Upon success, a fitted nlme.mmkin object, which is an nlme object -#'   with additional elements +#' @return Upon success, a fitted 'nlme.mmkin' object, which is an nlme object +#'   with additional elements. It also inherits from 'mixed.mmkin'.  #' @note As the object inherits from [nlme::nlme], there is a wealth of  #'   methods that will automatically work on 'nlme.mmkin' objects, such as  #'   [nlme::intervals()], [nlme::anova.lme()] and [nlme::coef.lme()].  #' @export -#' @seealso [nlme_function()] +#' @seealso [nlme_function()], [plot.mixed.mmkin], [summary.nlme.mmkin], +#'  [parms.nlme.mmkin]  #' @examples  #' ds <- lapply(experimental_data_for_UBA_2019[6:10],  #'  function(x) subset(x$data[c("name", "time", "value")], name == "parent")) @@ -203,7 +204,7 @@ nlme.mmkin <- function(model, data = sys.frame(sys.parent()),    val$nlmeversion <- as.character(utils::packageVersion("nlme"))    val$mkinversion <- as.character(utils::packageVersion("mkin"))    val$Rversion <- paste(R.version$major, R.version$minor, sep=".") -  class(val) <- c("nlme.mmkin", "nlme", "lme") +  class(val) <- c("nlme.mmkin", "mixed.mmkin", "nlme", "lme")    return(val)  } diff --git a/R/plot_mixed.R b/R/plot.mixed.mmkin.R index 68404de4..903c3213 100644 --- a/R/plot_mixed.R +++ b/R/plot.mixed.mmkin.R @@ -2,7 +2,6 @@ if(getRversion() >= '2.15.1') utils::globalVariables("ds")  #' Plot predictions from a fitted nonlinear mixed model obtained via an mmkin row object  #' -#' @name plot_mixed  #' @param x An object of class [saem.mmkin] or [nlme.mmkin]  #' @param i A numeric index to select datasets for which to plot the individual predictions,  #'   in case plots get too large @@ -21,7 +20,7 @@ if(getRversion() >= '2.15.1') utils::globalVariables("ds")  #' @param pch_ds Symbols to be used for plotting the data.  #' @param lty_ds Line types to be used for the model predictions.  #' @importFrom stats coefficients -#' @return The functions are called for their side effect. +#' @return The function is called for its side effect.  #' @author Johannes Ranke  #' @examples  #' ds <- lapply(experimental_data_for_UBA_2019[6:10], @@ -33,7 +32,6 @@ if(getRversion() >= '2.15.1') utils::globalVariables("ds")  #' f <- mmkin(list("DFOP-SFO" = dfop_sfo), ds, quiet = TRUE)  #' plot(f[, 3:4], standardized = TRUE)  #' -#' library(nlme)  #' # For this fit we need to increase pnlsMaxiter, and we increase the  #' # tolerance in order to speed up the fit for this example evaluation  #' f_nlme <- nlme(f, control = list(pnlsMaxIter = 120, tolerance = 1e-3)) @@ -42,9 +40,9 @@ if(getRversion() >= '2.15.1') utils::globalVariables("ds")  #' f_saem <- saem(f)  #' plot(f_saem)  #' } -#' @rdname plot_mixed  #' @export -plot.saem.mmkin <- function(x, i = 1:ncol(x$mmkin), +plot.mixed.mmkin <- function(x, +  i = 1:ncol(x$mmkin),    obs_vars = names(x$mkinmod$map),    standardized = TRUE,    xlab = "Time", @@ -58,89 +56,30 @@ plot.saem.mmkin <- function(x, i = 1:ncol(x$mmkin),    pch_ds = 1:length(i),    col_ds = pch_ds + 1,    lty_ds = col_ds, -  frame = TRUE, ...) +  frame = TRUE, ... +)  { +  # Prepare parameters and data    fit_1 <- x$mmkin[[1]]    ds_names <- colnames(x$mmkin) -  degparms_optim <- saemix::psi(x$so) -  rownames(degparms_optim) <- ds_names -  degparms_optim_names <- setdiff(names(fit_1$par), names(fit_1$errparms)) -  colnames(degparms_optim) <- degparms_optim_names - -  residual_type = ifelse(standardized, "iwres", "ires") - -  residuals <- x$so@results@predictions[[residual_type]] - -  degparms_pop <- x$so@results@fixed.effects -  names(degparms_pop) <- degparms_optim_names - -  .plot_mixed(x, i, -    degparms_optim, degparms_pop, residuals, -    obs_vars, standardized, xlab, xlim, -    resplot, ymax, maxabs, -    ncol.legend, nrow.legend, -    rel.height.legend, rel.height.bottom, -    pch_ds, col_ds, lty_ds, frame, ...) -} - -#' @rdname plot_mixed -#' @export -plot.nlme.mmkin <- function(x, i = 1:ncol(x$mmkin), -  obs_vars = names(x$mkinmod$map), -  standardized = TRUE, -  xlab = "Time", -  xlim = range(x$data$time), -  resplot = c("predicted", "time"), -  ymax = "auto", maxabs = "auto", -  ncol.legend = ifelse(length(i) <= 3, length(i) + 1, ifelse(length(i) <= 8, 3, 4)), -  nrow.legend = ceiling((length(i) + 1) / ncol.legend), -  rel.height.legend = 0.03 + 0.08 * nrow.legend, -  rel.height.bottom = 1.1, -  pch_ds = 1:length(i), -  col_ds = pch_ds + 1, -  lty_ds = col_ds, -  frame = TRUE, ...) -{ -  degparms_optim <- coefficients(x) -  degparms_pop <- nlme::fixef(x) - -  residuals <- residuals(x, -    type = ifelse(standardized, "pearson", "response")) - -  .plot_mixed(x, i, -    degparms_optim, degparms_pop, residuals, -    obs_vars, standardized, xlab, xlim, -    resplot, ymax, maxabs, -    ncol.legend, nrow.legend, -    rel.height.legend, rel.height.bottom, -    pch_ds, col_ds, lty_ds, frame, ...) -} - -.plot_mixed <- function(x, i = 1:ncol(x$mmkin), -  degparms_optim, -  degparms_pop, -  residuals, -  obs_vars = names(x$mkinmod$map), -  standardized = TRUE, -  xlab = "Time", -  xlim = range(x$data$time), -  resplot = c("predicted", "time"), -  ymax = "auto", maxabs = "auto", -  ncol.legend = ifelse(length(i) <= 3, length(i) + 1, ifelse(length(i) <= 8, 3, 4)), -  nrow.legend = ceiling((length(i) + 1) / ncol.legend), -  rel.height.legend = 0.03 + 0.08 * nrow.legend, -  rel.height.bottom = 1.1, -  pch_ds = 1:length(i), -  col_ds = pch_ds + 1, -  lty_ds = col_ds, -  frame = TRUE, ...) -{ - -  oldpar <- par(no.readonly = TRUE) +  if (inherits(x, "nlme.mmkin")) { +    degparms_optim <- coefficients(x) +    degparms_pop <- nlme::fixef(x) +    residuals <- residuals(x, +      type = ifelse(standardized, "pearson", "response")) +  } -  fit_1 <- x$mmkin[[1]] -  ds_names <- colnames(x$mmkin) +  if (inherits(x, "saem.mmkin")) { +    degparms_optim <- saemix::psi(x$so) +    rownames(degparms_optim) <- ds_names +    degparms_optim_names <- setdiff(names(fit_1$par), names(fit_1$errparms)) +    colnames(degparms_optim) <- degparms_optim_names +    residual_type = ifelse(standardized, "iwres", "ires") +    residuals <- x$so@results@predictions[[residual_type]] +    degparms_pop <- x$so@results@fixed.effects +    names(degparms_pop) <- degparms_optim_names +  }    degparms_fixed <- fit_1$fixed$value    names(degparms_fixed) <- rownames(fit_1$fixed) @@ -161,29 +100,6 @@ plot.nlme.mmkin <- function(x, i = 1:ncol(x$mmkin),    observed <- cbind(x$data,      residual = residuals) -  n_plot_rows = length(obs_vars) -  n_plots = n_plot_rows * 2 - -  # Set relative plot heights, so the first plot row is the norm -  rel.heights <- if (n_plot_rows > 1) { -    c(rel.height.legend, c(rep(1, n_plot_rows - 1), rel.height.bottom)) -  } else { -    c(rel.height.legend, 1) -  } - -  layout_matrix = matrix(c(1, 1, 2:(n_plots + 1)), -    n_plot_rows + 1, 2, byrow = TRUE) -  layout(layout_matrix, heights = rel.heights) - -  par(mar = c(0.1, 2.1, 0.6, 2.1)) - -  plot(0, type = "n", axes = FALSE, ann = FALSE) -  legend("center", bty = "n", ncol = ncol.legend, -    legend = c("Population", ds_names[i]), -    lty = c(1, lty_ds), lwd = c(2, rep(1, length(i))), -    col = c(1, col_ds), -    pch = c(NA, pch_ds)) -    solution_type = fit_1$solution_type    outtimes <- sort(unique(c(x$data$time, @@ -220,6 +136,32 @@ plot.nlme.mmkin <- function(x, i = 1:ncol(x$mmkin),        outtimes, solution_type = solution_type,        atol = fit_1$atol, rtol = fit_1$rtol)) +  # Start of graphical section +  oldpar <- par(no.readonly = TRUE) + +  n_plot_rows = length(obs_vars) +  n_plots = n_plot_rows * 2 + +  # Set relative plot heights, so the first plot row is the norm +  rel.heights <- if (n_plot_rows > 1) { +    c(rel.height.legend, c(rep(1, n_plot_rows - 1), rel.height.bottom)) +  } else { +    c(rel.height.legend, 1) +  } + +  layout_matrix = matrix(c(1, 1, 2:(n_plots + 1)), +    n_plot_rows + 1, 2, byrow = TRUE) +  layout(layout_matrix, heights = rel.heights) + +  par(mar = c(0.1, 2.1, 0.6, 2.1)) + +  plot(0, type = "n", axes = FALSE, ann = FALSE) +  legend("center", bty = "n", ncol = ncol.legend, +    legend = c("Population", ds_names[i]), +    lty = c(1, lty_ds), lwd = c(2, rep(1, length(i))), +    col = c(1, col_ds), +    pch = c(NA, pch_ds)) +    resplot <- match.arg(resplot)    # Loop plot rows @@ -24,8 +24,9 @@  #' @param \dots Further parameters passed to [saemix::saemixData]  #'   and [saemix::saemixModel].  #' @return An S3 object of class 'saem.mmkin', containing the fitted -#'   [saemix::SaemixObject] as a list component named 'so'. -#' @seealso [summary.saem.mmkin] +#'   [saemix::SaemixObject] as a list component named 'so'. The +#'   object also inherits from 'mixed.mmkin'. +#' @seealso [summary.saem.mmkin] [plot.mixed.mmkin]  #' @examples  #' \dontrun{  #' ds <- lapply(experimental_data_for_UBA_2019[6:10], @@ -134,7 +135,7 @@ saem.mmkin <- function(object,      Rversion = paste(R.version$major, R.version$minor, sep=".")    ) -  class(result) <- "saem.mmkin" +  class(result) <- c("saem.mmkin", "mixed.mmkin")    return(result)  } diff --git a/_pkgdown.yml b/_pkgdown.yml index 61c69a9d..75296568 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -42,11 +42,10 @@ reference:      desc: Create and work with nonlinear mixed effects models      contents:        - nlme.mmkin -      - plot.nlme.mmkin -      - summary.nlme.mmkin        - saem.mmkin +      - plot.mixed.mmkin +      - summary.nlme.mmkin        - summary.saem.mmkin -      - plot.saem.mmkin        - nlme_function        - get_deg_func        - saemix_model diff --git a/docs/dev/news/index.html b/docs/dev/news/index.html index 4f811b9f..c068b8a4 100644 --- a/docs/dev/news/index.html +++ b/docs/dev/news/index.html @@ -146,7 +146,7 @@  <a href="#mkin-0-9-50-4-unreleased" class="anchor"></a>mkin 0.9.50.4 (unreleased)<small> Unreleased </small>  </h1>  <ul> -<li><p>‘saem’ generic function to fit saemix models, with a method ‘saem.mmkin’ and a corresponding ‘summary.saem.mmkin’</p></li> +<li><p>‘saem’ generic function to fit saemix models, with a generator ‘saem.mmkin’ and further methods ‘summary.saem.mmkin’, ‘plot.saem.mmkin’</p></li>  <li><p>‘transform_odeparms’, ‘backtransform_odeparms’: Use logit transformation for solitary fractions like the g parameter of the DFOP model, or formation fractions for a pathway to only one target variable</p></li>  <li><p>‘update’ method for ‘mmkin’ objects</p></li>  <li><p>‘plot’, ‘summary’ and ‘print’ methods for ‘nlme.mmkin’ objects</p></li> diff --git a/docs/dev/pkgdown.yml b/docs/dev/pkgdown.yml index 4b2b76f7..ef9bb681 100644 --- a/docs/dev/pkgdown.yml +++ b/docs/dev/pkgdown.yml @@ -10,7 +10,7 @@ articles:    web_only/NAFTA_examples: NAFTA_examples.html    web_only/benchmarks: benchmarks.html    web_only/compiled_models: compiled_models.html -last_built: 2020-11-09T15:29Z +last_built: 2020-11-09T16:21Z  urls:    reference: https://pkgdown.jrwb.de/mkin/reference    article: https://pkgdown.jrwb.de/mkin/articles diff --git a/docs/dev/reference/Rplot001.png b/docs/dev/reference/Rplot001.pngBinary files differ index cfc5bc2b..fc26276a 100644 --- a/docs/dev/reference/Rplot001.png +++ b/docs/dev/reference/Rplot001.png diff --git a/docs/dev/reference/Rplot002.png b/docs/dev/reference/Rplot002.pngBinary files differ index 8ada7133..48e8698c 100644 --- a/docs/dev/reference/Rplot002.png +++ b/docs/dev/reference/Rplot002.png diff --git a/docs/dev/reference/Rplot003.png b/docs/dev/reference/Rplot003.pngBinary files differ index cd2014eb..b4581e35 100644 --- a/docs/dev/reference/Rplot003.png +++ b/docs/dev/reference/Rplot003.png diff --git a/docs/dev/reference/index.html b/docs/dev/reference/index.html index 5ed2044b..ada9fb24 100644 --- a/docs/dev/reference/index.html +++ b/docs/dev/reference/index.html @@ -325,21 +325,21 @@ of an mmkin object</p></td>        </tr><tr>          <td> -          <p><code><a href="plot_mixed.html">plot(<i><saem.mmkin></i>)</a></code> <code><a href="plot_mixed.html">plot(<i><nlme.mmkin></i>)</a></code> </p> +          <p><code><a href="saem.html">saem()</a></code> <code><a href="saem.html">saemix_model()</a></code> <code><a href="saem.html">saemix_data()</a></code> </p>          </td> -        <td><p>Plot predictions from a fitted nonlinear mixed model obtained via an mmkin row object</p></td> +        <td><p>Fit nonlinear mixed models with SAEM</p></td>        </tr><tr>          <td> -          <p><code><a href="summary.nlme.mmkin.html">summary(<i><nlme.mmkin></i>)</a></code> <code><a href="summary.nlme.mmkin.html">print(<i><summary.nlme.mmkin></i>)</a></code> </p> +          <p><code><a href="plot.mixed.mmkin.html">plot(<i><mixed.mmkin></i>)</a></code> </p>          </td> -        <td><p>Summary method for class "nlme.mmkin"</p></td> +        <td><p>Plot predictions from a fitted nonlinear mixed model obtained via an mmkin row object</p></td>        </tr><tr>          <td> -          <p><code><a href="saem.html">saem()</a></code> <code><a href="saem.html">saemix_model()</a></code> <code><a href="saem.html">saemix_data()</a></code> </p> +          <p><code><a href="summary.nlme.mmkin.html">summary(<i><nlme.mmkin></i>)</a></code> <code><a href="summary.nlme.mmkin.html">print(<i><summary.nlme.mmkin></i>)</a></code> </p>          </td> -        <td><p>Fit nonlinear mixed models with SAEM</p></td> +        <td><p>Summary method for class "nlme.mmkin"</p></td>        </tr><tr>          <td> diff --git a/docs/dev/reference/nlme.mmkin-1.png b/docs/dev/reference/nlme.mmkin-1.pngBinary files differ index 04d8b234..25bebeca 100644 --- a/docs/dev/reference/nlme.mmkin-1.png +++ b/docs/dev/reference/nlme.mmkin-1.png diff --git a/docs/dev/reference/nlme.mmkin-3.png b/docs/dev/reference/nlme.mmkin-3.pngBinary files differ index 281d6024..46846067 100644 --- a/docs/dev/reference/nlme.mmkin-3.png +++ b/docs/dev/reference/nlme.mmkin-3.png diff --git a/docs/dev/reference/nlme.mmkin-4.png b/docs/dev/reference/nlme.mmkin-4.pngBinary files differ index d504e8f0..6724163f 100644 --- a/docs/dev/reference/nlme.mmkin-4.png +++ b/docs/dev/reference/nlme.mmkin-4.png diff --git a/docs/dev/reference/nlme.mmkin.html b/docs/dev/reference/nlme.mmkin.html index c3cc53ff..defef75d 100644 --- a/docs/dev/reference/nlme.mmkin.html +++ b/docs/dev/reference/nlme.mmkin.html @@ -152,7 +152,7 @@ have been obtained by fitting the same model to a list of datasets.</p>      </div>      <pre class="usage"><span class='co'># S3 method for mmkin</span> -<span class='fu'>nlme</span><span class='op'>(</span> +<span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span><span class='op'>(</span>    <span class='va'>model</span>,    data <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/sys.parent.html'>sys.frame</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/sys.parent.html'>sys.parent</a></span><span class='op'>(</span><span class='op'>)</span><span class='op'>)</span>,    <span class='va'>fixed</span>, @@ -253,8 +253,8 @@ parameters taken from the mmkin object are used</p></td>      <h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2> -    <p>Upon success, a fitted nlme.mmkin object, which is an nlme object -with additional elements</p> +    <p>Upon success, a fitted 'nlme.mmkin' object, which is an nlme object +with additional elements. It also inherits from 'mixed.mmkin'.</p>      <h2 class="hasAnchor" id="note"><a class="anchor" href="#note"></a>Note</h2>      <p>As the object inherits from <a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme::nlme</a>, there is a wealth of @@ -262,7 +262,8 @@ methods that will automatically work on 'nlme.mmkin' objects, such as  <code><a href='https://rdrr.io/pkg/nlme/man/intervals.html'>nlme::intervals()</a></code>, <code><a href='https://rdrr.io/pkg/nlme/man/anova.lme.html'>nlme::anova.lme()</a></code> and <code><a href='https://rdrr.io/pkg/nlme/man/coef.lme.html'>nlme::coef.lme()</a></code>.</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_function.html'>nlme_function()</a></code></p></div> +    <div class='dont-index'><p><code><a href='nlme_function.html'>nlme_function()</a></code>, <a href='plot.mixed.mmkin.html'>plot.mixed.mmkin</a>, <a href='summary.nlme.mmkin.html'>summary.nlme.mmkin</a>, +parms.nlme.mmkin</p></div>      <h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2>      <pre class="examples"><div class='input'><span class='va'>ds</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/base/lapply.html'>lapply</a></span><span class='op'>(</span><span class='va'>experimental_data_for_UBA_2019</span><span class='op'>[</span><span class='fl'>6</span><span class='op'>:</span><span class='fl'>10</span><span class='op'>]</span>, @@ -288,21 +289,21 @@ methods that will automatically work on 'nlme.mmkin' objects, such as  #> Log-likelihood: -238.5635  #>   #> Fixed effects: -#>  list(parent_0 ~ 1, log_k1 ~ 1, log_k2 ~ 1, g_ilr ~ 1)  -#>    parent_0      log_k1      log_k2       g_ilr  -#> 94.17015133 -1.80015306 -4.14738870  0.02290935  +#>  list(parent_0 ~ 1, log_k1 ~ 1, log_k2 ~ 1, g_qlogis ~ 1)  +#>    parent_0      log_k1      log_k2    g_qlogis  +#> 94.17015185 -1.80015278 -4.14738834  0.03239833   #>   #> Random effects: -#>  Formula: list(parent_0 ~ 1, log_k1 ~ 1, log_k2 ~ 1, g_ilr ~ 1) +#>  Formula: list(parent_0 ~ 1, log_k1 ~ 1, log_k2 ~ 1, g_qlogis ~ 1)  #>  Level: ds  #>  Structure: Diagonal -#>         parent_0    log_k1  log_k2     g_ilr Residual -#> StdDev: 2.488249 0.8447273 1.32965 0.3289311 2.321364 +#>         parent_0    log_k1  log_k2  g_qlogis Residual +#> StdDev: 2.488249 0.8447275 1.32965 0.4651789 2.321364  #> </div><div class='input'><span class='fu'><a href='https://rdrr.io/r/graphics/plot.default.html'>plot</a></span><span class='op'>(</span><span class='va'>f_nlme_dfop</span><span class='op'>)</span>  </div><div class='img'><img src='nlme.mmkin-1.png' alt='' width='700' height='433' /></div><div class='input'><span class='fu'><a href='endpoints.html'>endpoints</a></span><span class='op'>(</span><span class='va'>f_nlme_dfop</span><span class='op'>)</span>  </div><div class='output co'>#> $distimes  #>            DT50     DT90 DT50back  DT50_k1  DT50_k2 -#> parent 10.79857 100.7937 30.34193 4.193938 43.85443 +#> parent 10.79857 100.7937 30.34192 4.193937 43.85442  #> </div><div class='input'>  <span class='co'># \dontrun{</span>    <span class='va'>f_nlme_2</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span><span class='op'>(</span><span class='va'>f</span><span class='op'>[</span><span class='st'>"SFO"</span>, <span class='op'>]</span>, start <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span>parent_0 <span class='op'>=</span> <span class='fl'>100</span>, log_k_parent <span class='op'>=</span> <span class='fl'>0.1</span><span class='op'>)</span><span class='op'>)</span> @@ -353,35 +354,35 @@ methods that will automatically work on 'nlme.mmkin' objects, such as      control <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span>pnlsMaxIter <span class='op'>=</span> <span class='fl'>120</span>, tolerance <span class='op'>=</span> <span class='fl'>5e-4</span><span class='op'>)</span>, verbose <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>  </div><div class='output co'>#>   #> **Iteration 1 -#> LME step: Loglik: -404.9582, nlminb iterations: 1 +#> LME step: Loglik: -404.9583, nlminb iterations: 1  #> reStruct  parameters:  #>        ds1        ds2        ds3        ds4        ds5        ds6  -#> -0.4114355  0.9798697  1.6990037  0.7293315  0.3354323  1.7113046  +#> -0.4114356  0.9798646  1.3524300  0.7293315  0.3354323  1.3647313   #>  Beginning PNLS step: ..  completed fit_nlme() step. -#> PNLS step: RSS =  630.3644  -#>  fixed effects: 93.82269  -5.455991  -0.6788957  -1.862196  -4.199671  0.05532828   +#> PNLS step: RSS =  630.3633  +#>  fixed effects: 93.82269  -5.455993  -0.9601037  -1.862196  -4.199671  0.07824609    #>  iterations: 120   #> Convergence crit. (must all become <= tolerance = 0.0005):  #>     fixed  reStruct  -#> 0.7885368 0.5822683  +#> 0.7897284 0.5822782   #>   #> **Iteration 2  #> LME step: Loglik: -407.7755, nlminb iterations: 11  #> reStruct  parameters: -#>          ds1          ds2          ds3          ds4          ds5          ds6  -#> -0.371224133  0.003056179  1.789939402  0.724671158  0.301602977  1.754200729  +#>         ds1         ds2         ds3         ds4         ds5         ds6  +#> -0.37122411  0.00305562  1.44336560  0.72467122  0.30160310  1.40762692   #>  Beginning PNLS step: ..  completed fit_nlme() step. -#> PNLS step: RSS =  630.3633  -#>  fixed effects: 93.82269  -5.455992  -0.6788958  -1.862196  -4.199671  0.05532831   +#> PNLS step: RSS =  630.3637  +#>  fixed effects: 93.82269  -5.455992  -0.9601036  -1.862196  -4.199671  0.0782462    #>  iterations: 120   #> Convergence crit. (must all become <= tolerance = 0.0005):  #>        fixed     reStruct  -#> 4.789774e-07 2.200661e-05 </div><div class='input'> +#> 1.375673e-06 9.758294e-06 </div><div class='input'>    <span class='fu'><a href='https://rdrr.io/r/graphics/plot.default.html'>plot</a></span><span class='op'>(</span><span class='va'>f_nlme_dfop_sfo</span><span class='op'>)</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/stats/anova.html'>anova</a></span><span class='op'>(</span><span class='va'>f_nlme_dfop_sfo</span>, <span class='va'>f_nlme_sfo_sfo</span><span class='op'>)</span>  </div><div class='output co'>#>                 Model df       AIC       BIC    logLik   Test  L.Ratio p-value -#> f_nlme_dfop_sfo     1 13  843.8547  884.6201 -408.9273                         +#> f_nlme_dfop_sfo     1 13  843.8547  884.6201 -408.9274                          #> f_nlme_sfo_sfo      2  9 1085.1821 1113.4043 -533.5910 1 vs 2 249.3274  <.0001</div><div class='input'>    <span class='fu'><a href='endpoints.html'>endpoints</a></span><span class='op'>(</span><span class='va'>f_nlme_sfo_sfo</span><span class='op'>)</span>  </div><div class='output co'>#> $ff @@ -400,7 +401,7 @@ methods that will automatically work on 'nlme.mmkin' objects, such as  #> $distimes  #>             DT50     DT90 DT50back  DT50_k1  DT50_k2  #> parent  11.07091 104.6320 31.49738 4.462384 46.20825 -#> A1     162.30536 539.1667       NA       NA       NA +#> A1     162.30523 539.1663       NA       NA       NA  #> </div><div class='input'>    <span class='kw'>if</span> <span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/length.html'>length</a></span><span class='op'>(</span><span class='fu'>findFunction</span><span class='op'>(</span><span class='st'>"varConstProp"</span><span class='op'>)</span><span class='op'>)</span> <span class='op'>></span> <span class='fl'>0</span><span class='op'>)</span> <span class='op'>{</span> <span class='co'># tc error model for nlme available</span>      <span class='co'># Attempts to fit metabolite kinetics with the tc error model are possible,</span> @@ -425,23 +426,23 @@ methods that will automatically work on 'nlme.mmkin' objects, such as  #> Log-likelihood: -238.4298  #>   #> Fixed effects: -#>  list(parent_0 ~ 1, log_k1 ~ 1, log_k2 ~ 1, g_ilr ~ 1)  -#>    parent_0      log_k1      log_k2       g_ilr  -#> 94.04774463 -1.82339924 -4.16715509  0.04020161  +#>  list(parent_0 ~ 1, log_k1 ~ 1, log_k2 ~ 1, g_qlogis ~ 1)  +#>    parent_0      log_k1      log_k2    g_qlogis  +#> 94.04774566 -1.82339808 -4.16715311  0.05685186   #>   #> Random effects: -#>  Formula: list(parent_0 ~ 1, log_k1 ~ 1, log_k2 ~ 1, g_ilr ~ 1) +#>  Formula: list(parent_0 ~ 1, log_k1 ~ 1, log_k2 ~ 1, g_qlogis ~ 1)  #>  Level: ds  #>  Structure: Diagonal -#>         parent_0    log_k1   log_k2     g_ilr Residual -#> StdDev: 2.473883 0.8499901 1.337187 0.3294411        1 +#>         parent_0    log_k1   log_k2  g_qlogis Residual +#> StdDev: 2.473881 0.8499884 1.337185 0.4659005        1  #>   #> Variance function:  #>  Structure: Constant plus proportion of variance covariate  #>  Formula: ~fitted(.)   #>  Parameter estimates:  #>      const       prop  -#> 2.23222625 0.01262414 </div><div class='input'> +#> 2.23224114 0.01262341 </div><div class='input'>    <span class='va'>f_2_obs</span> <span class='op'><-</span> <span class='fu'><a href='mmkin.html'>mmkin</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span><span class='st'>"SFO-SFO"</span> <span class='op'>=</span> <span class='va'>m_sfo_sfo</span>,     <span class='st'>"DFOP-SFO"</span> <span class='op'>=</span> <span class='va'>m_dfop_sfo</span><span class='op'>)</span>,      <span class='va'>ds_2</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span>, error_model <span class='op'>=</span> <span class='st'>"obs"</span><span class='op'>)</span> diff --git a/docs/dev/reference/plot.mixed.mmkin-1.png b/docs/dev/reference/plot.mixed.mmkin-1.pngBinary files differ new file mode 100644 index 00000000..5cb33214 --- /dev/null +++ b/docs/dev/reference/plot.mixed.mmkin-1.png diff --git a/docs/dev/reference/plot.mixed.mmkin-2.png b/docs/dev/reference/plot.mixed.mmkin-2.pngBinary files differ new file mode 100644 index 00000000..c0d67204 --- /dev/null +++ b/docs/dev/reference/plot.mixed.mmkin-2.png diff --git a/docs/dev/reference/plot.mixed.mmkin-3.png b/docs/dev/reference/plot.mixed.mmkin-3.pngBinary files differ new file mode 100644 index 00000000..67058e6c --- /dev/null +++ b/docs/dev/reference/plot.mixed.mmkin-3.png diff --git a/docs/dev/reference/plot.mixed.mmkin.html b/docs/dev/reference/plot.mixed.mmkin.html new file mode 100644 index 00000000..4108aea3 --- /dev/null +++ b/docs/dev/reference/plot.mixed.mmkin.html @@ -0,0 +1,313 @@ +<!-- Generated by pkgdown: do not edit by hand --> +<!DOCTYPE html> +<html lang="en"> +  <head> +  <meta charset="utf-8"> +<meta http-equiv="X-UA-Compatible" content="IE=edge"> +<meta name="viewport" content="width=device-width, initial-scale=1.0"> + +<title>Plot predictions from a fitted nonlinear mixed model obtained via an mmkin row object — plot.mixed.mmkin • mkin</title> + + +<!-- jquery --> +<script src="https://cdnjs.cloudflare.com/ajax/libs/jquery/3.4.1/jquery.min.js" integrity="sha256-CSXorXvZcTkaix6Yvo6HppcZGetbYMGWSFlBw8HfCJo=" crossorigin="anonymous"></script> +<!-- Bootstrap --> + +<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.4.1/css/bootstrap.min.css" integrity="sha256-bZLfwXAP04zRMK2BjiO8iu9pf4FbLqX6zitd+tIvLhE=" crossorigin="anonymous" /> + +<script src="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.4.1/js/bootstrap.min.js" integrity="sha256-nuL8/2cJ5NDSSwnKD8VqreErSWHtnEP9E7AySL+1ev4=" crossorigin="anonymous"></script> + +<!-- bootstrap-toc --> +<link rel="stylesheet" href="../bootstrap-toc.css"> +<script src="../bootstrap-toc.js"></script> + +<!-- Font Awesome icons --> +<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/all.min.css" integrity="sha256-mmgLkCYLUQbXn0B1SRqzHar6dCnv9oZFPEC1g1cwlkk=" crossorigin="anonymous" /> +<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/v4-shims.min.css" integrity="sha256-wZjR52fzng1pJHwx4aV2AO3yyTOXrcDW7jBpJtTwVxw=" crossorigin="anonymous" /> + +<!-- clipboard.js --> +<script src="https://cdnjs.cloudflare.com/ajax/libs/clipboard.js/2.0.6/clipboard.min.js" integrity="sha256-inc5kl9MA1hkeYUt+EC3BhlIgyp/2jDIyBLS6k3UxPI=" crossorigin="anonymous"></script> + +<!-- headroom.js --> +<script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/headroom.min.js" integrity="sha256-AsUX4SJE1+yuDu5+mAVzJbuYNPHj/WroHuZ8Ir/CkE0=" crossorigin="anonymous"></script> +<script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/jQuery.headroom.min.js" integrity="sha256-ZX/yNShbjqsohH1k95liqY9Gd8uOiE1S4vZc+9KQ1K4=" crossorigin="anonymous"></script> + +<!-- pkgdown --> +<link href="../pkgdown.css" rel="stylesheet"> +<script src="../pkgdown.js"></script> + + + + +<meta property="og:title" content="Plot predictions from a fitted nonlinear mixed model obtained via an mmkin row object — plot.mixed.mmkin" /> +<meta property="og:description" content="Plot predictions from a fitted nonlinear mixed model obtained via an mmkin row object" /> + + +<meta name="robots" content="noindex"> + +<!-- mathjax --> +<script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script> +<script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script> + +<!--[if lt IE 9]> +<script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> +<script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> +<![endif]--> + + + +  </head> + +  <body data-spy="scroll" data-target="#toc"> +    <div class="container template-reference-topic"> +      <header> +      <div class="navbar navbar-default navbar-fixed-top" role="navigation"> +  <div class="container"> +    <div class="navbar-header"> +      <button type="button" class="navbar-toggle collapsed" data-toggle="collapse" data-target="#navbar" aria-expanded="false"> +        <span class="sr-only">Toggle navigation</span> +        <span class="icon-bar"></span> +        <span class="icon-bar"></span> +        <span class="icon-bar"></span> +      </button> +      <span class="navbar-brand"> +        <a class="navbar-link" href="../index.html">mkin</a> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +      </span> +    </div> + +    <div id="navbar" class="navbar-collapse collapse"> +      <ul class="nav navbar-nav"> +        <li> +  <a href="../reference/index.html">Functions and data</a> +</li> +<li class="dropdown"> +  <a href="#" class="dropdown-toggle" data-toggle="dropdown" role="button" aria-expanded="false"> +    Articles +      +    <span class="caret"></span> +  </a> +  <ul class="dropdown-menu" role="menu"> +    <li> +      <a href="../articles/mkin.html">Introduction to mkin</a> +    </li> +    <li> +      <a href="../articles/FOCUS_D.html">Example evaluation of FOCUS Example Dataset D</a> +    </li> +    <li> +      <a href="../articles/FOCUS_L.html">Example evaluation of FOCUS Laboratory Data L1 to L3</a> +    </li> +    <li> +      <a href="../articles/web_only/FOCUS_Z.html">Example evaluation of FOCUS Example Dataset Z</a> +    </li> +    <li> +      <a href="../articles/web_only/compiled_models.html">Performance benefit by using compiled model definitions in mkin</a> +    </li> +    <li> +      <a href="../articles/twa.html">Calculation of time weighted average concentrations with mkin</a> +    </li> +    <li> +      <a href="../articles/web_only/NAFTA_examples.html">Example evaluation of NAFTA SOP Attachment examples</a> +    </li> +    <li> +      <a href="../articles/web_only/benchmarks.html">Some benchmark timings</a> +    </li> +  </ul> +</li> +<li> +  <a href="../news/index.html">News</a> +</li> +      </ul> +      <ul class="nav navbar-nav navbar-right"> +        <li> +  <a href="https://github.com/jranke/mkin/"> +    <span class="fab fa fab fa-github fa-lg"></span> +      +  </a> +</li> +      </ul> +       +    </div><!--/.nav-collapse --> +  </div><!--/.container --> +</div><!--/.navbar --> + +       + +      </header> + +<div class="row"> +  <div class="col-md-9 contents"> +    <div class="page-header"> +    <h1>Plot predictions from a fitted nonlinear mixed model obtained via an mmkin row object</h1> +    <small class="dont-index">Source: <a href='https://github.com/jranke/mkin/blob/master/R/plot.mixed.mmkin.R'><code>R/plot.mixed.mmkin.R</code></a></small> +    <div class="hidden name"><code>plot.mixed.mmkin.Rd</code></div> +    </div> + +    <div class="ref-description"> +    <p>Plot predictions from a fitted nonlinear mixed model obtained via an mmkin row object</p> +    </div> + +    <pre class="usage"><span class='co'># S3 method for mixed.mmkin</span> +<span class='fu'><a href='https://rdrr.io/r/graphics/plot.default.html'>plot</a></span><span class='op'>(</span> +  <span class='va'>x</span>, +  i <span class='op'>=</span> <span class='fl'>1</span><span class='op'>:</span><span class='fu'><a href='https://rdrr.io/r/base/nrow.html'>ncol</a></span><span class='op'>(</span><span class='va'>x</span><span class='op'>$</span><span class='va'>mmkin</span><span class='op'>)</span>, +  obs_vars <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/names.html'>names</a></span><span class='op'>(</span><span class='va'>x</span><span class='op'>$</span><span class='va'>mkinmod</span><span class='op'>$</span><span class='va'>map</span><span class='op'>)</span>, +  standardized <span class='op'>=</span> <span class='cn'>TRUE</span>, +  xlab <span class='op'>=</span> <span class='st'>"Time"</span>, +  xlim <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/range.html'>range</a></span><span class='op'>(</span><span class='va'>x</span><span class='op'>$</span><span class='va'>data</span><span class='op'>$</span><span class='va'>time</span><span class='op'>)</span>, +  resplot <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='st'>"predicted"</span>, <span class='st'>"time"</span><span class='op'>)</span>, +  ymax <span class='op'>=</span> <span class='st'>"auto"</span>, +  maxabs <span class='op'>=</span> <span class='st'>"auto"</span>, +  ncol.legend <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/ifelse.html'>ifelse</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/length.html'>length</a></span><span class='op'>(</span><span class='va'>i</span><span class='op'>)</span> <span class='op'><=</span> <span class='fl'>3</span>, <span class='fu'><a href='https://rdrr.io/r/base/length.html'>length</a></span><span class='op'>(</span><span class='va'>i</span><span class='op'>)</span> <span class='op'>+</span> <span class='fl'>1</span>, <span class='fu'><a href='https://rdrr.io/r/base/ifelse.html'>ifelse</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/length.html'>length</a></span><span class='op'>(</span><span class='va'>i</span><span class='op'>)</span> <span class='op'><=</span> <span class='fl'>8</span>, <span class='fl'>3</span>, <span class='fl'>4</span><span class='op'>)</span><span class='op'>)</span>, +  nrow.legend <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/Round.html'>ceiling</a></span><span class='op'>(</span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/length.html'>length</a></span><span class='op'>(</span><span class='va'>i</span><span class='op'>)</span> <span class='op'>+</span> <span class='fl'>1</span><span class='op'>)</span><span class='op'>/</span><span class='va'>ncol.legend</span><span class='op'>)</span>, +  rel.height.legend <span class='op'>=</span> <span class='fl'>0.03</span> <span class='op'>+</span> <span class='fl'>0.08</span> <span class='op'>*</span> <span class='va'>nrow.legend</span>, +  rel.height.bottom <span class='op'>=</span> <span class='fl'>1.1</span>, +  pch_ds <span class='op'>=</span> <span class='fl'>1</span><span class='op'>:</span><span class='fu'><a href='https://rdrr.io/r/base/length.html'>length</a></span><span class='op'>(</span><span class='va'>i</span><span class='op'>)</span>, +  col_ds <span class='op'>=</span> <span class='va'>pch_ds</span> <span class='op'>+</span> <span class='fl'>1</span>, +  lty_ds <span class='op'>=</span> <span class='va'>col_ds</span>, +  frame <span class='op'>=</span> <span class='cn'>TRUE</span>, +  <span class='va'>...</span> +<span class='op'>)</span></pre> + +    <h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2> +    <table class="ref-arguments"> +    <colgroup><col class="name" /><col class="desc" /></colgroup> +    <tr> +      <th>x</th> +      <td><p>An object of class <a href='saem.html'>saem.mmkin</a> or <a href='nlme.mmkin.html'>nlme.mmkin</a></p></td> +    </tr> +    <tr> +      <th>i</th> +      <td><p>A numeric index to select datasets for which to plot the individual predictions, +in case plots get too large</p></td> +    </tr> +    <tr> +      <th>obs_vars</th> +      <td><p>A character vector of names of the observed variables for +which the data and the model should be plotted. Defauls to all observed +variables in the model.</p></td> +    </tr> +    <tr> +      <th>standardized</th> +      <td><p>Should the residuals be standardized? Only takes effect if +<code>resplot = "time"</code>.</p></td> +    </tr> +    <tr> +      <th>xlab</th> +      <td><p>Label for the x axis.</p></td> +    </tr> +    <tr> +      <th>xlim</th> +      <td><p>Plot range in x direction.</p></td> +    </tr> +    <tr> +      <th>resplot</th> +      <td><p>Should the residuals plotted against time or against +predicted values?</p></td> +    </tr> +    <tr> +      <th>ymax</th> +      <td><p>Vector of maximum y axis values</p></td> +    </tr> +    <tr> +      <th>maxabs</th> +      <td><p>Maximum absolute value of the residuals. This is used for the +scaling of the y axis and defaults to "auto".</p></td> +    </tr> +    <tr> +      <th>ncol.legend</th> +      <td><p>Number of columns to use in the legend</p></td> +    </tr> +    <tr> +      <th>nrow.legend</th> +      <td><p>Number of rows to use in the legend</p></td> +    </tr> +    <tr> +      <th>rel.height.legend</th> +      <td><p>The relative height of the legend shown on top</p></td> +    </tr> +    <tr> +      <th>rel.height.bottom</th> +      <td><p>The relative height of the bottom plot row</p></td> +    </tr> +    <tr> +      <th>pch_ds</th> +      <td><p>Symbols to be used for plotting the data.</p></td> +    </tr> +    <tr> +      <th>col_ds</th> +      <td><p>Colors used for plotting the observed data and the +corresponding model prediction lines for the different datasets.</p></td> +    </tr> +    <tr> +      <th>lty_ds</th> +      <td><p>Line types to be used for the model predictions.</p></td> +    </tr> +    <tr> +      <th>frame</th> +      <td><p>Should a frame be drawn around the plots?</p></td> +    </tr> +    <tr> +      <th>...</th> +      <td><p>Further arguments passed to <code><a href='https://rdrr.io/r/graphics/plot.default.html'>plot</a></code>.</p></td> +    </tr> +    </table> + +    <h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2> + +    <p>The function is called for its side effect.</p> +    <h2 class="hasAnchor" id="author"><a class="anchor" href="#author"></a>Author</h2> + +    <p>Johannes Ranke</p> + +    <h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2> +    <pre class="examples"><div class='input'><span class='va'>ds</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/base/lapply.html'>lapply</a></span><span class='op'>(</span><span class='va'>experimental_data_for_UBA_2019</span><span class='op'>[</span><span class='fl'>6</span><span class='op'>:</span><span class='fl'>10</span><span class='op'>]</span>, + <span class='kw'>function</span><span class='op'>(</span><span class='va'>x</span><span class='op'>)</span> <span class='va'>x</span><span class='op'>$</span><span class='va'>data</span><span class='op'>[</span><span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='st'>"name"</span>, <span class='st'>"time"</span>, <span class='st'>"value"</span><span class='op'>)</span><span class='op'>]</span><span class='op'>)</span> +<span class='fu'><a href='https://rdrr.io/r/base/names.html'>names</a></span><span class='op'>(</span><span class='va'>ds</span><span class='op'>)</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/base/paste.html'>paste0</a></span><span class='op'>(</span><span class='st'>"ds "</span>, <span class='fl'>6</span><span class='op'>:</span><span class='fl'>10</span><span class='op'>)</span> +<span class='va'>dfop_sfo</span> <span class='op'><-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span><span class='op'>(</span>parent <span class='op'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span><span class='op'>(</span><span class='st'>"DFOP"</span>, <span class='st'>"A1"</span><span class='op'>)</span>, +  A1 <span class='op'>=</span> <span class='fu'><a href='mkinsub.html'>mkinsub</a></span><span class='op'>(</span><span class='st'>"SFO"</span><span class='op'>)</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> +<span class='co'># \dontrun{</span> +<span class='va'>f</span> <span class='op'><-</span> <span class='fu'><a href='mmkin.html'>mmkin</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span><span class='st'>"DFOP-SFO"</span> <span class='op'>=</span> <span class='va'>dfop_sfo</span><span class='op'>)</span>, <span class='va'>ds</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> +<span class='fu'><a href='https://rdrr.io/r/graphics/plot.default.html'>plot</a></span><span class='op'>(</span><span class='va'>f</span><span class='op'>[</span>, <span class='fl'>3</span><span class='op'>:</span><span class='fl'>4</span><span class='op'>]</span>, standardized <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> +</div><div class='img'><img src='plot.mixed.mmkin-1.png' alt='' width='700' height='433' /></div><div class='input'> +<span class='co'># For this fit we need to increase pnlsMaxiter, and we increase the</span> +<span class='co'># tolerance in order to speed up the fit for this example evaluation</span> +<span class='va'>f_nlme</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span><span class='op'>(</span><span class='va'>f</span>, control <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span>pnlsMaxIter <span class='op'>=</span> <span class='fl'>120</span>, tolerance <span class='op'>=</span> <span class='fl'>1e-3</span><span class='op'>)</span><span class='op'>)</span> +<span class='fu'><a href='https://rdrr.io/r/graphics/plot.default.html'>plot</a></span><span class='op'>(</span><span class='va'>f_nlme</span><span class='op'>)</span> +</div><div class='img'><img src='plot.mixed.mmkin-2.png' alt='' width='700' height='433' /></div><div class='input'> +<span class='va'>f_saem</span> <span class='op'><-</span> <span class='fu'><a href='saem.html'>saem</a></span><span class='op'>(</span><span class='va'>f</span><span class='op'>)</span> +</div><div class='output co'>#> Running main SAEM algorithm +#> [1] "Mon Nov  9 17:18:17 2020" +#> .... +#>     Minimisation finished +#> [1] "Mon Nov  9 17:18:26 2020"</div><div class='input'><span class='fu'><a href='https://rdrr.io/r/graphics/plot.default.html'>plot</a></span><span class='op'>(</span><span class='va'>f_saem</span><span class='op'>)</span> +</div><div class='img'><img src='plot.mixed.mmkin-3.png' alt='' width='700' height='433' /></div><div class='input'><span class='co'># }</span> +</div></pre> +  </div> +  <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> +    <nav id="toc" data-toggle="toc" class="sticky-top"> +      <h2 data-toc-skip>Contents</h2> +    </nav> +  </div> +</div> + + +      <footer> +      <div class="copyright"> +  <p>Developed by Johannes Ranke.</p> +</div> + +<div class="pkgdown"> +  <p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.6.1.</p> +</div> + +      </footer> +   </div> + +   + + +  </body> +</html> + + diff --git a/docs/dev/reference/saem.html b/docs/dev/reference/saem.html index 26f4c3e3..f1b4c421 100644 --- a/docs/dev/reference/saem.html +++ b/docs/dev/reference/saem.html @@ -206,7 +206,8 @@ by the saemix function?</p></td>      <h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2>      <p>An S3 object of class 'saem.mmkin', containing the fitted -<a href='https://rdrr.io/pkg/saemix/man/SaemixObject-class.html'>saemix::SaemixObject</a> as a list component named 'so'.</p> +<a href='https://rdrr.io/pkg/saemix/man/SaemixObject-class.html'>saemix::SaemixObject</a> as a list component named 'so'. The +object also inherits from 'mixed.mmkin'.</p>  <p>An <a href='https://rdrr.io/pkg/saemix/man/SaemixModel-class.html'>saemix::SaemixModel</a> object.</p>  <p>An <a href='https://rdrr.io/pkg/saemix/man/SaemixData-class.html'>saemix::SaemixData</a> object.</p>      <h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2> @@ -218,7 +219,7 @@ psi0 of <code><a href='https://rdrr.io/pkg/saemix/man/saemixModel.html'>saemix::  using <a href='mmkin.html'>mmkin</a>.</p>      <h2 class="hasAnchor" id="see-also"><a class="anchor" href="#see-also"></a>See also</h2> -    <div class='dont-index'><p><a href='summary.saem.mmkin.html'>summary.saem.mmkin</a></p></div> +    <div class='dont-index'><p><a href='summary.saem.mmkin.html'>summary.saem.mmkin</a> <a href='plot.mixed.mmkin.html'>plot.mixed.mmkin</a></p></div>      <h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2>      <pre class="examples"><div class='input'><span class='co'># \dontrun{</span> @@ -229,27 +230,27 @@ using <a href='mmkin.html'>mmkin</a>.</p>    state.ini <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span>parent <span class='op'>=</span> <span class='fl'>100</span><span class='op'>)</span>, fixed_initials <span class='op'>=</span> <span class='st'>"parent"</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>  <span class='va'>f_saem_p0_fixed</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent_p0_fixed</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Nov  9 09:03:11 2020" +#> [1] "Mon Nov  9 17:18:28 2020"  #> ....  #>     Minimisation finished -#> [1] "Mon Nov  9 09:03:13 2020"</div><div class='input'> +#> [1] "Mon Nov  9 17:18:30 2020"</div><div class='input'>  <span class='va'>f_mmkin_parent</span> <span class='op'><-</span> <span class='fu'><a href='mmkin.html'>mmkin</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='st'>"SFO"</span>, <span class='st'>"FOMC"</span>, <span class='st'>"DFOP"</span><span class='op'>)</span>, <span class='va'>ds</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>  <span class='va'>f_saem_sfo</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent</span><span class='op'>[</span><span class='st'>"SFO"</span>, <span class='op'>]</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Nov  9 09:03:14 2020" +#> [1] "Mon Nov  9 17:18:31 2020"  #> ....  #>     Minimisation finished -#> [1] "Mon Nov  9 09:03:16 2020"</div><div class='input'><span class='va'>f_saem_fomc</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent</span><span class='op'>[</span><span class='st'>"FOMC"</span>, <span class='op'>]</span><span class='op'>)</span> +#> [1] "Mon Nov  9 17:18:33 2020"</div><div class='input'><span class='va'>f_saem_fomc</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent</span><span class='op'>[</span><span class='st'>"FOMC"</span>, <span class='op'>]</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Nov  9 09:03:16 2020" +#> [1] "Mon Nov  9 17:18:33 2020"  #> ....  #>     Minimisation finished -#> [1] "Mon Nov  9 09:03:18 2020"</div><div class='input'><span class='va'>f_saem_dfop</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent</span><span class='op'>[</span><span class='st'>"DFOP"</span>, <span class='op'>]</span><span class='op'>)</span> +#> [1] "Mon Nov  9 17:18:35 2020"</div><div class='input'><span class='va'>f_saem_dfop</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent</span><span class='op'>[</span><span class='st'>"DFOP"</span>, <span class='op'>]</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Nov  9 09:03:19 2020" +#> [1] "Mon Nov  9 17:18:36 2020"  #> ....  #>     Minimisation finished -#> [1] "Mon Nov  9 09:03:22 2020"</div><div class='input'> +#> [1] "Mon Nov  9 17:18:39 2020"</div><div class='input'>  <span class='co'># The returned saem.mmkin object contains an SaemixObject, therefore we can use</span>  <span class='co'># functions from saemix</span>  <span class='kw'><a href='https://rdrr.io/r/base/library.html'>library</a></span><span class='op'>(</span><span class='va'>saemix</span><span class='op'>)</span> @@ -295,10 +296,10 @@ using <a href='mmkin.html'>mmkin</a>.</p>  <span class='va'>f_mmkin_parent_tc</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/update.html'>update</a></span><span class='op'>(</span><span class='va'>f_mmkin_parent</span>, error_model <span class='op'>=</span> <span class='st'>"tc"</span><span class='op'>)</span>  <span class='va'>f_saem_fomc_tc</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent_tc</span><span class='op'>[</span><span class='st'>"FOMC"</span>, <span class='op'>]</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Nov  9 09:03:24 2020" +#> [1] "Mon Nov  9 17:18:41 2020"  #> ....  #>     Minimisation finished -#> [1] "Mon Nov  9 09:03:29 2020"</div><div class='input'><span class='fu'><a href='https://rdrr.io/pkg/saemix/man/compare.saemix.html'>compare.saemix</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span><span class='va'>f_saem_fomc</span><span class='op'>$</span><span class='va'>so</span>, <span class='va'>f_saem_fomc_tc</span><span class='op'>$</span><span class='va'>so</span><span class='op'>)</span><span class='op'>)</span> +#> [1] "Mon Nov  9 17:18:46 2020"</div><div class='input'><span class='fu'><a href='https://rdrr.io/pkg/saemix/man/compare.saemix.html'>compare.saemix</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span><span class='va'>f_saem_fomc</span><span class='op'>$</span><span class='va'>so</span>, <span class='va'>f_saem_fomc_tc</span><span class='op'>$</span><span class='va'>so</span><span class='op'>)</span><span class='op'>)</span>  </div><div class='output co'>#> Likelihoods computed by importance sampling </div><div class='output co'>#>        AIC      BIC  #> 1 467.7644 465.0305  #> 2 469.4862 466.3617</div><div class='input'> @@ -318,20 +319,20 @@ using <a href='mmkin.html'>mmkin</a>.</p>  <span class='co'># solutions written for mkin this took around four minutes</span>  <span class='va'>f_saem_sfo_sfo</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin</span><span class='op'>[</span><span class='st'>"SFO-SFO"</span>, <span class='op'>]</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Nov  9 09:03:31 2020" +#> [1] "Mon Nov  9 17:18:48 2020"  #> ....  #>     Minimisation finished -#> [1] "Mon Nov  9 09:03:36 2020"</div><div class='input'><span class='va'>f_saem_dfop_sfo</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin</span><span class='op'>[</span><span class='st'>"DFOP-SFO"</span>, <span class='op'>]</span><span class='op'>)</span> +#> [1] "Mon Nov  9 17:18:53 2020"</div><div class='input'><span class='va'>f_saem_dfop_sfo</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin</span><span class='op'>[</span><span class='st'>"DFOP-SFO"</span>, <span class='op'>]</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Nov  9 09:03:37 2020" +#> [1] "Mon Nov  9 17:18:54 2020"  #> ....  #>     Minimisation finished -#> [1] "Mon Nov  9 09:03:46 2020"</div><div class='input'><span class='fu'><a href='https://rdrr.io/pkg/saemix/man/summary-methods.html'>summary</a></span><span class='op'>(</span><span class='va'>f_saem_dfop_sfo</span>, data <span class='op'>=</span> <span class='cn'>FALSE</span><span class='op'>)</span> +#> [1] "Mon Nov  9 17:19:03 2020"</div><div class='input'><span class='fu'><a href='https://rdrr.io/pkg/saemix/man/summary-methods.html'>summary</a></span><span class='op'>(</span><span class='va'>f_saem_dfop_sfo</span>, data <span class='op'>=</span> <span class='cn'>FALSE</span><span class='op'>)</span>  </div><div class='output co'>#> saemix version used for fitting:      3.1.9000   #> mkin version used for pre-fitting:  0.9.50.4   #> R version used for fitting:         4.0.3  -#> Date of fit:     Mon Nov  9 09:03:47 2020  -#> Date of summary: Mon Nov  9 09:03:47 2020  +#> Date of fit:     Mon Nov  9 17:19:04 2020  +#> Date of summary: Mon Nov  9 17:19:04 2020   #>   #> Equations:  #> d_parent/dt = - ((k1 * g * exp(-k1 * time) + k2 * (1 - g) * exp(-k2 * @@ -346,7 +347,7 @@ using <a href='mmkin.html'>mmkin</a>.</p>  #>   #> Model predictions using solution type analytical   #>  -#> Fitted in 9.758 s using 300, 100 iterations +#> Fitted in 9.941 s using 300, 100 iterations  #>   #> Variance model: Constant variance   #>  diff --git a/docs/dev/sitemap.xml b/docs/dev/sitemap.xml index 5cfca07a..02fca7f9 100644 --- a/docs/dev/sitemap.xml +++ b/docs/dev/sitemap.xml @@ -148,6 +148,9 @@      <loc>https://pkgdown.jrwb.de/mkin/reference/parms.html</loc>    </url>    <url> +    <loc>https://pkgdown.jrwb.de/mkin/reference/plot.mixed.mmkin.html</loc> +  </url> +  <url>      <loc>https://pkgdown.jrwb.de/mkin/reference/plot.mkinfit.html</loc>    </url>    <url> @@ -157,9 +160,6 @@      <loc>https://pkgdown.jrwb.de/mkin/reference/plot.nafta.html</loc>    </url>    <url> -    <loc>https://pkgdown.jrwb.de/mkin/reference/plot_mixed.html</loc> -  </url> -  <url>      <loc>https://pkgdown.jrwb.de/mkin/reference/print.mkinds.html</loc>    </url>    <url> diff --git a/man/nlme.mmkin.Rd b/man/nlme.mmkin.Rd index 85bd74f6..9526a427 100644 --- a/man/nlme.mmkin.Rd +++ b/man/nlme.mmkin.Rd @@ -66,8 +66,8 @@ parameters taken from the mmkin object are used}  \item{object}{An nlme.mmkin object to update}  }  \value{ -Upon success, a fitted nlme.mmkin object, which is an nlme object -with additional elements +Upon success, a fitted 'nlme.mmkin' object, which is an nlme object +with additional elements. It also inherits from 'mixed.mmkin'.  }  \description{  This functions sets up a nonlinear mixed effects model for an mmkin row @@ -150,5 +150,6 @@ endpoints(f_nlme_dfop)  }  }  \seealso{ -\code{\link[=nlme_function]{nlme_function()}} +\code{\link[=nlme_function]{nlme_function()}}, \link{plot.mixed.mmkin}, \link{summary.nlme.mmkin}, +\link{parms.nlme.mmkin}  } diff --git a/man/plot_mixed.Rd b/man/plot.mixed.mmkin.Rd index d3cee7c9..66e79f09 100644 --- a/man/plot_mixed.Rd +++ b/man/plot.mixed.mmkin.Rd @@ -1,33 +1,10 @@  % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/plot_mixed.R -\name{plot_mixed} -\alias{plot_mixed} -\alias{plot.saem.mmkin} -\alias{plot.nlme.mmkin} +% Please edit documentation in R/plot.mixed.mmkin.R +\name{plot.mixed.mmkin} +\alias{plot.mixed.mmkin}  \title{Plot predictions from a fitted nonlinear mixed model obtained via an mmkin row object}  \usage{ -\method{plot}{saem.mmkin}( -  x, -  i = 1:ncol(x$mmkin), -  obs_vars = names(x$mkinmod$map), -  standardized = TRUE, -  xlab = "Time", -  xlim = range(x$data$time), -  resplot = c("predicted", "time"), -  ymax = "auto", -  maxabs = "auto", -  ncol.legend = ifelse(length(i) <= 3, length(i) + 1, ifelse(length(i) <= 8, 3, 4)), -  nrow.legend = ceiling((length(i) + 1)/ncol.legend), -  rel.height.legend = 0.03 + 0.08 * nrow.legend, -  rel.height.bottom = 1.1, -  pch_ds = 1:length(i), -  col_ds = pch_ds + 1, -  lty_ds = col_ds, -  frame = TRUE, -  ... -) - -\method{plot}{nlme.mmkin}( +\method{plot}{mixed.mmkin}(    x,    i = 1:ncol(x$mmkin),    obs_vars = names(x$mkinmod$map), @@ -93,7 +70,7 @@ corresponding model prediction lines for the different datasets.}  \item{...}{Further arguments passed to \code{\link{plot}}.}  }  \value{ -The functions are called for their side effect. +The function is called for its side effect.  }  \description{  Plot predictions from a fitted nonlinear mixed model obtained via an mmkin row object @@ -108,7 +85,6 @@ dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "A1"),  f <- mmkin(list("DFOP-SFO" = dfop_sfo), ds, quiet = TRUE)  plot(f[, 3:4], standardized = TRUE) -library(nlme)  # For this fit we need to increase pnlsMaxiter, and we increase the  # tolerance in order to speed up the fit for this example evaluation  f_nlme <- nlme(f, control = list(pnlsMaxIter = 120, tolerance = 1e-3)) diff --git a/man/saem.Rd b/man/saem.Rd index 56b54fbf..17f777c4 100644 --- a/man/saem.Rd +++ b/man/saem.Rd @@ -44,7 +44,8 @@ by the saemix function?}  }  \value{  An S3 object of class 'saem.mmkin', containing the fitted -\link[saemix:SaemixObject-class]{saemix::SaemixObject} as a list component named 'so'. +\link[saemix:SaemixObject-class]{saemix::SaemixObject} as a list component named 'so'. The +object also inherits from 'mixed.mmkin'.  An \link[saemix:SaemixModel-class]{saemix::SaemixModel} object. @@ -114,5 +115,5 @@ summary(f_saem_dfop_sfo, data = FALSE)  }  }  \seealso{ -\link{summary.saem.mmkin} +\link{summary.saem.mmkin} \link{plot.mixed.mmkin}  } | 
