diff options
author | Johannes Ranke <jranke@uni-bremen.de> | 2020-10-24 00:32:00 +0200 |
---|---|---|
committer | Johannes Ranke <jranke@uni-bremen.de> | 2020-10-24 00:32:00 +0200 |
commit | dd80ab5d64bc6b56587b0542dc95e965a3a25590 (patch) | |
tree | 5d7f1b1ff464a9cb9401e6a32be5485adaae7118 | |
parent | ba806b0255821d5e508d82c7bf7dc68cc3c8328c (diff) |
Plot method for nlme.mmkin objects
Update docs
-rw-r--r-- | NAMESPACE | 1 | ||||
-rw-r--r-- | NEWS.md | 2 | ||||
-rw-r--r-- | R/nlme.mmkin.R | 2 | ||||
-rw-r--r-- | R/plot.mmkin.R | 18 | ||||
-rw-r--r-- | R/plot.nlme.mmkin.R | 259 | ||||
-rw-r--r-- | _pkgdown.yml | 2 | ||||
-rw-r--r-- | docs/dev/news/index.html | 4 | ||||
-rw-r--r-- | docs/dev/pkgdown.yml | 2 | ||||
-rw-r--r-- | docs/dev/reference/Extract.mmkin.html | 71 | ||||
-rw-r--r-- | docs/dev/reference/Rplot001.png | bin | 25568 -> 27839 bytes | |||
-rw-r--r-- | docs/dev/reference/Rplot002.png | bin | 26000 -> 63682 bytes | |||
-rw-r--r-- | docs/dev/reference/index.html | 12 | ||||
-rw-r--r-- | docs/dev/reference/plot.nlme.mmkin-1.png | bin | 35382 -> 86071 bytes | |||
-rw-r--r-- | docs/dev/reference/plot.nlme.mmkin-2.png | bin | 35346 -> 177237 bytes | |||
-rw-r--r-- | docs/dev/reference/plot.nlme.mmkin.html | 141 | ||||
-rw-r--r-- | docs/dev/reference/print.mmkin.html | 194 | ||||
-rw-r--r-- | docs/dev/sitemap.xml | 3 | ||||
-rw-r--r-- | man/Extract.mmkin.Rd | 3 | ||||
-rw-r--r-- | man/plot.nlme.mmkin.Rd | 83 | ||||
-rw-r--r-- | man/print.mmkin.Rd | 16 |
20 files changed, 624 insertions, 189 deletions
@@ -22,6 +22,7 @@ S3method(plot,nafta) S3method(plot,nlme.mmkin) S3method(print,mkinds) S3method(print,mkinmod) +S3method(print,mmkin) S3method(print,nafta) S3method(print,nlme.mmkin) S3method(print,summary.mkinfit) @@ -1,5 +1,7 @@ # mkin 0.9.50.4 (unreleased) +- 'plot' method for 'nlme.mmkin' objects + - 'print' method for 'mmkin' objects - 'saemix_model', 'saemix_data': Helper functions to fit nonlinear mixed-effects models for mmkin row objects using the saemix package diff --git a/R/nlme.mmkin.R b/R/nlme.mmkin.R index c8a99d59..d4720e79 100644 --- a/R/nlme.mmkin.R +++ b/R/nlme.mmkin.R @@ -196,6 +196,8 @@ nlme.mmkin <- function(model, data = sys.frame(sys.parent()), val <- do.call("nlme.formula", thisCall) val$mmkin_orig <- model + val$data <- thisCall[["data"]] + val$mkinmod <- model[[1]]$mkinmod class(val) <- c("nlme.mmkin", "nlme", "lme") return(val) } diff --git a/R/plot.mmkin.R b/R/plot.mmkin.R index ac66e542..0523e4d3 100644 --- a/R/plot.mmkin.R +++ b/R/plot.mmkin.R @@ -54,12 +54,16 @@ #' #' @export plot.mmkin <- function(x, 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", ...) { + 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", ...) +{ + + oldpar <- par(no.readonly = TRUE) + n.m <- nrow(x) n.d <- ncol(x) @@ -82,8 +86,6 @@ plot.mmkin <- function(x, main = "auto", legends = 1, datasets = rownames(x)) } - oldpar <- par(no.readonly = TRUE) - # Set relative plot heights, so the first and the last plot are the norm # and the middle plots (if n.fits >2) are smaller by rel.height.middle rel.heights <- if (n.fits > 2) c(1, rep(rel.height.middle, n.fits - 2), 1) diff --git a/R/plot.nlme.mmkin.R b/R/plot.nlme.mmkin.R index 0f3ad715..084099ac 100644 --- a/R/plot.nlme.mmkin.R +++ b/R/plot.nlme.mmkin.R @@ -1,115 +1,224 @@ +if(getRversion() >= '2.15.1') utils::globalVariables("ds") + #' Plot a fitted nonlinear mixed model obtained via an mmkin row object #' #' @param x An object of class \code{\link{nlme.mmkin}} #' @param i A numeric index to select datasets for which to plot the nlme fit, #' in case plots get too large #' @param main The main title placed on the outer margin of the plot. +#' @inheritParams plot.mkinfit #' @param legends An index for the fits for which legends should be shown. -#' @param resplot Should the residuals plotted against time, using -#' \code{\link{mkinresplot}}, or as squared residuals against predicted -#' values, with the error model, using \code{\link{mkinerrplot}}. -#' @param standardized Should the residuals be standardized? This option -#' is passed to \code{\link{mkinresplot}}, it only takes effect if +#' @param standardized Should the residuals be standardized? 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. -#' @param ymax Maximum y axis value for \code{\link{plot.mkinfit}}. +#' @param ymax Vector of maximum y axis values #' @param \dots Further arguments passed to \code{\link{plot.mkinfit}} and #' \code{\link{mkinresplot}}. +#' @param resplot Should the residuals plotted against time or against +#' predicted values? +#' @param col_ds Colors used for plotting the observed data and the +#' corresponding model prediction lines for the different datasets. +#' @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 function is called for its side effect. #' @author Johannes Ranke #' @examples #' 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]) +#' function(x) x$data[c("name", "time", "value")]) +#' names(ds) <- paste0("ds ", 6:10) +#' dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "A1"), +#' A1 = mkinsub("SFO"), quiet = TRUE) +#' f <- mmkin(list("DFOP-SFO" = dfop_sfo), ds, quiet = TRUE, cores = 1) +#' plot(f[, 3:4], standardized = TRUE) #' library(nlme) -#' f_nlme <- nlme(f) -#' -#' #plot(f_nlme) # too many panels for pkgdown -#' plot(f_nlme, 3:4) +#' # 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-4)) +#' plot(f_nlme) #' @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, + main = rownames(x$mmkin_orig), + obs_vars = names(x$mkinmod$map), + standardized = TRUE, + xlab = "Time", ylab = "Observed", + xlim = range(x$data$time), + legends = 1, + lpos = "topright", inset = c(0.05, 0.05), + resplot = c("predicted", "time"), + ymax = "auto", maxabs = "auto", cex = 0.7, rel.height.middle = 0.9, - ymax = "auto", ...) + pch_ds = 1:length(i), + col_ds = pch_ds + 1, + lty_ds = col_ds, + frame = TRUE, ...) { - degparms_optim_nlme <- coefficients(x) - degparms_optim_names <- names(degparms_optim_nlme) + oldpar <- par(no.readonly = TRUE) - odeini_optim_names <- grep("_0$", degparms_optim_names, value = TRUE) - odeparms_optim_names <- setdiff(degparms_optim_names, odeini_optim_names) + fit_1 = x$mmkin_orig[[1]] + ds_names <- colnames(x$mmkin_orig) - fit_1 <- x$mmkin_orig[[1]] + degparms_optim <- coefficients(x) + degparms_optim_names <- names(degparms_optim) + degparms_fixed <- fit_1$fixed$value + names(degparms_fixed) <- rownames(fit_1$fixed) + degparms_all <- cbind(as.matrix(degparms_optim), fit_1$bparms.fixed) + degparms_all_names <- c(degparms_optim_names, names(degparms_fixed)) + colnames(degparms_all) <- degparms_all_names - mkinfit_call <- as.list(fit_1$call)[-1] - mkinfit_call[["mkinmod"]] <- fit_1$mkinmod + odeini_names <- grep("_0$", degparms_all_names, value = TRUE) + odeparms_names <- setdiff(degparms_all_names, odeini_names) - ds <- lapply(x$mmkin_orig, function(x) { - data.frame(name = x$data$variable, - time = x$data$time, - value = x$data$observed) - }) + residual_type = ifelse(standardized, "pearson", "response") - # This takes quite some time. This could be greatly reduced - # if the plot.mkinfit code would be imported and adapted, - # allowing also to overly plots of mmkin fits and nlme fits - mmkin_nlme <- lapply(i, function(a) { + observed <- cbind(x$data, + residual = residuals(x, type = residual_type)) - degparms_optim <- as.numeric(degparms_optim_nlme[a, ]) - names(degparms_optim) <- degparms_optim_names + n_plot_rows = length(obs_vars) + n_plots = n_plot_rows * 2 - odeini_optim <- degparms_optim[odeini_optim_names] - names(odeini_optim) <- gsub("_0$", "", names(odeini_optim)) - - odeparms_optim_trans <- degparms_optim[odeparms_optim_names] - odeparms_optim <- backtransform_odeparms(odeparms_optim_trans, - fit_1$mkinmod, - transform_rates = fit_1$transform_rates, - transform_fractions = fit_1$transform_fractions) + # Set relative plot heights, so the first and the last plot are the norm + # and the middle plots (if n_plot_rows >2) are smaller by rel.height.middle + rel.heights <- if (n_plot_rows > 2) { + c(1, rep(rel.height.middle, n_plot_rows - 2), 1) + } else { + rep(1, n_plot_rows) + } - fit_a <- x$mmkin_orig[[a]] + layout_matrix = matrix(1:n_plots, + n_plot_rows, 2, byrow = TRUE) + layout(layout_matrix, heights = rel.heights) - state_ini <- fit_a$bparms.state - state_ini[names(odeini_optim)] <- odeini_optim + solution_type = fit_1$solution_type - odeparms <- fit_a$bparms.ode - odeparms[names(odeparms_optim)] <- odeparms_optim + outtimes <- sort(unique(c(x$data$time, + seq(xlim[1], xlim[2], length.out = 50)))) - mkinfit_call[["observed"]] <- ds[[a]] - mkinfit_call[["parms.ini"]] <- odeparms - mkinfit_call[["state.ini"]] <- state_ini + pred_ds <- purrr::map_dfr(i, function(ds_i) { + odeparms_trans <- degparms_all[ds_i, odeparms_names] + odeparms <- backtransform_odeparms(odeparms_trans, + x$mkinmod, + transform_rates = fit_1$transform_rates, + transform_fractions = fit_1$transform_fractions) - mkinfit_call[["control"]] <- list(iter.max = 0) - mkinfit_call[["quiet"]] <- TRUE + odeini <- degparms_all[ds_i, odeini_names] + names(odeini) <- gsub("_0", "", names(odeini)) - res <- suppressWarnings(do.call("mkinfit", mkinfit_call)) - return(res) + out <- mkinpredict(x$mkinmod, odeparms, odeini, + outtimes, solution_type = solution_type, + atol = fit_1$atol, rtol = fit_1$rtol) + return(cbind(as.data.frame(out), ds = ds_names[ds_i])) }) - # Set dimensions with names and the class (mmkin) - attributes(mmkin_nlme) <- attributes(x$mmkin_orig[, i]) - - plot(mmkin_nlme, main = main, legends = legends, - resplot = resplot, standardized = standardized, - show_errmin = show_errmin, - errmin_var = errmin_var, errmin_digits = errmin_digits, - cex = cex, - rel.height.middle = rel.height.middle, - ymax = ymax, ...) - + degparms_all_pop <- c(fixef(x), degparms_fixed) + + odeparms_pop_trans <- degparms_all_pop[odeparms_names] + odeparms_pop <- backtransform_odeparms(odeparms_pop_trans, + x$mkinmod, + transform_rates = fit_1$transform_rates, + transform_fractions = fit_1$transform_fractions) + + odeini_pop <- degparms_all_pop[odeini_names] + names(odeini_pop) <- gsub("_0", "", names(odeini_pop)) + + pred_pop <- as.data.frame( + mkinpredict(x$mkinmod, odeparms_pop, odeini_pop, + outtimes, solution_type = solution_type, + atol = fit_1$atol, rtol = fit_1$rtol)) + + resplot <- match.arg(resplot) + + # Loop plot rows + for (plot_row in 1:n_plot_rows) { + + obs_var <- obs_vars[plot_row] + observed_row <- subset(observed, name == obs_var) + + # Set ylim to sensible default, or use ymax + if (identical(ymax, "auto")) { + ylim_row = c(0, + max(c(observed_row$value, pred_ds[[obs_var]]), na.rm = TRUE)) + } else { + ylim_row = c(0, ymax[plot_row]) + } + + # Margins for top row of plots when we have more than one row + # Reduce bottom margin by 2.1 - hides x axis legend + if (plot_row == 1 & n_plot_rows > 1) { + par(mar = c(3.0, 4.1, 4.1, 2.1)) + } + + # Margins for middle rows of plots, if any + if (plot_row > 1 & plot_row < n_plot_rows) { + # Reduce top margin by 2 after the first plot as we have no main title, + # reduced plot height, therefore we need rel.height.middle in the layout + par(mar = c(3.0, 4.1, 2.1, 2.1)) + } + + # Margins for bottom row of plots when we have more than one row + if (plot_row == n_plot_rows & n_plot_rows > 1) { + # Restore bottom margin for last plot to show x axis legend + par(mar = c(5.1, 4.1, 2.1, 2.1)) + } + + plot(pred_pop$time, pred_pop[[obs_var]], + main = obs_var, + type = "l", lwd = 2, + xlim = xlim, ylim = ylim_row, + xlab = xlab, ylab = ylab, frame = frame, + cex = cex) + + for (ds_i in seq_along(i)) { + points(subset(observed_row, ds == ds_names[ds_i], c("time", "value")), + col = col_ds[ds_i], pch = pch_ds[ds_i]) + lines(subset(pred_ds, ds == ds_names[ds_i], c("time", obs_var)), + col = col_ds[ds_i], lty = lty_ds[ds_i]) + } + + if (plot_row %in% legends) { + legend(lpos, inset = inset, + legend = c("Population mean", 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)) + } + + if (identical(maxabs, "auto")) { + maxabs = max(abs(observed_row$residual), na.rm = TRUE) + } + + + if (identical(resplot, "time")) { + plot(0, type = "n", xlim = xlim, xlab = "Time", + main = obs_var, + ylim = c(-1.2 * maxabs, 1.2 * maxabs), + ylab = if (standardized) "Standardized residual" else "Residual") + abline(h = 0, lty = 2) + + for (ds_i in seq_along(i)) { + points(subset(observed_row, ds == ds_names[ds_i], c("time", "residual")), + col = col_ds[ds_i], pch = pch_ds[ds_i]) + } + } + + if (identical(resplot, "predicted")) { + plot(0, type = "n", + main = obs_var, + xlim = c(0, max(pred_ds[[obs_var]])), + xlab = "Predicted", + ylim = c(-1.2 * maxabs, 1.2 * maxabs), + ylab = if (standardized) "Standardized residual" else "Residual") + + for (ds_i in seq_along(i)) { + observed_row_ds <- merge( + subset(observed_row, ds == ds_names[ds_i], c("time", "residual")), + subset(pred_ds, ds == ds_names[ds_i], c("time", obs_var))) + points(observed_row_ds[c(3, 2)], + col = col_ds[ds_i], pch = pch_ds[ds_i]) + } + } + } } diff --git a/_pkgdown.yml b/_pkgdown.yml index 74abeeba..a73b8b09 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -37,6 +37,7 @@ reference: - "`[.mmkin`" - plot.mmkin - AIC.mmkin + - print.mmkin - title: Mixed models desc: Create and work with nonlinear mixed models contents: @@ -44,6 +45,7 @@ reference: - plot.nlme.mmkin - nlme_function - get_deg_func + - saemix_model - title: Datasets and known results contents: - FOCUS_2006_A diff --git a/docs/dev/news/index.html b/docs/dev/news/index.html index 190bfe87..c29e413d 100644 --- a/docs/dev/news/index.html +++ b/docs/dev/news/index.html @@ -146,7 +146,9 @@ <a href="#mkin-0-9-50-4-unreleased" class="anchor"></a>mkin 0.9.50.4 (unreleased)<small> Unreleased </small> </h1> <ul> -<li>‘saemix_model’, ‘saemix_data’: Helper functions to fit nonlinear mixed-effects models for mmkin row objects using the saemix package</li> +<li><p>‘plot’ method for ‘nlme.mmkin’ objects</p></li> +<li><p>‘print’ method for ‘mmkin’ objects</p></li> +<li><p>‘saemix_model’, ‘saemix_data’: Helper functions to fit nonlinear mixed-effects models for mmkin row objects using the saemix package</p></li> </ul> </div> <div id="mkin-0-9-50-3-2020-10-08" class="section level1"> diff --git a/docs/dev/pkgdown.yml b/docs/dev/pkgdown.yml index 4bca36e6..8c97cd7c 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-10-22T11:16Z +last_built: 2020-10-23T22:30Z urls: reference: https://pkgdown.jrwb.de/mkin/reference article: https://pkgdown.jrwb.de/mkin/articles diff --git a/docs/dev/reference/Extract.mmkin.html b/docs/dev/reference/Extract.mmkin.html index c69259b6..0c02355f 100644 --- a/docs/dev/reference/Extract.mmkin.html +++ b/docs/dev/reference/Extract.mmkin.html @@ -40,7 +40,7 @@ <meta property="og:title" content="Subsetting method for mmkin objects — [.mmkin" /> -<meta property="og:description" content="Subsetting method for mmkin objects." /> +<meta property="og:description" content="Subsetting method for mmkin objects" /> <meta name="robots" content="noindex"> @@ -72,7 +72,7 @@ </button> <span class="navbar-brand"> <a class="navbar-link" href="../index.html">mkin</a> - <span class="version label label-danger" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.3</span> + <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> </span> </div> @@ -120,7 +120,7 @@ </ul> <ul class="nav navbar-nav navbar-right"> <li> - <a href="http://github.com/jranke/mkin/"> + <a href="https://github.com/jranke/mkin/"> <span class="fab fa fab fa-github fa-lg"></span> </a> @@ -139,12 +139,12 @@ <div class="col-md-9 contents"> <div class="page-header"> <h1>Subsetting method for mmkin objects</h1> - <small class="dont-index">Source: <a href='http://github.com/jranke/mkin/blob/master/R/mmkin.R'><code>R/mmkin.R</code></a></small> + <small class="dont-index">Source: <a href='https://github.com/jranke/mkin/blob/master/R/mmkin.R'><code>R/mmkin.R</code></a></small> <div class="hidden name"><code>Extract.mmkin.Rd</code></div> </div> <div class="ref-description"> - <p>Subsetting method for mmkin objects.</p> + <p>Subsetting method for mmkin objects</p> </div> <pre class="usage"># S3 method for mmkin @@ -179,30 +179,46 @@ either a list of mkinfit objects or a single mkinfit object.</p></td> <h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2> <p>An object of class <code><a href='mmkin.html'>mmkin</a></code>.</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='co'># Only use one core, to pass R CMD check --as-cran</span> - <span class='no'>fits</span> <span class='kw'><-</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'>"SFO"</span>, <span class='st'>"FOMC"</span>), <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='kw'>B</span> <span class='kw'>=</span> <span class='no'>FOCUS_2006_B</span>, <span class='kw'>C</span> <span class='kw'>=</span> <span class='no'>FOCUS_2006_C</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='no'>fits</span>[<span class='st'>"FOMC"</span>, ]</div><div class='output co'>#> dataset -#> model B C -#> FOMC List,39 List,39 -#> attr(,"class") -#> [1] "mmkin"</div><div class='input'> <span class='no'>fits</span>[, <span class='st'>"B"</span>]</div><div class='output co'>#> dataset -#> model B -#> SFO List,39 -#> FOMC List,39 -#> attr(,"class") -#> [1] "mmkin"</div><div class='input'> <span class='no'>fits</span>[<span class='st'>"SFO"</span>, <span class='st'>"B"</span>]</div><div class='output co'>#> dataset -#> model B -#> SFO List,39 -#> attr(,"class") -#> [1] "mmkin"</div><div class='input'> - <span class='fu'><a href='https://rdrr.io/r/utils/head.html'>head</a></span>( + <span class='va'>fits</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='op'>)</span>, <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span>B <span class='op'>=</span> <span class='va'>FOCUS_2006_B</span>, C <span class='op'>=</span> <span class='va'>FOCUS_2006_C</span><span class='op'>)</span>, + cores <span class='op'>=</span> <span class='fl'>1</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> + <span class='va'>fits</span><span class='op'>[</span><span class='st'>"FOMC"</span>, <span class='op'>]</span> +</div><div class='output co'>#> <mmkin> object +#> Status of individual fits: +#> +#> dataset +#> model B C +#> FOMC OK OK +#> +#> OK: No warnings</div><div class='input'> <span class='va'>fits</span><span class='op'>[</span>, <span class='st'>"B"</span><span class='op'>]</span> +</div><div class='output co'>#> <mmkin> object +#> Status of individual fits: +#> +#> dataset +#> model B +#> SFO OK +#> FOMC OK +#> +#> OK: No warnings</div><div class='input'> <span class='va'>fits</span><span class='op'>[</span><span class='st'>"SFO"</span>, <span class='st'>"B"</span><span class='op'>]</span> +</div><div class='output co'>#> <mmkin> object +#> Status of individual fits: +#> +#> dataset +#> model B +#> SFO OK +#> +#> OK: No warnings</div><div class='input'> + <span class='fu'><a href='https://rdrr.io/r/utils/head.html'>head</a></span><span class='op'>(</span> <span class='co'># This extracts an mkinfit object with lots of components</span> - <span class='no'>fits</span><span class='kw'>[[</span><span class='st'>"FOMC"</span>, <span class='st'>"B"</span>]] - )</div><div class='output co'>#> $par + <span class='va'>fits</span><span class='op'>[[</span><span class='st'>"FOMC"</span>, <span class='st'>"B"</span><span class='op'>]</span><span class='op'>]</span> + <span class='op'>)</span> +</div><div class='output co'>#> $par #> parent_0 log_alpha log_beta sigma #> 99.666193 2.549849 5.050586 1.890202 #> @@ -217,12 +233,11 @@ either a list of mkinfit objects or a single mkinfit object.</p></td> #> #> $evaluations #> function gradient -#> 25 72 +#> 25 78 #> #> $message #> [1] "both X-convergence and relative convergence (5)" -#> </div><div class='input'> -</div></pre> +#> </div></pre> </div> <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> <nav id="toc" data-toggle="toc" class="sticky-top"> @@ -238,7 +253,7 @@ either a list of mkinfit objects or a single mkinfit object.</p></td> </div> <div class="pkgdown"> - <p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.5.1.</p> + <p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.6.1.</p> </div> </footer> diff --git a/docs/dev/reference/Rplot001.png b/docs/dev/reference/Rplot001.png Binary files differindex 9c8f80fc..cfc5bc2b 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.png Binary files differindex 1b15782a..71c768bd 100644 --- a/docs/dev/reference/Rplot002.png +++ b/docs/dev/reference/Rplot002.png diff --git a/docs/dev/reference/index.html b/docs/dev/reference/index.html index 5d70a450..24056025 100644 --- a/docs/dev/reference/index.html +++ b/docs/dev/reference/index.html @@ -297,6 +297,12 @@ of an mmkin object</p></td> <p><code><a href="AIC.mmkin.html">AIC(<i><mmkin></i>)</a></code> <code><a href="AIC.mmkin.html">BIC(<i><mmkin></i>)</a></code> </p> </td> <td><p>Calculate the AIC for a column of an mmkin object</p></td> + </tr><tr> + + <td> + <p><code><a href="print.mmkin.html">print(<i><mmkin></i>)</a></code> </p> + </td> + <td><p>Print method for mmkin objects</p></td> </tr> </tbody><tbody> <tr> @@ -334,6 +340,12 @@ of an mmkin object</p></td> <p><code><a href="get_deg_func.html">get_deg_func()</a></code> </p> </td> <td><p>Retrieve a degradation function from the mmkin namespace</p></td> + </tr><tr> + + <td> + <p><code><a href="saemix.html">saemix_model()</a></code> <code><a href="saemix.html">saemix_data()</a></code> </p> + </td> + <td><p>Create saemix models from mmkin row objects</p></td> </tr> </tbody><tbody> <tr> diff --git a/docs/dev/reference/plot.nlme.mmkin-1.png b/docs/dev/reference/plot.nlme.mmkin-1.png Binary files differindex fe2ef7d3..91e3ca52 100644 --- a/docs/dev/reference/plot.nlme.mmkin-1.png +++ b/docs/dev/reference/plot.nlme.mmkin-1.png diff --git a/docs/dev/reference/plot.nlme.mmkin-2.png b/docs/dev/reference/plot.nlme.mmkin-2.png Binary files differindex 265fd2e0..57128ade 100644 --- a/docs/dev/reference/plot.nlme.mmkin-2.png +++ b/docs/dev/reference/plot.nlme.mmkin-2.png diff --git a/docs/dev/reference/plot.nlme.mmkin.html b/docs/dev/reference/plot.nlme.mmkin.html index 7e6124a1..f17a23e3 100644 --- a/docs/dev/reference/plot.nlme.mmkin.html +++ b/docs/dev/reference/plot.nlme.mmkin.html @@ -72,7 +72,7 @@ </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.3</span> + <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> </span> </div> @@ -120,7 +120,7 @@ </ul> <ul class="nav navbar-nav navbar-right"> <li> - <a href="http://github.com/jranke/mkin/"> + <a href="https://github.com/jranke/mkin/"> <span class="fab fa fab fa-github fa-lg"></span> </a> @@ -139,7 +139,7 @@ <div class="col-md-9 contents"> <div class="page-header"> <h1>Plot a fitted nonlinear mixed model obtained via an mmkin row object</h1> - <small class="dont-index">Source: <a href='http://github.com/jranke/mkin/blob/master/R/plot.nlme.mmkin.R'><code>R/plot.nlme.mmkin.R</code></a></small> + <small class="dont-index">Source: <a href='https://github.com/jranke/mkin/blob/master/R/plot.nlme.mmkin.R'><code>R/plot.nlme.mmkin.R</code></a></small> <div class="hidden name"><code>plot.nlme.mmkin.Rd</code></div> </div> @@ -148,21 +148,29 @@ </div> <pre class="usage"><span class='co'># S3 method for nlme.mmkin</span> -<span class='fu'><a href='https://rdrr.io/r/base/plot.html'>plot</a></span>( - <span class='no'>x</span>, - <span class='kw'>i</span> <span class='kw'>=</span> <span class='fl'>1</span>:<span class='fu'><a href='https://rdrr.io/r/base/nrow.html'>ncol</a></span>(<span class='no'>x</span>$<span class='no'>mmkin_orig</span>), - <span class='kw'>main</span> <span class='kw'>=</span> <span class='st'>"auto"</span>, - <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>, - <span class='no'>...</span> -)</pre> +<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_orig</span><span class='op'>)</span>, + main <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/colnames.html'>rownames</a></span><span class='op'>(</span><span class='va'>x</span><span class='op'>$</span><span class='va'>mmkin_orig</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>, + ylab <span class='op'>=</span> <span class='st'>"Observed"</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>, + legends <span class='op'>=</span> <span class='fl'>1</span>, + lpos <span class='op'>=</span> <span class='st'>"topright"</span>, + inset <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='fl'>0.05</span>, <span class='fl'>0.05</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>, + cex <span class='op'>=</span> <span class='fl'>0.7</span>, + rel.height.middle <span class='op'>=</span> <span class='fl'>0.9</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"> @@ -181,35 +189,55 @@ in case plots get too large</p></td> <td><p>The main title placed on the outer margin of the plot.</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>ylab</th> + <td><p>Label for the y axis.</p></td> + </tr> + <tr> + <th>xlim</th> + <td><p>Plot range in x direction.</p></td> + </tr> + <tr> <th>legends</th> <td><p>An index for the fits for which legends should be shown.</p></td> </tr> <tr> - <th>resplot</th> - <td><p>Should the residuals plotted against time, using -<code><a href='mkinresplot.html'>mkinresplot</a></code>, or as squared residuals against predicted -values, with the error model, using <code><a href='mkinerrplot.html'>mkinerrplot</a></code>.</p></td> + <th>lpos</th> + <td><p>Position(s) of the legend(s). Passed to <code><a href='https://rdrr.io/r/graphics/legend.html'>legend</a></code> as +the first argument. If not length one, this should be of the same length +as the obs_var argument.</p></td> </tr> <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 -<code>resplot = "time"</code>.</p></td> + <th>inset</th> + <td><p>Passed to <code><a href='https://rdrr.io/r/graphics/legend.html'>legend</a></code> if applicable.</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> + <th>resplot</th> + <td><p>Should the residuals plotted against time or against +predicted values?</p></td> </tr> <tr> - <th>errmin_var</th> - <td><p>The variable for which the FOCUS chi2 error value should -be shown.</p></td> + <th>ymax</th> + <td><p>Vector of maximum y axis values</p></td> </tr> <tr> - <th>errmin_digits</th> - <td><p>The number of significant digits for rounding the FOCUS -chi2 error percentage.</p></td> + <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>cex</th> @@ -221,8 +249,21 @@ chi2 error percentage.</p></td> than two rows of plots are shown.</p></td> </tr> <tr> - <th>ymax</th> - <td><p>Maximum y axis value for <code><a href='plot.mkinfit.html'>plot.mkinfit</a></code>.</p></td> + <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> @@ -234,16 +275,24 @@ than two rows of plots are shown.</p></td> <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='no'>ds</span> <span class='kw'><-</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='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'><-</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>)</div><div class='output co'>#> <span class='warning'>Warning: Shapiro-Wilk test for standardized residuals: p = 0.0195</span></div><div class='output co'>#> <span class='warning'>Warning: Shapiro-Wilk test for standardized residuals: p = 0.011</span></div><div class='input'><span class='co'>#plot(f) # too many panels for pkgdown</span> -<span class='fu'><a href='https://rdrr.io/r/base/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'><-</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/base/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> + <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='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>, cores <span class='op'>=</span> <span class='fl'>1</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.nlme.mmkin-1.png' alt='' width='700' height='433' /></div><div class='input'><span class='kw'><a href='https://rdrr.io/r/base/library.html'>library</a></span><span class='op'>(</span><span class='va'><a href='https://svn.r-project.org/R-packages/trunk/nlme/'>nlme</a></span><span class='op'>)</span> +<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-4</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.nlme.mmkin-2.png' alt='' width='700' height='433' /></div></pre> </div> <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> <nav id="toc" data-toggle="toc" class="sticky-top"> @@ -259,7 +308,7 @@ than two rows of plots are shown.</p></td> </div> <div class="pkgdown"> - <p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.5.1.</p> + <p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.6.1.</p> </div> </footer> diff --git a/docs/dev/reference/print.mmkin.html b/docs/dev/reference/print.mmkin.html new file mode 100644 index 00000000..12c67d86 --- /dev/null +++ b/docs/dev/reference/print.mmkin.html @@ -0,0 +1,194 @@ +<!-- 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>Print method for mmkin objects — print.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="Print method for mmkin objects — print.mmkin" /> +<meta property="og:description" content="Print method for mmkin objects" /> + + +<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>Print method for mmkin objects</h1> + <small class="dont-index">Source: <a href='https://github.com/jranke/mkin/blob/master/R/mmkin.R'><code>R/mmkin.R</code></a></small> + <div class="hidden name"><code>print.mmkin.Rd</code></div> + </div> + + <div class="ref-description"> + <p>Print method for mmkin objects</p> + </div> + + <pre class="usage"><span class='co'># S3 method for mmkin</span> +<span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>x</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 <a href='mmkin.html'>mmkin</a> object.</p></td> + </tr> + <tr> + <th>...</th> + <td><p>Not used.</p></td> + </tr> + </table> + + + </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/sitemap.xml b/docs/dev/sitemap.xml index e284abf6..8c4d8cbe 100644 --- a/docs/dev/sitemap.xml +++ b/docs/dev/sitemap.xml @@ -166,6 +166,9 @@ <loc>https://pkgdown.jrwb.de/mkin/reference/print.mkinmod.html</loc> </url> <url> + <loc>https://pkgdown.jrwb.de/mkin/reference/print.mmkin.html</loc> + </url> + <url> <loc>https://pkgdown.jrwb.de/mkin/reference/reexports.html</loc> </url> <url> diff --git a/man/Extract.mmkin.Rd b/man/Extract.mmkin.Rd index 7677bdba..fd54755c 100644 --- a/man/Extract.mmkin.Rd +++ b/man/Extract.mmkin.Rd @@ -22,7 +22,7 @@ either a list of mkinfit objects or a single mkinfit object.} An object of class \code{\link{mmkin}}. } \description{ -Subsetting method for mmkin objects. +Subsetting method for mmkin objects } \examples{ @@ -37,7 +37,6 @@ Subsetting method for mmkin objects. # This extracts an mkinfit object with lots of components fits[["FOMC", "B"]] ) - } \author{ Johannes Ranke diff --git a/man/plot.nlme.mmkin.Rd b/man/plot.nlme.mmkin.Rd index 91130402..d1fde212 100644 --- a/man/plot.nlme.mmkin.Rd +++ b/man/plot.nlme.mmkin.Rd @@ -7,16 +7,24 @@ \method{plot}{nlme.mmkin}( x, i = 1:ncol(x$mmkin_orig), - main = "auto", + main = rownames(x$mmkin_orig), + obs_vars = names(x$mkinmod$map), + standardized = TRUE, + xlab = "Time", + ylab = "Observed", + xlim = range(x$data$time), legends = 1, - resplot = c("time", "errmod"), - standardized = FALSE, - show_errmin = TRUE, - errmin_var = "All data", - errmin_digits = 3, + lpos = "topright", + inset = c(0.05, 0.05), + resplot = c("predicted", "time"), + ymax = "auto", + maxabs = "auto", cex = 0.7, rel.height.middle = 0.9, - ymax = "auto", + pch_ds = 1:length(i), + col_ds = pch_ds + 1, + lty_ds = col_ds, + frame = TRUE, ... ) } @@ -28,31 +36,48 @@ in case plots get too large} \item{main}{The main title placed on the outer margin of the plot.} +\item{obs_vars}{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.} + +\item{standardized}{Should the residuals be standardized? Only takes effect if +\code{resplot = "time"}.} + +\item{xlab}{Label for the x axis.} + +\item{ylab}{Label for the y axis.} + +\item{xlim}{Plot range in x direction.} + \item{legends}{An index for the fits for which legends should be shown.} -\item{resplot}{Should the residuals plotted against time, using -\code{\link{mkinresplot}}, or as squared residuals against predicted -values, with the error model, using \code{\link{mkinerrplot}}.} +\item{lpos}{Position(s) of the legend(s). Passed to \code{\link{legend}} as +the first argument. If not length one, this should be of the same length +as the obs_var argument.} -\item{standardized}{Should the residuals be standardized? This option -is passed to \code{\link{mkinresplot}}, it only takes effect if -\code{resplot = "time"}.} +\item{inset}{Passed to \code{\link{legend}} if applicable.} -\item{show_errmin}{Should the chi2 error level be shown on top of the plots -to the left?} +\item{resplot}{Should the residuals plotted against time or against +predicted values?} -\item{errmin_var}{The variable for which the FOCUS chi2 error value should -be shown.} +\item{ymax}{Vector of maximum y axis values} -\item{errmin_digits}{The number of significant digits for rounding the FOCUS -chi2 error percentage.} +\item{maxabs}{Maximum absolute value of the residuals. This is used for the +scaling of the y axis and defaults to "auto".} \item{cex}{Passed to the plot functions and \code{\link{mtext}}.} \item{rel.height.middle}{The relative height of the middle plot, if more than two rows of plots are shown.} -\item{ymax}{Maximum y axis value for \code{\link{plot.mkinfit}}.} +\item{pch_ds}{Symbols to be used for plotting the data.} + +\item{col_ds}{Colors used for plotting the observed data and the +corresponding model prediction lines for the different datasets.} + +\item{lty_ds}{Line types to be used for the model predictions.} + +\item{frame}{Should a frame be drawn around the plots?} \item{\dots}{Further arguments passed to \code{\link{plot.mkinfit}} and \code{\link{mkinresplot}}.} @@ -65,15 +90,17 @@ Plot a fitted nonlinear mixed model obtained via an mmkin row object } \examples{ 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]) + function(x) x$data[c("name", "time", "value")]) +names(ds) <- paste0("ds ", 6:10) +dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "A1"), + A1 = mkinsub("SFO"), quiet = TRUE) +f <- mmkin(list("DFOP-SFO" = dfop_sfo), ds, quiet = TRUE, cores = 1) +plot(f[, 3:4], standardized = TRUE) library(nlme) -f_nlme <- nlme(f) - -#plot(f_nlme) # too many panels for pkgdown -plot(f_nlme, 3:4) +# 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-4)) +plot(f_nlme) } \author{ Johannes Ranke diff --git a/man/print.mmkin.Rd b/man/print.mmkin.Rd new file mode 100644 index 00000000..29abe143 --- /dev/null +++ b/man/print.mmkin.Rd @@ -0,0 +1,16 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/mmkin.R +\name{print.mmkin} +\alias{print.mmkin} +\title{Print method for mmkin objects} +\usage{ +\method{print}{mmkin}(x, ...) +} +\arguments{ +\item{x}{An \link{mmkin} object.} + +\item{\dots}{Not used.} +} +\description{ +Print method for mmkin objects +} |