From cfa1340c41fe77117c3c2481ddbb25579f196bdd Mon Sep 17 00:00:00 2001 From: Johannes Ranke Date: Mon, 30 Mar 2020 19:17:13 +0200 Subject: Don't check for gcc on the path in mkinmod Roxygen update -> formatting changes in Rd files --- DESCRIPTION | 2 +- R/mkinmod.R | 117 ++++++++++++++++++++++------------------------ man/CAKE_export.Rd | 21 ++++++--- man/add_err.Rd | 12 ++++- man/confint.mkinfit.Rd | 17 +++++-- man/lrtest.mkinfit.Rd | 2 +- man/mkinds.Rd | 35 ++++++++++++-- man/mkinerrplot.Rd | 19 ++++++-- man/mkinfit.Rd | 33 +++++++++---- man/mkinmod.Rd | 9 +++- man/mkinpredict.Rd | 57 +++++++++++++++------- man/mkinresplot.Rd | 18 +++++-- man/mmkin.Rd | 11 +++-- man/plot.mkinfit.Rd | 55 ++++++++++++++++------ man/plot.mmkin.Rd | 17 +++++-- man/summary.mkinfit.Rd | 6 +-- man/transform_odeparms.Rd | 16 +++++-- 17 files changed, 304 insertions(+), 143 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 0bc78ed2..bd6a0a09 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -27,4 +27,4 @@ Encoding: UTF-8 VignetteBuilder: knitr BugReports: http://github.com/jranke/mkin/issues URL: https://pkgdown.jrwb.de/mkin -RoxygenNote: 6.1.1 +RoxygenNote: 7.0.2 diff --git a/R/mkinmod.R b/R/mkinmod.R index a1ae0021..cf618525 100644 --- a/R/mkinmod.R +++ b/R/mkinmod.R @@ -364,79 +364,76 @@ mkinmod <- function(..., use_of_ff = "min", speclist = NULL, quiet = FALSE, verb model$coefmat <- m }#}}} - # Try to create a function compiled from C code if more than one observed {{{ - # variable and gcc is available + # Try to create a function compiled from C code if >1 observed variable {{{ if (length(obs_vars) > 1) { - if (Sys.which("gcc") != "") { - # Translate the R code for the derivatives to C code - diffs.C <- paste(diffs, collapse = ";\n") - diffs.C <- paste0(diffs.C, ";") + # Translate the R code for the derivatives to C code + diffs.C <- paste(diffs, collapse = ";\n") + diffs.C <- paste0(diffs.C, ";") - # HS - diffs.C <- gsub(HS_decline, "(time <= tb ? k1 : k2)", diffs.C, fixed = TRUE) + # HS + diffs.C <- gsub(HS_decline, "(time <= tb ? k1 : k2)", diffs.C, fixed = TRUE) - for (i in seq_along(diffs)) { - state_var <- names(diffs)[i] + for (i in seq_along(diffs)) { + state_var <- names(diffs)[i] - # IORE - if (state_var %in% obs_vars) { - if (spec[[state_var]]$type == "IORE") { - diffs.C <- gsub(paste0(state_var, "^N_", state_var), - paste0("pow(y[", i - 1, "], N_", state_var, ")"), - diffs.C, fixed = TRUE) - } + # IORE + if (state_var %in% obs_vars) { + if (spec[[state_var]]$type == "IORE") { + diffs.C <- gsub(paste0(state_var, "^N_", state_var), + paste0("pow(y[", i - 1, "], N_", state_var, ")"), + diffs.C, fixed = TRUE) } + } - # Replace d_... terms by f[i-1] - # First line - pattern <- paste0("^d_", state_var) - replacement <- paste0("\nf[", i - 1, "]") - diffs.C <- gsub(pattern, replacement, diffs.C) - # Other lines - pattern <- paste0("\\nd_", state_var) - replacement <- paste0("\nf[", i - 1, "]") - diffs.C <- gsub(pattern, replacement, diffs.C) + # Replace d_... terms by f[i-1] + # First line + pattern <- paste0("^d_", state_var) + replacement <- paste0("\nf[", i - 1, "]") + diffs.C <- gsub(pattern, replacement, diffs.C) + # Other lines + pattern <- paste0("\\nd_", state_var) + replacement <- paste0("\nf[", i - 1, "]") + diffs.C <- gsub(pattern, replacement, diffs.C) - # Replace names of observed variables by y[i], - # making the implicit assumption that the observed variables only occur after "* " - pattern <- paste0("\\* ", state_var) - replacement <- paste0("* y[", i - 1, "]") - diffs.C <- gsub(pattern, replacement, diffs.C) - } + # Replace names of observed variables by y[i], + # making the implicit assumption that the observed variables only occur after "* " + pattern <- paste0("\\* ", state_var) + replacement <- paste0("* y[", i - 1, "]") + diffs.C <- gsub(pattern, replacement, diffs.C) + } - derivs_sig <- signature(n = "integer", t = "numeric", y = "numeric", - f = "numeric", rpar = "numeric", ipar = "integer") + derivs_sig <- signature(n = "integer", t = "numeric", y = "numeric", + f = "numeric", rpar = "numeric", ipar = "integer") - # Declare the time variable in the body of the function if it is used - derivs_code <- if (spec[[1]]$type %in% c("FOMC", "DFOP", "HS")) { - paste0("double time = *t;\n", diffs.C) - } else { - diffs.C - } + # Declare the time variable in the body of the function if it is used + derivs_code <- if (spec[[1]]$type %in% c("FOMC", "DFOP", "HS")) { + paste0("double time = *t;\n", diffs.C) + } else { + diffs.C + } - # Define the function initializing the parameters - npar <- length(parms) - initpar_code <- paste0( - "static double parms [", npar, "];\n", - paste0("#define ", parms, " parms[", 0:(npar - 1), "]\n", collapse = ""), - "\n", - "void initpar(void (* odeparms)(int *, double *)) {\n", - " int N = ", npar, ";\n", - " odeparms(&N, parms);\n", - "}\n\n") + # Define the function initializing the parameters + npar <- length(parms) + initpar_code <- paste0( + "static double parms [", npar, "];\n", + paste0("#define ", parms, " parms[", 0:(npar - 1), "]\n", collapse = ""), + "\n", + "void initpar(void (* odeparms)(int *, double *)) {\n", + " int N = ", npar, ";\n", + " odeparms(&N, parms);\n", + "}\n\n") - # Try to build a shared library - cf <- try(cfunction(list(func = derivs_sig), derivs_code, - otherdefs = initpar_code, - verbose = verbose, - convention = ".C", language = "C"), - silent = TRUE) + # Try to build a shared library + cf <- try(cfunction(list(func = derivs_sig), derivs_code, + otherdefs = initpar_code, + verbose = verbose, + convention = ".C", language = "C"), + silent = TRUE) - if (!inherits(cf, "try-error")) { - if (!quiet) message("Successfully compiled differential equation model from auto-generated C code.") - model$cf <- cf - } + if (!inherits(cf, "try-error")) { + if (!quiet) message("Successfully compiled differential equation model from auto-generated C code.") + model$cf <- cf } } # }}} diff --git a/man/CAKE_export.Rd b/man/CAKE_export.Rd index 142b4a75..4bcd8581 100644 --- a/man/CAKE_export.Rd +++ b/man/CAKE_export.Rd @@ -4,12 +4,21 @@ \alias{CAKE_export} \title{Export a list of datasets format to a CAKE study file} \usage{ -CAKE_export(ds, map = c(parent = "Parent"), links = NA, - filename = "CAKE_export.csf", path = ".", overwrite = FALSE, - study = "Codlemone aerobic soil degradation", description = "", - time_unit = "days", res_unit = "\% AR", - comment = "Created using mkin::CAKE_export", date = Sys.Date(), - optimiser = "IRLS") +CAKE_export( + ds, + map = c(parent = "Parent"), + links = NA, + filename = "CAKE_export.csf", + path = ".", + overwrite = FALSE, + study = "Codlemone aerobic soil degradation", + description = "", + time_unit = "days", + res_unit = "\% AR", + comment = "Created using mkin::CAKE_export", + date = Sys.Date(), + optimiser = "IRLS" +) } \arguments{ \item{ds}{A named list of datasets in long format as compatible with diff --git a/man/add_err.Rd b/man/add_err.Rd index 36b98be9..3452923e 100644 --- a/man/add_err.Rd +++ b/man/add_err.Rd @@ -4,8 +4,16 @@ \alias{add_err} \title{Add normally distributed errors to simulated kinetic degradation data} \usage{ -add_err(prediction, sdfunc, secondary = c("M1", "M2"), n = 1000, - LOD = 0.1, reps = 2, digits = 1, seed = NA) +add_err( + prediction, + sdfunc, + secondary = c("M1", "M2"), + n = 1000, + LOD = 0.1, + reps = 2, + digits = 1, + seed = NA +) } \arguments{ \item{prediction}{A prediction from a kinetic model as produced by diff --git a/man/confint.mkinfit.Rd b/man/confint.mkinfit.Rd index f2521ccd..81d7a6e8 100644 --- a/man/confint.mkinfit.Rd +++ b/man/confint.mkinfit.Rd @@ -4,10 +4,19 @@ \alias{confint.mkinfit} \title{Confidence intervals for parameters of mkinfit objects} \usage{ -\method{confint}{mkinfit}(object, parm, level = 0.95, alpha = 1 - - level, cutoff, method = c("quadratic", "profile"), - transformed = TRUE, backtransform = TRUE, - cores = round(detectCores()/2), quiet = FALSE, ...) +\method{confint}{mkinfit}( + object, + parm, + level = 0.95, + alpha = 1 - level, + cutoff, + method = c("quadratic", "profile"), + transformed = TRUE, + backtransform = TRUE, + cores = round(detectCores()/2), + quiet = FALSE, + ... +) } \arguments{ \item{object}{An \code{\link{mkinfit}} object} diff --git a/man/lrtest.mkinfit.Rd b/man/lrtest.mkinfit.Rd index 84d7bc99..8025b883 100644 --- a/man/lrtest.mkinfit.Rd +++ b/man/lrtest.mkinfit.Rd @@ -47,7 +47,7 @@ lrtest(sfo_fit, dfop_fit) #lrtest(dfop_fit, error_model = "tc") #lrtest(dfop_fit, fixed_parms = c(k2 = 0)) -# However, this equivalent syntax works for static help pages +# However, this equivalent syntax also works for static help pages lrtest(dfop_fit, update(dfop_fit, error_model = "tc")) lrtest(dfop_fit, update(dfop_fit, fixed_parms = c(k2 = 0))) } diff --git a/man/mkinds.Rd b/man/mkinds.Rd index 0ea562ed..79eb0167 100644 --- a/man/mkinds.Rd +++ b/man/mkinds.Rd @@ -5,9 +5,6 @@ \alias{mkinds} \title{A dataset class for mkin} \format{An \code{\link{R6Class}} generator object.} -\usage{ -mkinds -} \description{ A dataset class for mkin } @@ -36,3 +33,35 @@ mds <- mkinds$new("FOCUS A", FOCUS_2006_A) } \keyword{datasets} +\section{Methods}{ +\subsection{Public methods}{ +\itemize{ +\item \href{#method-new}{\code{mkinds$new()}} +\item \href{#method-clone}{\code{mkinds$clone()}} +} +} +\if{html}{\out{
}} +\if{html}{\out{}} +\subsection{Method \code{new()}}{ +\subsection{Usage}{ +\if{html}{\out{
}}\preformatted{mkinds$new(title = "", data, time_unit = NA, unit = NA)}\if{html}{\out{
}} +} + +} +\if{html}{\out{
}} +\if{html}{\out{}} +\subsection{Method \code{clone()}}{ +The objects of this class are cloneable with this method. +\subsection{Usage}{ +\if{html}{\out{
}}\preformatted{mkinds$clone(deep = FALSE)}\if{html}{\out{
}} +} + +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{deep}}{Whether to make a deep clone.} +} +\if{html}{\out{
}} +} +} +} diff --git a/man/mkinerrplot.Rd b/man/mkinerrplot.Rd index 3c53e7f8..9564ec19 100644 --- a/man/mkinerrplot.Rd +++ b/man/mkinerrplot.Rd @@ -4,11 +4,20 @@ \alias{mkinerrplot} \title{Function to plot squared residuals and the error model for an mkin object} \usage{ -mkinerrplot(object, obs_vars = names(object$mkinmod$map), xlim = c(0, - 1.1 * max(object$data$predicted)), xlab = "Predicted", - ylab = "Squared residual", maxy = "auto", legend = TRUE, - lpos = "topright", col_obs = "auto", pch_obs = "auto", - frame = TRUE, ...) +mkinerrplot( + object, + obs_vars = names(object$mkinmod$map), + xlim = c(0, 1.1 * max(object$data$predicted)), + xlab = "Predicted", + ylab = "Squared residual", + maxy = "auto", + legend = TRUE, + lpos = "topright", + col_obs = "auto", + pch_obs = "auto", + frame = TRUE, + ... +) } \arguments{ \item{object}{A fit represented in an \code{\link{mkinfit}} object.} diff --git a/man/mkinfit.Rd b/man/mkinfit.Rd index e58e61e2..45036361 100644 --- a/man/mkinfit.Rd +++ b/man/mkinfit.Rd @@ -8,18 +8,33 @@ Rocke, David M. und Lorenzato, Stefan (1995) A two-component model for measurement error in analytical chemistry. Technometrics 37(2), 176-184. } \usage{ -mkinfit(mkinmod, observed, parms.ini = "auto", state.ini = "auto", - err.ini = "auto", fixed_parms = NULL, - fixed_initials = names(mkinmod$diffs)[-1], from_max_mean = FALSE, +mkinfit( + mkinmod, + observed, + parms.ini = "auto", + state.ini = "auto", + err.ini = "auto", + fixed_parms = NULL, + fixed_initials = names(mkinmod$diffs)[-1], + from_max_mean = FALSE, solution_type = c("auto", "analytical", "eigen", "deSolve"), - method.ode = "lsoda", use_compiled = "auto", + method.ode = "lsoda", + use_compiled = "auto", control = list(eval.max = 300, iter.max = 200), - transform_rates = TRUE, transform_fractions = TRUE, quiet = FALSE, - atol = 1e-08, rtol = 1e-10, n.outtimes = 100, + transform_rates = TRUE, + transform_fractions = TRUE, + quiet = FALSE, + atol = 1e-08, + rtol = 1e-10, + n.outtimes = 100, error_model = c("const", "obs", "tc"), - error_model_algorithm = c("auto", "d_3", "direct", "twostep", - "threestep", "fourstep", "IRLS", "OLS"), reweight.tol = 1e-08, - reweight.max.iter = 10, trace_parms = FALSE, ...) + error_model_algorithm = c("auto", "d_3", "direct", "twostep", "threestep", "fourstep", + "IRLS", "OLS"), + reweight.tol = 1e-08, + reweight.max.iter = 10, + trace_parms = FALSE, + ... +) } \arguments{ \item{mkinmod}{A list of class \code{\link{mkinmod}}, containing the kinetic diff --git a/man/mkinmod.Rd b/man/mkinmod.Rd index 91f285e2..d2b851b6 100644 --- a/man/mkinmod.Rd +++ b/man/mkinmod.Rd @@ -4,8 +4,13 @@ \alias{mkinmod} \title{Function to set up a kinetic model with one or more state variables} \usage{ -mkinmod(..., use_of_ff = "min", speclist = NULL, quiet = FALSE, - verbose = FALSE) +mkinmod( + ..., + use_of_ff = "min", + speclist = NULL, + quiet = FALSE, + verbose = FALSE +) } \arguments{ \item{...}{For each observed variable, a list has to be specified as an diff --git a/man/mkinpredict.Rd b/man/mkinpredict.Rd index 53f02dea..17d7ef21 100644 --- a/man/mkinpredict.Rd +++ b/man/mkinpredict.Rd @@ -6,22 +6,47 @@ \alias{mkinpredict.mkinfit} \title{Produce predictions from a kinetic model using specific parameters} \usage{ -mkinpredict(x, odeparms, odeini, outtimes = seq(0, 120, by = 0.1), - solution_type = "deSolve", use_compiled = "auto", - method.ode = "lsoda", atol = 1e-08, rtol = 1e-10, - map_output = TRUE, ...) - -\method{mkinpredict}{mkinmod}(x, odeparms = c(k_parent_sink = 0.1), - odeini = c(parent = 100), outtimes = seq(0, 120, by = 0.1), - solution_type = "deSolve", use_compiled = "auto", - method.ode = "lsoda", atol = 1e-08, rtol = 1e-10, - map_output = TRUE, ...) - -\method{mkinpredict}{mkinfit}(x, odeparms = x$bparms.ode, - odeini = x$bparms.state, outtimes = seq(0, 120, by = 0.1), - solution_type = "deSolve", use_compiled = "auto", - method.ode = "lsoda", atol = 1e-08, rtol = 1e-10, - map_output = TRUE, ...) +mkinpredict( + x, + odeparms, + odeini, + outtimes = seq(0, 120, by = 0.1), + solution_type = "deSolve", + use_compiled = "auto", + method.ode = "lsoda", + atol = 1e-08, + rtol = 1e-10, + map_output = TRUE, + ... +) + +\method{mkinpredict}{mkinmod}( + x, + odeparms = c(k_parent_sink = 0.1), + odeini = c(parent = 100), + outtimes = seq(0, 120, by = 0.1), + solution_type = "deSolve", + use_compiled = "auto", + method.ode = "lsoda", + atol = 1e-08, + rtol = 1e-10, + map_output = TRUE, + ... +) + +\method{mkinpredict}{mkinfit}( + x, + odeparms = x$bparms.ode, + odeini = x$bparms.state, + outtimes = seq(0, 120, by = 0.1), + solution_type = "deSolve", + use_compiled = "auto", + method.ode = "lsoda", + atol = 1e-08, + rtol = 1e-10, + map_output = TRUE, + ... +) } \arguments{ \item{x}{A kinetic model as produced by \code{\link{mkinmod}}, or a kinetic diff --git a/man/mkinresplot.Rd b/man/mkinresplot.Rd index 465b3038..2a8b2d41 100644 --- a/man/mkinresplot.Rd +++ b/man/mkinresplot.Rd @@ -4,11 +4,21 @@ \alias{mkinresplot} \title{Function to plot residuals stored in an mkin object} \usage{ -mkinresplot(object, obs_vars = names(object$mkinmod$map), xlim = c(0, - 1.1 * max(object$data$time)), standardized = FALSE, xlab = "Time", +mkinresplot( + object, + obs_vars = names(object$mkinmod$map), + xlim = c(0, 1.1 * max(object$data$time)), + standardized = FALSE, + xlab = "Time", ylab = ifelse(standardized, "Standardized residual", "Residual"), - maxabs = "auto", legend = TRUE, lpos = "topright", - col_obs = "auto", pch_obs = "auto", frame = TRUE, ...) + maxabs = "auto", + legend = TRUE, + lpos = "topright", + col_obs = "auto", + pch_obs = "auto", + frame = TRUE, + ... +) } \arguments{ \item{object}{A fit represented in an \code{\link{mkinfit}} object.} diff --git a/man/mmkin.Rd b/man/mmkin.Rd index a763fcdf..4bf07370 100644 --- a/man/mmkin.Rd +++ b/man/mmkin.Rd @@ -5,11 +5,16 @@ \title{Fit one or more kinetic models with one or more state variables to one or more datasets} \usage{ -mmkin(models = c("SFO", "FOMC", "DFOP"), datasets, - cores = round(detectCores()/2), cluster = NULL, ...) +mmkin( + models = c("SFO", "FOMC", "DFOP"), + datasets, + cores = round(detectCores()/2), + cluster = NULL, + ... +) } \arguments{ -\item{models}{Either a character vector of shorthand names like +\item{models}{Either a character vector of shorthand names like \code{c("SFO", "FOMC", "DFOP", "HS", "SFORB")}, or an optionally named list of \code{\link{mkinmod}} objects.} diff --git a/man/plot.mkinfit.Rd b/man/plot.mkinfit.Rd index 47cc08a4..c3f3134a 100644 --- a/man/plot.mkinfit.Rd +++ b/man/plot.mkinfit.Rd @@ -7,22 +7,47 @@ \alias{plot_err} \title{Plot the observed data and the fitted model of an mkinfit object} \usage{ -\method{plot}{mkinfit}(x, fit = x, obs_vars = names(fit$mkinmod$map), - xlab = "Time", ylab = "Observed", xlim = range(fit$data$time), - ylim = "default", col_obs = 1:length(obs_vars), pch_obs = col_obs, - lty_obs = rep(1, length(obs_vars)), add = FALSE, legend = !add, - show_residuals = FALSE, show_errplot = FALSE, maxabs = "auto", - sep_obs = FALSE, rel.height.middle = 0.9, row_layout = FALSE, - lpos = "topright", inset = c(0.05, 0.05), show_errmin = FALSE, - errmin_digits = 3, frame = TRUE, ...) - -plot_sep(fit, show_errmin = TRUE, - show_residuals = ifelse(identical(fit$err_mod, "const"), TRUE, - "standardized"), ...) - -plot_res(fit, sep_obs = FALSE, show_errmin = sep_obs, +\method{plot}{mkinfit}( + x, + fit = x, + obs_vars = names(fit$mkinmod$map), + xlab = "Time", + ylab = "Observed", + xlim = range(fit$data$time), + ylim = "default", + col_obs = 1:length(obs_vars), + pch_obs = col_obs, + lty_obs = rep(1, length(obs_vars)), + add = FALSE, + legend = !add, + show_residuals = FALSE, + show_errplot = FALSE, + maxabs = "auto", + sep_obs = FALSE, + rel.height.middle = 0.9, + row_layout = FALSE, + lpos = "topright", + inset = c(0.05, 0.05), + show_errmin = FALSE, + errmin_digits = 3, + frame = TRUE, + ... +) + +plot_sep( + fit, + show_errmin = TRUE, + show_residuals = ifelse(identical(fit$err_mod, "const"), TRUE, "standardized"), + ... +) + +plot_res( + fit, + sep_obs = FALSE, + show_errmin = sep_obs, standardized = ifelse(identical(fit$err_mod, "const"), FALSE, TRUE), - ...) + ... +) plot_err(fit, sep_obs = FALSE, show_errmin = sep_obs, ...) } diff --git a/man/plot.mmkin.Rd b/man/plot.mmkin.Rd index 605e458e..f14e0362 100644 --- a/man/plot.mmkin.Rd +++ b/man/plot.mmkin.Rd @@ -5,10 +5,19 @@ \title{Plot model fits (observed and fitted) and the residuals for a row or column of an mmkin object} \usage{ -\method{plot}{mmkin}(x, main = "auto", legends = 1, - resplot = c("time", "errmod"), show_errmin = TRUE, - errmin_var = "All data", errmin_digits = 3, cex = 0.7, - rel.height.middle = 0.9, ymax = "auto", ...) +\method{plot}{mmkin}( + x, + main = "auto", + legends = 1, + resplot = c("time", "errmod"), + show_errmin = TRUE, + errmin_var = "All data", + errmin_digits = 3, + cex = 0.7, + rel.height.middle = 0.9, + ymax = "auto", + ... +) } \arguments{ \item{x}{An object of class \code{\link{mmkin}}, with either one row or one diff --git a/man/summary.mkinfit.Rd b/man/summary.mkinfit.Rd index fcc1295f..fabe31d0 100644 --- a/man/summary.mkinfit.Rd +++ b/man/summary.mkinfit.Rd @@ -5,11 +5,9 @@ \alias{print.summary.mkinfit} \title{Summary method for class "mkinfit"} \usage{ -\method{summary}{mkinfit}(object, data = TRUE, distimes = TRUE, - alpha = 0.05, ...) +\method{summary}{mkinfit}(object, data = TRUE, distimes = TRUE, alpha = 0.05, ...) -\method{print}{summary.mkinfit}(x, digits = max(3, getOption("digits") - - 3), ...) +\method{print}{summary.mkinfit}(x, digits = max(3, getOption("digits") - 3), ...) } \arguments{ \item{object}{an object of class \code{\link{mkinfit}}.} diff --git a/man/transform_odeparms.Rd b/man/transform_odeparms.Rd index 5c8c90ba..5257fe12 100644 --- a/man/transform_odeparms.Rd +++ b/man/transform_odeparms.Rd @@ -5,11 +5,19 @@ \alias{backtransform_odeparms} \title{Functions to transform and backtransform kinetic parameters for fitting} \usage{ -transform_odeparms(parms, mkinmod, transform_rates = TRUE, - transform_fractions = TRUE) +transform_odeparms( + parms, + mkinmod, + transform_rates = TRUE, + transform_fractions = TRUE +) -backtransform_odeparms(transparms, mkinmod, transform_rates = TRUE, - transform_fractions = TRUE) +backtransform_odeparms( + transparms, + mkinmod, + transform_rates = TRUE, + transform_fractions = TRUE +) } \arguments{ \item{parms}{Parameters of kinetic models as used in the differential -- cgit v1.2.1 From 575fcacaa33076de97f41a79afb37efb97ca82e0 Mon Sep 17 00:00:00 2001 From: Johannes Ranke Date: Mon, 30 Mar 2020 21:43:10 +0200 Subject: Static documentation rebuilt by pkgdown --- DESCRIPTION | 2 +- NEWS.md | 6 +- docs/news/index.html | 15 ++++- docs/reference/CAKE_export.html | 23 ++++--- docs/reference/add_err-1.png | Bin 89500 -> 89498 bytes docs/reference/add_err.html | 14 ++++- docs/reference/aw.html | 2 +- docs/reference/confint.mkinfit.html | 107 ++++++++++++++------------------ docs/reference/loftest-3.png | Bin 65409 -> 65397 bytes docs/reference/loftest.html | 2 +- docs/reference/lrtest.mkinfit.html | 4 +- docs/reference/mkinds.html | 31 +++++++++- docs/reference/mkinerrplot-1.png | Bin 35440 -> 35440 bytes docs/reference/mkinerrplot.html | 21 +++++-- docs/reference/mkinfit.html | 109 +++++++++++++++++++-------------- docs/reference/mkinmod.html | 13 ++-- docs/reference/mkinpredict.html | 78 +++++++++++++++-------- docs/reference/mkinresplot.html | 20 ++++-- docs/reference/mmkin-2.png | Bin 88000 -> 88002 bytes docs/reference/mmkin-3.png | Bin 85371 -> 85375 bytes docs/reference/mmkin.html | 23 ++++--- docs/reference/plot.mkinfit.html | 57 ++++++++++++----- docs/reference/plot.mmkin.html | 19 ++++-- docs/reference/summary.mkinfit.html | 24 ++++---- docs/reference/transform_odeparms.html | 20 ++++-- 25 files changed, 371 insertions(+), 219 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index bd6a0a09..f631a541 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -2,7 +2,7 @@ Package: mkin Type: Package Title: Kinetic Evaluation of Chemical Degradation Data Version: 0.9.49.9 -Date: 2020-01-09 +Date: 2020-03-20 Authors@R: c(person("Johannes", "Ranke", role = c("aut", "cre", "cph"), email = "jranke@uni-bremen.de", comment = c(ORCID = "0000-0003-4371-6538")), diff --git a/NEWS.md b/NEWS.md index 622a82b0..63cf18bc 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,8 @@ -# mkin 0.9.49.8 (unreleased) +# mkin 0.9.49.9 (unreleased) + +- 'mkinmod': Do not check for gcc using Sys.which('gcc') any more, as this will often fail even if Rtools are installed + +# mkin 0.9.49.8 (2020-01-09) - 'aw': Generic function for calculating Akaike weights, methods for mkinfit objects and mmkin columns diff --git a/docs/news/index.html b/docs/news/index.html index 3327e48f..b7c814ce 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -129,9 +129,17 @@ -
+

-mkin 0.9.49.8 (unreleased) Unreleased +mkin 0.9.49.9 (unreleased) Unreleased +

+
    +
  • ‘mkinmod’: Do not check for gcc using Sys.which(‘gcc’) any more, as this will often fail even if Rtools are installed
  • +
+
+
+

+mkin 0.9.49.8 (2020-01-09) 2020-01-09

  • ‘aw’: Generic function for calculating Akaike weights, methods for mkinfit objects and mmkin columns

  • @@ -747,7 +755,8 @@

    Contents

    @@ -138,12 +138,21 @@ specified as well." /> specified as well.

-
CAKE_export(ds, map = c(parent = "Parent"), links = NA,
-  filename = "CAKE_export.csf", path = ".", overwrite = FALSE,
-  study = "Codlemone aerobic soil degradation", description = "",
-  time_unit = "days", res_unit = "% AR",
-  comment = "Created using mkin::CAKE_export", date = Sys.Date(),
-  optimiser = "IRLS")
+
CAKE_export(
+  ds,
+  map = c(parent = "Parent"),
+  links = NA,
+  filename = "CAKE_export.csf",
+  path = ".",
+  overwrite = FALSE,
+  study = "Codlemone aerobic soil degradation",
+  description = "",
+  time_unit = "days",
+  res_unit = "% AR",
+  comment = "Created using mkin::CAKE_export",
+  date = Sys.Date(),
+  optimiser = "IRLS"
+)

Arguments

diff --git a/docs/reference/add_err-1.png b/docs/reference/add_err-1.png index fb369053..3018ff7f 100644 Binary files a/docs/reference/add_err-1.png and b/docs/reference/add_err-1.png differ diff --git a/docs/reference/add_err.html b/docs/reference/add_err.html index 67789694..ab499a19 100644 --- a/docs/reference/add_err.html +++ b/docs/reference/add_err.html @@ -71,7 +71,7 @@ may depend on the predicted value and is specified as a standard deviation." /> mkin - 0.9.49.6 + 0.9.49.9 @@ -140,8 +140,16 @@ degradation model using mkinpredict. may depend on the predicted value and is specified as a standard deviation.

-
add_err(prediction, sdfunc, secondary = c("M1", "M2"), n = 1000,
-  LOD = 0.1, reps = 2, digits = 1, seed = NA)
+
add_err(
+  prediction,
+  sdfunc,
+  secondary = c("M1", "M2"),
+  n = 1000,
+  LOD = 0.1,
+  reps = 2,
+  digits = 1,
+  seed = NA
+)

Arguments

diff --git a/docs/reference/aw.html b/docs/reference/aw.html index 22201229..0b37847c 100644 --- a/docs/reference/aw.html +++ b/docs/reference/aw.html @@ -71,7 +71,7 @@ by Burnham and Anderson (2004)." /> mkin - 0.9.49.8 + 0.9.49.9 diff --git a/docs/reference/confint.mkinfit.html b/docs/reference/confint.mkinfit.html index ea69c3bb..1dd6288b 100644 --- a/docs/reference/confint.mkinfit.html +++ b/docs/reference/confint.mkinfit.html @@ -76,7 +76,7 @@ method of Venzon and Moolgavkar (1988)." /> mkin - 0.9.49.8 + 0.9.49.9 @@ -151,10 +151,19 @@ method of Venzon and Moolgavkar (1988).

# S3 method for mkinfit
-confint(object, parm, level = 0.95, alpha = 1 -
-  level, cutoff, method = c("quadratic", "profile"),
-  transformed = TRUE, backtransform = TRUE,
-  cores = round(detectCores()/2), quiet = FALSE, ...)
+confint( + object, + parm, + level=0.95, + alpha=1 - level, + cutoff, + method=c("quadratic", "profile"), + transformed=TRUE, + backtransform=TRUE, + cores=round(detectCores()/2), + quiet=FALSE, + ... +)

Arguments

@@ -253,52 +262,30 @@ On Windows machines, cores > 1 is currently not supported.

SFO_SFO.ff<-mkinmod(parent=mkinsub("SFO", "m1"), m1=mkinsub("SFO"), use_of_ff="max", quiet=TRUE) f_d_1<-mkinfit(SFO_SFO, subset(FOCUS_2006_D, value!=0), quiet=TRUE) -system.time(ci_profile<-confint(f_d_1, method="profile", cores=1, quiet=TRUE))
#> User System verstrichen -#> 51.058 0.000 51.088
# Using more cores does not save much time here, as parent_0 takes up most of the time +system.time(ci_profile <- confint(f_d_1, method = "profile", cores = 1, quiet = TRUE))
#> Error in mkinpredict.mkinmod(mkinmod, parms, odeini, outtimes, solution_type = solution_type, use_compiled = use_compiled, method.ode = method.ode, atol = atol, rtol = rtol, ...): Differential equations were not integrated for all output times because +#> NaN values occurred in output from ode()
#> Timing stopped at: 11.39 0 11.4
# Using more cores does not save much time here, as parent_0 takes up most of the time # If we additionally exclude parent_0 (the confidence of which is often of # minor interest), we get a nice performance improvement from about 50 # seconds to about 12 seconds if we use at least four cores system.time(ci_profile_no_parent_0 <- confint(f_d_1, method = "profile", c("k_parent_sink", "k_parent_m1", "k_m1_sink", "sigma"), cores = n_cores))
#> Profiling the likelihood
#> User System verstrichen -#> 0.005 0.004 11.349
ci_profile
#> 2.5% 97.5% -#> parent_0 96.456003650 1.027703e+02 -#> k_parent_sink 0.040762501 5.549764e-02 -#> k_parent_m1 0.046786482 5.500879e-02 -#> k_m1_sink 0.003892605 6.702778e-03 -#> sigma 2.535612399 3.985263e+00
ci_quadratic_transformed <- confint(f_d_1, method = "quadratic") +#> 20.058 0.122 11.784
ci_profile
#> Error in eval(expr, envir, enclos): Objekt 'ci_profile' nicht gefunden
ci_quadratic_transformed <- confint(f_d_1, method = "quadratic") ci_quadratic_transformed
#> 2.5% 97.5% -#> parent_0 96.403841649 1.027931e+02 +#> parent_0 96.403841641 1.027931e+02 #> k_parent_sink 0.041033378 5.596269e-02 #> k_parent_m1 0.046777902 5.511931e-02 #> k_m1_sink 0.004012217 6.897547e-03 #> sigma 2.396089689 3.854918e+00
ci_quadratic_untransformed <- confint(f_d_1, method = "quadratic", transformed = FALSE) ci_quadratic_untransformed
#> 2.5% 97.5% -#> parent_0 96.403841653 102.79312450 +#> parent_0 96.403841648 102.79312450 #> k_parent_sink 0.040485331 0.05535491 -#> k_parent_m1 0.046611581 0.05494364 +#> k_parent_m1 0.046611582 0.05494364 #> k_m1_sink 0.003835483 0.00668582 #> sigma 2.396089689 3.85491806
# Against the expectation based on Bates and Watts (1988), the confidence # intervals based on the internal parameter transformation are less # congruent with the likelihood based intervals. Note the superiority of the # interval based on the untransformed fit for k_m1_sink -rel_diffs_transformed <- abs((ci_quadratic_transformed - ci_profile)/ci_profile) -rel_diffs_untransformed <- abs((ci_quadratic_untransformed - ci_profile)/ci_profile) -rel_diffs_transformed < rel_diffs_untransformed
#> 2.5% 97.5% -#> parent_0 FALSE FALSE -#> k_parent_sink TRUE FALSE -#> k_parent_m1 TRUE FALSE -#> k_m1_sink FALSE FALSE -#> sigma FALSE FALSE
signif(rel_diffs_transformed, 3)
#> 2.5% 97.5% -#> parent_0 0.000541 0.000222 -#> k_parent_sink 0.006650 0.008380 -#> k_parent_m1 0.000183 0.002010 -#> k_m1_sink 0.030700 0.029100 -#> sigma 0.055000 0.032700
signif(rel_diffs_untransformed, 3)
#> 2.5% 97.5% -#> parent_0 0.000541 0.000222 -#> k_parent_sink 0.006800 0.002570 -#> k_parent_m1 0.003740 0.001180 -#> k_m1_sink 0.014700 0.002530 -#> sigma 0.055000 0.032700
+rel_diffs_transformed <- abs((ci_quadratic_transformed - ci_profile)/ci_profile)
#> Error in eval(expr, envir, enclos): Objekt 'ci_profile' nicht gefunden
rel_diffs_untransformed <- abs((ci_quadratic_untransformed - ci_profile)/ci_profile)
#> Error in eval(expr, envir, enclos): Objekt 'ci_profile' nicht gefunden
rel_diffs_transformed < rel_diffs_untransformed
#> Error in eval(expr, envir, enclos): Objekt 'rel_diffs_transformed' nicht gefunden
signif(rel_diffs_transformed, 3)
#> Error in eval(expr, envir, enclos): Objekt 'rel_diffs_transformed' nicht gefunden
signif(rel_diffs_untransformed, 3)
#> Error in eval(expr, envir, enclos): Objekt 'rel_diffs_untransformed' nicht gefunden
# Investigate a case with formation fractions f_d_2 <- mkinfit(SFO_SFO.ff, subset(FOCUS_2006_D, value != 0), quiet = TRUE) @@ -309,16 +296,16 @@ On Windows machines, cores > 1 is currently not supported.

#> f_parent_to_m1 0.471328495 5.611550e-01 #> sigma 2.535612399 3.985263e+00
ci_quadratic_transformed_ff <- confint(f_d_2, method = "quadratic") ci_quadratic_transformed_ff
#> 2.5% 97.5% -#> parent_0 96.403840123 1.027931e+02 -#> k_parent 0.090823791 1.072543e-01 +#> parent_0 96.403839992 1.027931e+02 +#> k_parent 0.090823790 1.072543e-01 #> k_m1 0.004012216 6.897547e-03 -#> f_parent_to_m1 0.469118710 5.595960e-01 +#> f_parent_to_m1 0.469118711 5.595960e-01 #> sigma 2.396089689 3.854918e+00
ci_quadratic_untransformed_ff <- confint(f_d_2, method = "quadratic", transformed = FALSE) ci_quadratic_untransformed_ff
#> 2.5% 97.5% -#> parent_0 96.403840057 1.027931e+02 -#> k_parent 0.090491932 1.069035e-01 +#> parent_0 96.403839944 1.027931e+02 +#> k_parent 0.090491931 1.069035e-01 #> k_m1 0.003835483 6.685819e-03 -#> f_parent_to_m1 0.469113361 5.598386e-01 +#> f_parent_to_m1 0.469113362 5.598386e-01 #> sigma 2.396089689 3.854918e+00
rel_diffs_transformed_ff <- abs((ci_quadratic_transformed_ff - ci_profile_ff)/ci_profile_ff) rel_diffs_untransformed_ff <- abs((ci_quadratic_untransformed_ff - ci_profile_ff)/ci_profile_ff) # While the confidence interval for the parent rate constant is closer to @@ -330,16 +317,16 @@ On Windows machines, cores > 1 is currently not supported.

#> k_parent TRUE TRUE #> k_m1 FALSE FALSE #> f_parent_to_m1 TRUE FALSE -#> sigma FALSE TRUE
rel_diffs_transformed_ff
#> 2.5% 97.5% -#> parent_0 0.0005408012 0.0002217857 -#> k_parent 0.0009596303 0.0009003981 -#> k_m1 0.0307277425 0.0290579163 -#> f_parent_to_m1 0.0046884178 0.0027782643 +#> sigma FALSE FALSE
rel_diffs_transformed_ff
#> 2.5% 97.5% +#> parent_0 0.0005408026 0.0002217846 +#> k_parent 0.0009596414 0.0009003877 +#> k_m1 0.0307277403 0.0290579212 +#> f_parent_to_m1 0.0046884168 0.0027782604 #> sigma 0.0550252516 0.0327066836
rel_diffs_untransformed_ff
#> 2.5% 97.5% -#> parent_0 0.0005408019 0.0002217863 -#> k_parent 0.0046099989 0.0023730118 -#> k_m1 0.0146746451 0.0025300990 -#> f_parent_to_m1 0.0046997668 0.0023460293 +#> parent_0 0.0005408031 0.0002217851 +#> k_parent 0.0046100089 0.0023730230 +#> k_m1 0.0146746442 0.0025300972 +#> f_parent_to_m1 0.0046997642 0.0023460268 #> sigma 0.0550252516 0.0327066836
# The profiling for the following fit does not finish in a reasonable time, # therefore we use the quadratic approximation @@ -351,17 +338,17 @@ On Windows machines, cores > 1 is currently not supported.

f_tc_2 <- mkinfit(m_synth_DFOP_par, DFOP_par_c, error_model = "tc", error_model_algorithm = "direct", quiet = TRUE) confint(f_tc_2, method = "quadratic")
#> 2.5% 97.5% -#> parent_0 94.596183241 106.19937044 -#> k_M1 0.037605436 0.04490758 -#> k_M2 0.008568746 0.01087675 -#> f_parent_to_M1 0.021464277 0.62023879 -#> f_parent_to_M2 0.015166876 0.37975352 -#> k1 0.273897622 0.33388081 -#> k2 0.018614564 0.02250380 -#> g 0.671943572 0.73583247 -#> sigma_low 0.251284138 0.83992136 -#> rsd_high 0.040410998 0.07661999
confint(f_tc_2, "parent_0", method = "quadratic")
#> 2.5% 97.5% -#> parent_0 94.59618 106.1994
# } +#> parent_0 94.596218141 106.19934683 +#> k_M1 0.037605440 0.04490756 +#> k_M2 0.008568747 0.01087674 +#> f_parent_to_M1 0.021466788 0.62023878 +#> f_parent_to_M2 0.015168650 0.37975352 +#> k1 0.273897581 0.33388066 +#> k2 0.018614556 0.02250379 +#> g 0.671943831 0.73583255 +#> sigma_low 0.251283700 0.83992071 +#> rsd_high 0.040411017 0.07662005
confint(f_tc_2, "parent_0", method = "quadratic")
#> 2.5% 97.5% +#> parent_0 94.59622 106.1993
# }
diff --git a/docs/reference/lrtest.mkinfit.html b/docs/reference/lrtest.mkinfit.html index 70157db9..6861b747 100644 --- a/docs/reference/lrtest.mkinfit.html +++ b/docs/reference/lrtest.mkinfit.html @@ -73,7 +73,7 @@ and can be expressed by fixing the parameters of the other." /> mkin - 0.9.49.8 + 0.9.49.9 @@ -205,7 +205,7 @@ lower number of fitted parameters (null hypothesis).

#lrtest(dfop_fit, error_model = "tc")#lrtest(dfop_fit, fixed_parms = c(k2 = 0)) -# However, this equivalent syntax works for static help pages +# However, this equivalent syntax also works for static help pageslrtest(dfop_fit, update(dfop_fit, error_model="tc"))
#> Likelihood ratio test #> #> Model 1: DFOP with error model tc diff --git a/docs/reference/mkinds.html b/docs/reference/mkinds.html index 386c00d7..c1cdcf99 100644 --- a/docs/reference/mkinds.html +++ b/docs/reference/mkinds.html @@ -69,7 +69,7 @@ mkin - 0.9.49.6 + 0.9.49.9
@@ -136,7 +136,6 @@

A dataset class for mkin

-
mkinds

Format

@@ -164,6 +163,33 @@ value in order to be compatible with mkinfit

+

Methods

+ + +

Public methods

+ + +


+

Method new()

+ +

Usage

+

mkinds$new(title = "", data, time_unit = NA, unit = NA)

+ +


+

Method clone()

+

The objects of this class are cloneable with this method.

Usage

+

mkinds$clone(deep = FALSE)

+ +

Arguments

+

+
deep

Whether to make a deep clone.

+ +

+ +

Examples

@@ -174,6 +200,7 @@ value in order to be compatible with mkinfit

diff --git a/docs/reference/mkinerrplot-1.png b/docs/reference/mkinerrplot-1.png index 476edc49..46a80308 100644 Binary files a/docs/reference/mkinerrplot-1.png and b/docs/reference/mkinerrplot-1.png differ diff --git a/docs/reference/mkinerrplot.html b/docs/reference/mkinerrplot.html index 079a6708..47f48b72 100644 --- a/docs/reference/mkinerrplot.html +++ b/docs/reference/mkinerrplot.html @@ -73,7 +73,7 @@ using the argument show_errplot = TRUE." /> mkin - 0.9.49.6 + 0.9.49.9
@@ -144,11 +144,20 @@ and this error model plot can be obtained with show_errplot = TRUE.

-
mkinerrplot(object, obs_vars = names(object$mkinmod$map), xlim = c(0,
-  1.1 * max(object$data$predicted)), xlab = "Predicted",
-  ylab = "Squared residual", maxy = "auto", legend = TRUE,
-  lpos = "topright", col_obs = "auto", pch_obs = "auto",
-  frame = TRUE, ...)
+
mkinerrplot(
+  object,
+  obs_vars = names(object$mkinmod$map),
+  xlim = c(0, 1.1 * max(object$data$predicted)),
+  xlab = "Predicted",
+  ylab = "Squared residual",
+  maxy = "auto",
+  legend = TRUE,
+  lpos = "topright",
+  col_obs = "auto",
+  pch_obs = "auto",
+  frame = TRUE,
+  ...
+)

Arguments

diff --git a/docs/reference/mkinfit.html b/docs/reference/mkinfit.html index 7ee73f15..ffc8d52b 100644 --- a/docs/reference/mkinfit.html +++ b/docs/reference/mkinfit.html @@ -75,7 +75,7 @@ likelihood function." /> mkin - 0.9.49.6 + 0.9.49.9 @@ -148,18 +148,33 @@ degradation model parameters, as both of them are arguments of the likelihood function.

-
mkinfit(mkinmod, observed, parms.ini = "auto", state.ini = "auto",
-  err.ini = "auto", fixed_parms = NULL,
-  fixed_initials = names(mkinmod$diffs)[-1], from_max_mean = FALSE,
+    
mkinfit(
+  mkinmod,
+  observed,
+  parms.ini = "auto",
+  state.ini = "auto",
+  err.ini = "auto",
+  fixed_parms = NULL,
+  fixed_initials = names(mkinmod$diffs)[-1],
+  from_max_mean = FALSE,
   solution_type = c("auto", "analytical", "eigen", "deSolve"),
-  method.ode = "lsoda", use_compiled = "auto",
+  method.ode = "lsoda",
+  use_compiled = "auto",
   control = list(eval.max = 300, iter.max = 200),
-  transform_rates = TRUE, transform_fractions = TRUE, quiet = FALSE,
-  atol = 1e-08, rtol = 1e-10, n.outtimes = 100,
+  transform_rates = TRUE,
+  transform_fractions = TRUE,
+  quiet = FALSE,
+  atol = 1e-08,
+  rtol = 1e-10,
+  n.outtimes = 100,
   error_model = c("const", "obs", "tc"),
-  error_model_algorithm = c("auto", "d_3", "direct", "twostep",
-  "threestep", "fourstep", "IRLS", "OLS"), reweight.tol = 1e-08,
-  reweight.max.iter = 10, trace_parms = FALSE, ...)
+ error_model_algorithm = c("auto", "d_3", "direct", "twostep", "threestep", "fourstep", + "IRLS", "OLS"), + reweight.tol = 1e-08, + reweight.max.iter = 10, + trace_parms = FALSE, + ... +)

Arguments

@@ -400,17 +415,17 @@ estimators.

# Use shorthand notation for parent only degradation fit <- mkinfit("FOMC", FOCUS_2006_C, quiet = TRUE) -summary(fit)
#> mkin version used for fitting: 0.9.49.6 -#> R version used for fitting: 3.6.1 -#> Date of fit: Fri Nov 1 10:08:21 2019 -#> Date of summary: Fri Nov 1 10:08:21 2019 +summary(fit)
#> mkin version used for fitting: 0.9.49.9 +#> R version used for fitting: 3.6.3 +#> Date of fit: Mon Mar 30 21:41:20 2020 +#> Date of summary: Mon Mar 30 21:41:20 2020 #> #> Equations: #> d_parent/dt = - (alpha/beta) * 1/((time/beta) + 1) * parent #> #> Model predictions using solution type analytical #> -#> Fitted using 222 model solutions performed in 0.456 s +#> Fitted using 222 model solutions performed in 0.463 s #> #> Error model: Constant variance #> @@ -440,10 +455,10 @@ estimators.

#> #> Parameter correlation: #> parent_0 log_alpha log_beta sigma -#> parent_0 1.000e+00 -1.565e-01 -3.142e-01 4.770e-08 -#> log_alpha -1.565e-01 1.000e+00 9.564e-01 9.974e-08 -#> log_beta -3.142e-01 9.564e-01 1.000e+00 8.468e-08 -#> sigma 4.770e-08 9.974e-08 8.468e-08 1.000e+00 +#> parent_0 1.000e+00 -1.565e-01 -3.142e-01 4.758e-08 +#> log_alpha -1.565e-01 1.000e+00 9.564e-01 1.007e-07 +#> log_beta -3.142e-01 9.564e-01 1.000e+00 8.568e-08 +#> sigma 4.758e-08 1.007e-07 8.568e-08 1.000e+00 #> #> Backtransformed parameters: #> Confidence intervals for internally transformed parameters are asymmetric. @@ -482,7 +497,7 @@ estimators.

m1 = mkinsub("SFO"))
#> Successfully compiled differential equation model from auto-generated C code.
# Fit the model to the FOCUS example dataset D using defaults print(system.time(fit <- mkinfit(SFO_SFO, FOCUS_2006_D, solution_type = "eigen", quiet = TRUE)))
#> Warning: Observations with value of zero were removed from the data
#> User System verstrichen -#> 1.488 0.000 1.491
coef(fit)
#> NULL
#> $ff +#> 1.526 0.000 1.530
coef(fit)
#> NULL
#> $ff #> parent_sink parent_m1 m1_sink #> 0.485524 0.514476 1.000000 #> @@ -533,9 +548,9 @@ estimators.

#> Sum of squared residuals at call 82: 373.1711 #> Sum of squared residuals at call 84: 373.1711 #> Sum of squared residuals at call 87: 372.6445 -#> Sum of squared residuals at call 88: 372.1615 -#> Sum of squared residuals at call 90: 372.1615 -#> Sum of squared residuals at call 91: 372.1615 +#> Sum of squared residuals at call 88: 372.1614 +#> Sum of squared residuals at call 90: 372.1614 +#> Sum of squared residuals at call 91: 372.1614 #> Sum of squared residuals at call 94: 371.6464 #> Sum of squared residuals at call 99: 371.4299 #> Sum of squared residuals at call 101: 371.4299 @@ -555,7 +570,7 @@ estimators.

#> Sum of squared residuals at call 126: 371.2134 #> Sum of squared residuals at call 135: 371.2134 #> Negative log-likelihood at call 145: 97.22429
#> Optimisation successfully terminated.
#> User System verstrichen -#> 1.058 0.000 1.059
coef(fit.deSolve)
#> NULL
endpoints(fit.deSolve)
#> $ff +#> 1.083 0.000 1.084
coef(fit.deSolve)
#> NULL
endpoints(fit.deSolve)
#> $ff #> parent_sink parent_m1 m1_sink #> 0.485524 0.514476 1.000000 #> @@ -589,10 +604,10 @@ estimators.

# \dontrun{ # Weighted fits, including IRLS SFO_SFO.ff <- mkinmod(parent = mkinsub("SFO", "m1"), - m1 = mkinsub("SFO"), use_of_ff = "max")
#> Successfully compiled differential equation model from auto-generated C code.
f.noweight <- mkinfit(SFO_SFO.ff, FOCUS_2006_D, quiet = TRUE)
#> Warning: Observations with value of zero were removed from the data
summary(f.noweight)
#> mkin version used for fitting: 0.9.49.6 -#> R version used for fitting: 3.6.1 -#> Date of fit: Fri Nov 1 10:08:36 2019 -#> Date of summary: Fri Nov 1 10:08:36 2019 + m1 = mkinsub("SFO"), use_of_ff = "max")
#> Successfully compiled differential equation model from auto-generated C code.
f.noweight <- mkinfit(SFO_SFO.ff, FOCUS_2006_D, quiet = TRUE)
#> Warning: Observations with value of zero were removed from the data
summary(f.noweight)
#> mkin version used for fitting: 0.9.49.9 +#> R version used for fitting: 3.6.3 +#> Date of fit: Mon Mar 30 21:41:36 2020 +#> Date of summary: Mon Mar 30 21:41:36 2020 #> #> Equations: #> d_parent/dt = - k_parent * parent @@ -600,7 +615,7 @@ estimators.

#> #> Model predictions using solution type deSolve #> -#> Fitted using 421 model solutions performed in 1.083 s +#> Fitted using 422 model solutions performed in 1.144 s #> #> Error model: Constant variance #> @@ -634,11 +649,11 @@ estimators.

#> #> Parameter correlation: #> parent_0 log_k_parent log_k_m1 f_parent_ilr_1 sigma -#> parent_0 1.000e+00 5.174e-01 -1.688e-01 -5.471e-01 -2.265e-07 -#> log_k_parent 5.174e-01 1.000e+00 -3.263e-01 -5.426e-01 3.785e-07 -#> log_k_m1 -1.688e-01 -3.263e-01 1.000e+00 7.478e-01 -1.386e-07 -#> f_parent_ilr_1 -5.471e-01 -5.426e-01 7.478e-01 1.000e+00 -3.641e-08 -#> sigma -2.265e-07 3.785e-07 -1.386e-07 -3.641e-08 1.000e+00 +#> parent_0 1.000e+00 5.174e-01 -1.688e-01 -5.471e-01 -2.443e-07 +#> log_k_parent 5.174e-01 1.000e+00 -3.263e-01 -5.426e-01 3.181e-07 +#> log_k_m1 -1.688e-01 -3.263e-01 1.000e+00 7.478e-01 -1.369e-07 +#> f_parent_ilr_1 -5.471e-01 -5.426e-01 7.478e-01 1.000e+00 -2.287e-08 +#> sigma -2.443e-07 3.181e-07 -1.369e-07 -2.287e-08 1.000e+00 #> #> Backtransformed parameters: #> Confidence intervals for internally transformed parameters are asymmetric. @@ -706,10 +721,10 @@ estimators.

#> 100 m1 31.04 31.98163 -9.416e-01 #> 100 m1 33.13 31.98163 1.148e+00 #> 120 m1 25.15 28.78984 -3.640e+00 -#> 120 m1 33.31 28.78984 4.520e+00
f.obs <- mkinfit(SFO_SFO.ff, FOCUS_2006_D, error_model = "obs", quiet = TRUE)
#> Warning: Observations with value of zero were removed from the data
summary(f.obs)
#> mkin version used for fitting: 0.9.49.6 -#> R version used for fitting: 3.6.1 -#> Date of fit: Fri Nov 1 10:08:39 2019 -#> Date of summary: Fri Nov 1 10:08:39 2019 +#> 120 m1 33.31 28.78984 4.520e+00
f.obs <- mkinfit(SFO_SFO.ff, FOCUS_2006_D, error_model = "obs", quiet = TRUE)
#> Warning: Observations with value of zero were removed from the data
summary(f.obs)
#> mkin version used for fitting: 0.9.49.9 +#> R version used for fitting: 3.6.3 +#> Date of fit: Mon Mar 30 21:41:39 2020 +#> Date of summary: Mon Mar 30 21:41:39 2020 #> #> Equations: #> d_parent/dt = - k_parent * parent @@ -717,7 +732,7 @@ estimators.

#> #> Model predictions using solution type deSolve #> -#> Fitted using 978 model solutions performed in 2.553 s +#> Fitted using 979 model solutions performed in 2.576 s #> #> Error model: Variance unique to each observed variable #> @@ -838,10 +853,10 @@ estimators.

#> 100 m1 31.04 31.98773 -9.477e-01 #> 100 m1 33.13 31.98773 1.142e+00 #> 120 m1 25.15 28.80429 -3.654e+00 -#> 120 m1 33.31 28.80429 4.506e+00
f.tc <- mkinfit(SFO_SFO.ff, FOCUS_2006_D, error_model = "tc", quiet = TRUE)
#> Warning: Observations with value of zero were removed from the data
summary(f.tc)
#> mkin version used for fitting: 0.9.49.6 -#> R version used for fitting: 3.6.1 -#> Date of fit: Fri Nov 1 10:08:48 2019 -#> Date of summary: Fri Nov 1 10:08:48 2019 +#> 120 m1 33.31 28.80429 4.506e+00
f.tc <- mkinfit(SFO_SFO.ff, FOCUS_2006_D, error_model = "tc", quiet = TRUE)
#> Warning: Observations with value of zero were removed from the data
summary(f.tc)
#> mkin version used for fitting: 0.9.49.9 +#> R version used for fitting: 3.6.3 +#> Date of fit: Mon Mar 30 21:41:50 2020 +#> Date of summary: Mon Mar 30 21:41:50 2020 #> #> Equations: #> d_parent/dt = - k_parent * parent @@ -849,12 +864,12 @@ estimators.

#> #> Model predictions using solution type deSolve #> -#> Fitted using 2289 model solutions performed in 9.253 s +#> Fitted using 2552 model solutions performed in 10.593 s #> #> Error model: Two-component variance function #> #> Error model algorithm: d_3 -#> Direct fitting and three-step fitting yield approximately the same likelihood +#> Three-step fitting yielded a higher likelihood than direct fitting #> #> Starting values for parameters to be optimised: #> value type @@ -960,8 +975,8 @@ estimators.

#> 50 m1 40.01 41.34199 -1.331985 #> 75 m1 40.09 36.61471 3.475295 #> 75 m1 33.85 36.61471 -2.764705 -#> 100 m1 31.04 32.20082 -1.160823 -#> 100 m1 33.13 32.20082 0.929177 +#> 100 m1 31.04 32.20082 -1.160824 +#> 100 m1 33.13 32.20082 0.929176 #> 120 m1 25.15 29.04130 -3.891304 #> 120 m1 33.31 29.04130 4.268696
# } diff --git a/docs/reference/mkinmod.html b/docs/reference/mkinmod.html index 317ffe5f..b25f2da3 100644 --- a/docs/reference/mkinmod.html +++ b/docs/reference/mkinmod.html @@ -72,7 +72,7 @@ list of lists can be given in the speclist argument." /> mkin - 0.9.49.6 + 0.9.49.9
@@ -142,8 +142,13 @@ to other observed compartments. Instead of specifying several expressions, a list of lists can be given in the speclist argument.

-
mkinmod(..., use_of_ff = "min", speclist = NULL, quiet = FALSE,
-  verbose = FALSE)
+
mkinmod(
+  ...,
+  use_of_ff = "min",
+  speclist = NULL,
+  quiet = FALSE,
+  verbose = FALSE
+)

Arguments

@@ -239,7 +244,7 @@ in the FOCUS and NAFTA guidance documents are used.

SFO_SFO<-mkinmod( parent=mkinsub("SFO", "m1"), m1=mkinsub("SFO"), verbose=TRUE)
#> Compilation argument: -#> /usr/lib/R/bin/R CMD SHLIB file12cd48616f1.c 2> file12cd48616f1.c.err.txt +#> /usr/lib/R/bin/R CMD SHLIB file414965c335f6.c 2> file414965c335f6.c.err.txt #> Program source: #> 1: #include <R.h> #> 2: diff --git a/docs/reference/mkinpredict.html b/docs/reference/mkinpredict.html index 0eca973c..fe5bc975 100644 --- a/docs/reference/mkinpredict.html +++ b/docs/reference/mkinpredict.html @@ -71,7 +71,7 @@ kinetic parameters and initial values for the state variables." /> mkin - 0.9.49.6 + 0.9.49.9
@@ -140,24 +140,49 @@ kinetic model as specified by mkinmod, u kinetic parameters and initial values for the state variables.

-
mkinpredict(x, odeparms, odeini, outtimes = seq(0, 120, by = 0.1),
-  solution_type = "deSolve", use_compiled = "auto",
-  method.ode = "lsoda", atol = 1e-08, rtol = 1e-10,
-  map_output = TRUE, ...)
+    
mkinpredict(
+  x,
+  odeparms,
+  odeini,
+  outtimes = seq(0, 120, by = 0.1),
+  solution_type = "deSolve",
+  use_compiled = "auto",
+  method.ode = "lsoda",
+  atol = 1e-08,
+  rtol = 1e-10,
+  map_output = TRUE,
+  ...
+)
 
 # S3 method for mkinmod
-mkinpredict(x, odeparms = c(k_parent_sink = 0.1),
-  odeini = c(parent = 100), outtimes = seq(0, 120, by = 0.1),
-  solution_type = "deSolve", use_compiled = "auto",
-  method.ode = "lsoda", atol = 1e-08, rtol = 1e-10,
-  map_output = TRUE, ...)
+mkinpredict(
+  x,
+  odeparms = c(k_parent_sink = 0.1),
+  odeini = c(parent = 100),
+  outtimes = seq(0, 120, by = 0.1),
+  solution_type = "deSolve",
+  use_compiled = "auto",
+  method.ode = "lsoda",
+  atol = 1e-08,
+  rtol = 1e-10,
+  map_output = TRUE,
+  ...
+)
 
 # S3 method for mkinfit
-mkinpredict(x, odeparms = x$bparms.ode,
-  odeini = x$bparms.state, outtimes = seq(0, 120, by = 0.1),
-  solution_type = "deSolve", use_compiled = "auto",
-  method.ode = "lsoda", atol = 1e-08, rtol = 1e-10,
-  map_output = TRUE, ...)
+mkinpredict( + x, + odeparms = x$bparms.ode, + odeini = x$bparms.state, + outtimes = seq(0, 120, by = 0.1), + solution_type = "deSolve", + use_compiled = "auto", + method.ode = "lsoda", + atol = 1e-08, + rtol = 1e-10, + map_output = TRUE, + ... +)

Arguments

@@ -350,7 +375,7 @@ solver is used.

c(parent=100, m1=0), seq(0, 20, by=0.1), solution_type="eigen")[201,]))
#> time parent m1 #> 201 20 4.978707 27.46227
#> User System verstrichen -#> 0.004 0.000 0.003
system.time( +#> 0.003 0.000 0.003
system.time( print(mkinpredict(SFO_SFO, c(k_parent_m1 = 0.05, k_parent_sink = 0.1, k_m1_sink = 0.01), c(parent = 100, m1 = 0), seq(0, 20, by = 0.1), solution_type = "deSolve")[201,]))
#> time parent m1 @@ -360,7 +385,7 @@ solver is used.

c(parent = 100, m1 = 0), seq(0, 20, by = 0.1), solution_type = "deSolve", use_compiled = FALSE)[201,]))
#> time parent m1 #> 201 20 4.978707 27.46227
#> User System verstrichen -#> 0.021 0.000 0.022
+#> 0.021 0.000 0.021
# \dontrun{ # Predict from a fitted model f <- mkinfit(SFO_SFO, FOCUS_2006_C)
#> Ordinary least squares optimisation
#> Sum of squared residuals at call 1: 552.5739 @@ -372,10 +397,10 @@ solver is used.

#> Sum of squared residuals at call 9: 279.9294 #> Sum of squared residuals at call 12: 200.3629 #> Sum of squared residuals at call 13: 200.3629 -#> Sum of squared residuals at call 18: 197.9039 -#> Sum of squared residuals at call 23: 197.9039 -#> Sum of squared residuals at call 25: 196.6754 -#> Sum of squared residuals at call 27: 196.6754 +#> Sum of squared residuals at call 18: 197.904 +#> Sum of squared residuals at call 22: 197.904 +#> Sum of squared residuals at call 25: 196.6753 +#> Sum of squared residuals at call 27: 196.6753 #> Sum of squared residuals at call 32: 196.5742 #> Sum of squared residuals at call 33: 196.5742 #> Sum of squared residuals at call 34: 196.5742 @@ -390,14 +415,13 @@ solver is used.

#> Sum of squared residuals at call 58: 196.5334 #> Sum of squared residuals at call 59: 196.5334 #> Sum of squared residuals at call 65: 196.5334 -#> Sum of squared residuals at call 73: 196.5334 #> Negative log-likelihood at call 75: 26.64668
#> Optimisation successfully terminated.
head(mkinpredict(f))
#> time parent m1 #> 1 0.0 82.49216 0.000000 -#> 2 0.1 80.00563 1.179955 -#> 3 0.2 77.59404 2.312580 -#> 4 0.3 75.25515 3.399419 -#> 5 0.4 72.98675 4.441969 -#> 6 0.5 70.78673 5.441679
# } +#> 2 0.1 80.00563 1.179963 +#> 3 0.2 77.59404 2.312596 +#> 4 0.3 75.25515 3.399443 +#> 5 0.4 72.98675 4.442000 +#> 6 0.5 70.78673 5.441717
# }
diff --git a/docs/reference/mkinresplot.html b/docs/reference/mkinresplot.html index 4429798b..698af302 100644 --- a/docs/reference/mkinresplot.html +++ b/docs/reference/mkinresplot.html @@ -72,7 +72,7 @@ argument show_residuals = TRUE." /> mkin - 0.9.49.8 + 0.9.49.9 @@ -142,11 +142,21 @@ the residuals can be obtained using plot.mkinf argument show_residuals = TRUE.

-
mkinresplot(object, obs_vars = names(object$mkinmod$map), xlim = c(0,
-  1.1 * max(object$data$time)), standardized = FALSE, xlab = "Time",
+    
mkinresplot(
+  object,
+  obs_vars = names(object$mkinmod$map),
+  xlim = c(0, 1.1 * max(object$data$time)),
+  standardized = FALSE,
+  xlab = "Time",
   ylab = ifelse(standardized, "Standardized residual", "Residual"),
-  maxabs = "auto", legend = TRUE, lpos = "topright",
-  col_obs = "auto", pch_obs = "auto", frame = TRUE, ...)
+ maxabs = "auto", + legend = TRUE, + lpos = "topright", + col_obs = "auto", + pch_obs = "auto", + frame = TRUE, + ... +)

Arguments

diff --git a/docs/reference/mmkin-2.png b/docs/reference/mmkin-2.png index 5e264309..7b1d73d5 100644 Binary files a/docs/reference/mmkin-2.png and b/docs/reference/mmkin-2.png differ diff --git a/docs/reference/mmkin-3.png b/docs/reference/mmkin-3.png index 0a58a86b..4c412abc 100644 Binary files a/docs/reference/mmkin-3.png and b/docs/reference/mmkin-3.png differ diff --git a/docs/reference/mmkin.html b/docs/reference/mmkin.html index d1ea7a52..8e1ea54f 100644 --- a/docs/reference/mmkin.html +++ b/docs/reference/mmkin.html @@ -72,7 +72,7 @@ datasets specified in its first two arguments." /> mkin - 0.9.49.6 + 0.9.49.9 @@ -141,15 +141,20 @@ more datasets datasets specified in its first two arguments.

-
mmkin(models = c("SFO", "FOMC", "DFOP"), datasets,
-  cores = round(detectCores()/2), cluster = NULL, ...)
+
mmkin(
+  models = c("SFO", "FOMC", "DFOP"),
+  datasets,
+  cores = round(detectCores()/2),
+  cluster = NULL,
+  ...
+)

Arguments

- @@ -202,11 +207,11 @@ for parallel execution.

time_1 <- system.time(fits.4 <- mmkin(models, datasets, cores = 1, quiet = TRUE)) time_default
#> User System verstrichen -#> 0.014 0.024 4.895
time_1
#> User System verstrichen -#> 19.047 0.004 19.063
+#> 18.739 0.379 6.198
time_1
#> User System verstrichen +#> 19.910 0.000 19.925
endpoints(fits.0[["SFO_lin", 2]])
#> $ff #> parent_M1 parent_sink M1_M2 M1_sink -#> 0.7340481 0.2659519 0.7505684 0.2494316 +#> 0.7340480 0.2659520 0.7505686 0.2494314 #> #> $SFORB #> logical(0) @@ -214,8 +219,8 @@ for parallel execution.

#> $distimes #> DT50 DT90 #> parent 0.8777689 2.915885 -#> M1 2.3257449 7.725957 -#> M2 33.7200958 112.015734 +#> M1 2.3257452 7.725958 +#> M2 33.7200890 112.015711 #>
# plot.mkinfit handles rows or columns of mmkin result objects plot(fits.0[1, ])
plot(fits.0[1, ], obs_var = c("M1", "M2"))
plot(fits.0[, 1])
# Use double brackets to extract a single mkinfit object, which will be plotted diff --git a/docs/reference/plot.mkinfit.html b/docs/reference/plot.mkinfit.html index 8dc21b06..33dc52b7 100644 --- a/docs/reference/plot.mkinfit.html +++ b/docs/reference/plot.mkinfit.html @@ -71,7 +71,7 @@ observed data together with the solution of the fitted model." /> mkin - 0.9.49.8 + 0.9.49.9
@@ -141,22 +141,47 @@ observed data together with the solution of the fitted model.

# S3 method for mkinfit
-plot(x, fit = x, obs_vars = names(fit$mkinmod$map),
-  xlab = "Time", ylab = "Observed", xlim = range(fit$data$time),
-  ylim = "default", col_obs = 1:length(obs_vars), pch_obs = col_obs,
-  lty_obs = rep(1, length(obs_vars)), add = FALSE, legend = !add,
-  show_residuals = FALSE, show_errplot = FALSE, maxabs = "auto",
-  sep_obs = FALSE, rel.height.middle = 0.9, row_layout = FALSE,
-  lpos = "topright", inset = c(0.05, 0.05), show_errmin = FALSE,
-  errmin_digits = 3, frame = TRUE, ...)
-
-plot_sep(fit, show_errmin = TRUE,
-  show_residuals = ifelse(identical(fit$err_mod, "const"), TRUE,
-  "standardized"), ...)
-
-plot_res(fit, sep_obs = FALSE, show_errmin = sep_obs,
+plot(
+  x,
+  fit = x,
+  obs_vars = names(fit$mkinmod$map),
+  xlab = "Time",
+  ylab = "Observed",
+  xlim = range(fit$data$time),
+  ylim = "default",
+  col_obs = 1:length(obs_vars),
+  pch_obs = col_obs,
+  lty_obs = rep(1, length(obs_vars)),
+  add = FALSE,
+  legend = !add,
+  show_residuals = FALSE,
+  show_errplot = FALSE,
+  maxabs = "auto",
+  sep_obs = FALSE,
+  rel.height.middle = 0.9,
+  row_layout = FALSE,
+  lpos = "topright",
+  inset = c(0.05, 0.05),
+  show_errmin = FALSE,
+  errmin_digits = 3,
+  frame = TRUE,
+  ...
+)
+
+plot_sep(
+  fit,
+  show_errmin = TRUE,
+  show_residuals = ifelse(identical(fit$err_mod, "const"), TRUE, "standardized"),
+  ...
+)
+
+plot_res(
+  fit,
+  sep_obs = FALSE,
+  show_errmin = sep_obs,
   standardized = ifelse(identical(fit$err_mod, "const"), FALSE, TRUE),
-  ...)
+  ...
+)
 
 plot_err(fit, sep_obs = FALSE, show_errmin = sep_obs, ...)
diff --git a/docs/reference/plot.mmkin.html b/docs/reference/plot.mmkin.html index 18907aa2..9d41b4c1 100644 --- a/docs/reference/plot.mmkin.html +++ b/docs/reference/plot.mmkin.html @@ -73,7 +73,7 @@ the fit of at least one model to the same dataset is shown." /> mkin - 0.9.49.8 + 0.9.49.9 @@ -144,10 +144,19 @@ the fit of at least one model to the same dataset is shown.

# S3 method for mmkin
-plot(x, main = "auto", legends = 1,
-  resplot = c("time", "errmod"), show_errmin = TRUE,
-  errmin_var = "All data", errmin_digits = 3, cex = 0.7,
-  rel.height.middle = 0.9, ymax = "auto", ...)
+plot( + x, + main = "auto", + legends = 1, + resplot = c("time", "errmod"), + show_errmin = TRUE, + errmin_var = "All data", + errmin_digits = 3, + cex = 0.7, + rel.height.middle = 0.9, + ymax = "auto", + ... +)

Arguments

models

Either a character vector of shorthand names like +

Either a character vector of shorthand names like c("SFO", "FOMC", "DFOP", "HS", "SFORB"), or an optionally named list of mkinmod objects.

diff --git a/docs/reference/summary.mkinfit.html b/docs/reference/summary.mkinfit.html index fb3c43ef..ec79c37d 100644 --- a/docs/reference/summary.mkinfit.html +++ b/docs/reference/summary.mkinfit.html @@ -73,7 +73,7 @@ values." /> mkin - 0.9.49.6 + 0.9.49.9 @@ -145,12 +145,10 @@ values.

# S3 method for mkinfit
-summary(object, data = TRUE, distimes = TRUE,
-  alpha = 0.05, ...)
+summary(object, data = TRUE, distimes = TRUE, alpha = 0.05, ...)
 
 # S3 method for summary.mkinfit
-print(x, digits = max(3, getOption("digits") -
-  3), ...)
+print(x, digits = max(3, getOption("digits") - 3), ...)

Arguments

@@ -223,17 +221,17 @@ distribution

Examples

- summary(mkinfit(mkinmod(parent = mkinsub("SFO")), FOCUS_2006_A, quiet = TRUE))
#> mkin version used for fitting: 0.9.49.6 -#> R version used for fitting: 3.6.1 -#> Date of fit: Fri Nov 1 10:10:07 2019 -#> Date of summary: Fri Nov 1 10:10:07 2019 + summary(mkinfit(mkinmod(parent = mkinsub("SFO")), FOCUS_2006_A, quiet = TRUE))
#> mkin version used for fitting: 0.9.49.9 +#> R version used for fitting: 3.6.3 +#> Date of fit: Mon Mar 30 21:43:00 2020 +#> Date of summary: Mon Mar 30 21:43:00 2020 #> #> Equations: #> d_parent/dt = - k_parent_sink * parent #> #> Model predictions using solution type analytical #> -#> Fitted using 131 model solutions performed in 0.265 s +#> Fitted using 131 model solutions performed in 0.306 s #> #> Error model: Constant variance #> @@ -260,9 +258,9 @@ distribution

#> #> Parameter correlation: #> parent_0 log_k_parent_sink sigma -#> parent_0 1.000e+00 5.428e-01 1.648e-07 -#> log_k_parent_sink 5.428e-01 1.000e+00 2.513e-07 -#> sigma 1.648e-07 2.513e-07 1.000e+00 +#> parent_0 1.000e+00 5.428e-01 1.642e-07 +#> log_k_parent_sink 5.428e-01 1.000e+00 2.507e-07 +#> sigma 1.642e-07 2.507e-07 1.000e+00 #> #> Backtransformed parameters: #> Confidence intervals for internally transformed parameters are asymmetric. diff --git a/docs/reference/transform_odeparms.html b/docs/reference/transform_odeparms.html index 4d88a03e..2a08228d 100644 --- a/docs/reference/transform_odeparms.html +++ b/docs/reference/transform_odeparms.html @@ -74,7 +74,7 @@ the ilr transformation is used." /> mkin - 0.9.49.6 + 0.9.49.9
@@ -146,11 +146,19 @@ formations fractions that should always sum up to 1 and can not be negative, the ilr transformation is used.

-
transform_odeparms(parms, mkinmod, transform_rates = TRUE,
-  transform_fractions = TRUE)
-
-backtransform_odeparms(transparms, mkinmod, transform_rates = TRUE,
-  transform_fractions = TRUE)
+
transform_odeparms(
+  parms,
+  mkinmod,
+  transform_rates = TRUE,
+  transform_fractions = TRUE
+)
+
+backtransform_odeparms(
+  transparms,
+  mkinmod,
+  transform_rates = TRUE,
+  transform_fractions = TRUE
+)

Arguments

-- cgit v1.2.1 From f9e0c46378f090a04fe95c70bb7977a686679895 Mon Sep 17 00:00:00 2001 From: Johannes Ranke Date: Tue, 31 Mar 2020 09:24:14 +0200 Subject: Static documentation rebuilt by pkgdown --- DESCRIPTION | 4 +- NAMESPACE | 1 + R/mkinmod.R | 6 ++- check.log | 15 +++++-- test.log | 51 ++++++++++++++-------- .../plotting/plot-errmod-with-sfo-lin-a-obs.svg | 6 +-- tests/testthat/DFOP_FOCUS_C_messages.txt | 4 +- tests/testthat/FOCUS_2006_D.csf | 2 +- 8 files changed, 57 insertions(+), 32 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index f631a541..5576e5bf 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -2,7 +2,7 @@ Package: mkin Type: Package Title: Kinetic Evaluation of Chemical Degradation Data Version: 0.9.49.9 -Date: 2020-03-20 +Date: 2020-03-31 Authors@R: c(person("Johannes", "Ranke", role = c("aut", "cre", "cph"), email = "jranke@uni-bremen.de", comment = c(ORCID = "0000-0003-4371-6538")), @@ -17,7 +17,7 @@ Description: Calculation routines based on the FOCUS Kinetics Report (2006, note that no warranty is implied for correctness of results or fitness for a particular purpose. Imports: stats, graphics, methods, deSolve, R6, inline, parallel, numDeriv, - lmtest + lmtest, pkgbuild Suggests: knitr, rbenchmark, tikzDevice, testthat, rmarkdown, covr, vdiffr, benchmarkme, tibble, stats4 License: GPL diff --git a/NAMESPACE b/NAMESPACE index 26995055..6f509cd7 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -76,6 +76,7 @@ importFrom(methods,signature) importFrom(parallel,detectCores) importFrom(parallel,mclapply) importFrom(parallel,parLapply) +importFrom(pkgbuild,has_compiler) importFrom(stats,AIC) importFrom(stats,BIC) importFrom(stats,aggregate) diff --git a/R/mkinmod.R b/R/mkinmod.R index cf618525..cfd40504 100644 --- a/R/mkinmod.R +++ b/R/mkinmod.R @@ -33,6 +33,7 @@ #' @param verbose If \code{TRUE}, passed to \code{\link{cfunction}} if #' applicable to give detailed information about the C function being built. #' @importFrom methods signature +#' @importFrom pkgbuild has_compiler #' @importFrom inline cfunction #' @return A list of class \code{mkinmod} for use with \code{\link{mkinfit}}, #' containing, among others, @@ -364,8 +365,9 @@ mkinmod <- function(..., use_of_ff = "min", speclist = NULL, quiet = FALSE, verb model$coefmat <- m }#}}} - # Try to create a function compiled from C code if >1 observed variable {{{ - if (length(obs_vars) > 1) { + # Try to create a function compiled from C code there is more than one observed variable {{{ + # and a compiler is available + if (length(obs_vars) > 1 & has_compiler()) { # Translate the R code for the derivatives to C code diffs.C <- paste(diffs, collapse = ";\n") diff --git a/check.log b/check.log index b7555c55..35ab651a 100644 --- a/check.log +++ b/check.log @@ -1,11 +1,11 @@ * using log directory ‘/home/jranke/git/mkin/mkin.Rcheck’ -* using R version 3.6.2 (2019-12-12) +* using R version 3.6.3 (2020-02-29) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using options ‘--no-tests --as-cran’ * checking for file ‘mkin/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘mkin’ version ‘0.9.49.8’ +* this is package ‘mkin’ version ‘0.9.49.9’ * package encoding: UTF-8 * checking CRAN incoming feasibility ... Note_to_CRAN_maintainers Maintainer: ‘Johannes Ranke ’ @@ -56,7 +56,10 @@ Maintainer: ‘Johannes Ranke ’ * checking data for ASCII and uncompressed saves ... OK * checking installed files from ‘inst/doc’ ... OK * checking files in ‘vignettes’ ... OK -* checking examples ... OK +* checking examples ... NOTE +Examples with CPU or elapsed time > 5s + user system elapsed +mkinsub 2.015 4.083 0.703 * checking for unstated dependencies in ‘tests’ ... OK * checking tests ... SKIPPED * checking for unstated dependencies in vignettes ... OK @@ -66,5 +69,9 @@ Maintainer: ‘Johannes Ranke ’ * checking for detritus in the temp directory ... OK * DONE -Status: OK +Status: 1 NOTE +See + ‘/home/jranke/git/mkin/mkin.Rcheck/00check.log’ +for details. + diff --git a/test.log b/test.log index c51d06b8..2db18301 100644 --- a/test.log +++ b/test.log @@ -1,38 +1,53 @@ Loading mkin Testing mkin ✔ | OK F W S | Context -✔ | 5 | Calculation of Akaike weights ✔ | 2 | Export dataset for reading into CAKE -✔ | 10 | Confidence intervals and p-values [9.7 s] -✔ | 14 | Error model fitting [36.9 s] -✔ | 4 | Calculation of FOCUS chi2 error levels [2.2 s] -✔ | 13 | Results for FOCUS D established in expertise for UBA (Ranke 2014) [3.3 s] -✔ | 6 | Test fitting the decline of metabolites from their maximum [0.7 s] -✔ | 1 | Fitting the logistic model [0.9 s] +✔ | 13 | Results for FOCUS D established in expertise for UBA (Ranke 2014) [3.8 s] +✔ | 4 | Calculation of FOCUS chi2 error levels [2.3 s] +✔ | 4 | Fitting the SFORB model [1.7 s] +✔ | 5 | Calculation of Akaike weights +✔ | 10 | Confidence intervals and p-values [10.2 s] +✔ | 14 | Error model fitting [40.7 s] +✔ | 6 | Test fitting the decline of metabolites from their maximum [0.8 s] +✔ | 1 | Fitting the logistic model [1.0 s] ✔ | 1 | Test dataset class mkinds used in gmkin -✔ | 12 | Special cases of mkinfit calls [2.4 s] +✖ | 11 1 | Special cases of mkinfit calls [2.3 s] +──────────────────────────────────────────────────────────────────────────────── +test_mkinfit_errors.R:64: failure: We get reproducible output if quiet = FALSE +Results have changed from known value recorded in 'DFOP_FOCUS_C_messages.txt'. +2/165 mismatches +x[84]: "Sum of squared residuals at call 57: 4.364077" +y[84]: "Sum of squared residuals at call 57: 4.364078" + +x[105]: "85.00134 -0.7776046 -4.025878 1.248775 " +y[105]: "85.00135 -0.7776046 -4.025878 1.248775 " +──────────────────────────────────────────────────────────────────────────────── ✔ | 9 | mkinmod model generation and printing [0.2 s] ✔ | 3 | Model predictions with mkinpredict [0.3 s] -✔ | 16 | Evaluations according to 2015 NAFTA guidance [4.1 s] -✔ | 4 | Calculation of maximum time weighted average concentrations (TWAs) [2.3 s] +✔ | 16 | Evaluations according to 2015 NAFTA guidance [4.3 s] +✔ | 4 | Calculation of maximum time weighted average concentrations (TWAs) [2.2 s] ✔ | 3 | Summary -✔ | 11 | Plotting [0.6 s] +✖ | 10 1 | Plotting [0.6 s] +──────────────────────────────────────────────────────────────────────────────── +test_plots_summary_twa.R:118: failure: Plotting mkinfit and mmkin objects is reproducible +Figures don't match: plot-errmod-with-sfo-lin-a-obs.svg + +──────────────────────────────────────────────────────────────────────────────── ✔ | 4 | AIC calculation ✔ | 2 | Residuals extracted from mkinfit models -✔ | 2 | Complex test case from Schaefer et al. (2007) Piacenza paper [5.3 s] -✔ | 4 | Fitting the SFORB model [1.7 s] +✔ | 2 | Complex test case from Schaefer et al. (2007) Piacenza paper [5.6 s] ✔ | 1 | Summaries of old mkinfit objects -✔ | 4 | Results for synthetic data established in expertise for UBA (Ranke 2014) [7.2 s] -✔ | 7 1 | Hypothesis tests [32.3 s] +✔ | 4 | Results for synthetic data established in expertise for UBA (Ranke 2014) [7.4 s] +✔ | 7 1 | Hypothesis tests [33.6 s] ──────────────────────────────────────────────────────────────────────────────── test_tests.R:60: skip: We can do a likelihood ratio test using an update specification Reason: This errors out if called by testthat while it works in a normal R session ──────────────────────────────────────────────────────────────────────────────── ══ Results ═════════════════════════════════════════════════════════════════════ -Duration: 110.2 s +Duration: 117.3 s -OK: 138 -Failed: 0 +OK: 136 +Failed: 2 Warnings: 0 Skipped: 1 diff --git a/tests/figs/plotting/plot-errmod-with-sfo-lin-a-obs.svg b/tests/figs/plotting/plot-errmod-with-sfo-lin-a-obs.svg index 2b4930ba..7ba81d7b 100644 --- a/tests/figs/plotting/plot-errmod-with-sfo-lin-a-obs.svg +++ b/tests/figs/plotting/plot-errmod-with-sfo-lin-a-obs.svg @@ -156,7 +156,7 @@ 5 10 15 -20 +20 25 30 @@ -186,7 +186,7 @@ - + @@ -222,7 +222,7 @@ - + diff --git a/tests/testthat/DFOP_FOCUS_C_messages.txt b/tests/testthat/DFOP_FOCUS_C_messages.txt index 78438d06..c36f11db 100644 --- a/tests/testthat/DFOP_FOCUS_C_messages.txt +++ b/tests/testthat/DFOP_FOCUS_C_messages.txt @@ -81,7 +81,7 @@ Sum of squared residuals at call 55: 4.364078 85.01633 -0.7763163 -4.027611 1.248897 Sum of squared residuals at call 56: 4.364078 85.01633 -0.7763164 -4.027611 1.248897 -Sum of squared residuals at call 57: 4.364078 +Sum of squared residuals at call 57: 4.364077 85.01633 -0.7763163 -4.027611 1.248897 85.01633 -0.7763163 -4.027611 1.248897 85.00894 -0.7777917 -4.026307 1.24772 @@ -102,7 +102,7 @@ Sum of squared residuals at call 67: 4.362751 85.00518 -0.7773082 -4.026004 1.248453 85.00134 -0.7776046 -4.025878 1.248775 Sum of squared residuals at call 70: 4.362721 -85.00135 -0.7776046 -4.025878 1.248775 +85.00134 -0.7776046 -4.025878 1.248775 Sum of squared residuals at call 71: 4.362721 85.00134 -0.7776046 -4.025878 1.248775 Sum of squared residuals at call 72: 4.362721 diff --git a/tests/testthat/FOCUS_2006_D.csf b/tests/testthat/FOCUS_2006_D.csf index 358b50e3..a7f8edaf 100644 --- a/tests/testthat/FOCUS_2006_D.csf +++ b/tests/testthat/FOCUS_2006_D.csf @@ -5,7 +5,7 @@ Description: MeasurementUnits: % AR TimeUnits: days Comments: Created using mkin::CAKE_export -Date: 2019-11-13 +Date: 2020-03-31 Optimiser: IRLS [Data] -- cgit v1.2.1 From 64a476750ff57f4c612620bd58cc4ac42812e185 Mon Sep 17 00:00:00 2001 From: Johannes Ranke Date: Tue, 31 Mar 2020 09:52:19 +0200 Subject: Use inline documentation for R6 class mkinds --- R/mkinds.R | 53 ++++++++++++++++++--------------- docs/reference/mkinds.html | 64 +++++++++++++++++++++++++--------------- docs/reference/print.mkinds.html | 6 ++-- man/mkinds.Rd | 55 +++++++++++++++++++++++----------- man/print.mkinds.Rd | 2 +- test.log | 45 ++++++++++------------------ 6 files changed, 126 insertions(+), 99 deletions(-) diff --git a/R/mkinds.R b/R/mkinds.R index a66adb14..d6f296bf 100644 --- a/R/mkinds.R +++ b/R/mkinds.R @@ -1,43 +1,50 @@ #' A dataset class for mkin #' -#' A dataset class for mkin -#' -#' @name mkinds -#' @docType class -#' @format An \code{\link{R6Class}} generator object. -#' @section Fields: -#' -#' \describe{ \item{list("title")}{A full title for the dataset} -#' -#' \item{list("sampling")}{times The sampling times} -#' -#' \item{list("time_unit")}{The time unit} -#' -#' \item{list("observed")}{Names of the observed compounds} -#' -#' \item{list("unit")}{The unit of the observations} -#' -#' \item{list("replicates")}{The number of replicates} -#' -#' \item{list("data")}{A dataframe with at least the columns name, time and -#' value in order to be compatible with mkinfit} } +#' @description +#' At the moment this dataset class is hardly used in mkin. For example, +#' mkinfit does not take mkinds datasets as argument, but works with dataframes +#' such as the on contained in the data field of mkinds objects. Some datasets +#' provided by this package come as mkinds objects nevertheless. +#' #' @importFrom R6 R6Class -#' @keywords datasets +#' @seealso The S3 printing method \code{\link{print.mkinds}} #' @examples #' #' mds <- mkinds$new("FOCUS A", FOCUS_2006_A) +#' print(mds) #' #' @export mkinds <- R6Class("mkinds", public = list( + + #' @field title A full title for the dataset title = NULL, + + #' @field sampling_times The sampling times sampling_times = NULL, + + #' @field time_unit The time unit time_unit = NULL, + + #' @field observed Names of the observed variables observed = NULL, + + #' @field unit The unit of the observations unit = NULL, + + #' @field replicates The maximum number of replicates per sampling time replicates = NULL, + + #' @field data A data frame with at least the columns name, time + #' and value in order to be compatible with mkinfit data = NULL, + #' @description + #' Create a new mkinds object + #' @param title The dataset title + #' @param data The data + #' @param time_unit The time unit + #' @param unit The unit of the observations initialize = function(title = "", data, time_unit = NA, unit = NA) { self$title <- title @@ -56,8 +63,6 @@ mkinds <- R6Class("mkinds", #' Print mkinds objects #' -#' Print mkinds objects. -#' #' @param x An \code{\link{mkinds}} object. #' @param \dots Not used. #' @export diff --git a/docs/reference/mkinds.html b/docs/reference/mkinds.html index c1cdcf99..ef6fb35c 100644 --- a/docs/reference/mkinds.html +++ b/docs/reference/mkinds.html @@ -36,7 +36,10 @@ - + @@ -133,36 +136,36 @@
-

A dataset class for mkin

+

At the moment this dataset class is hardly used in mkin. For example, +mkinfit does not take mkinds datasets as argument, but works with dataframes +such as the on contained in the data field of mkinds objects. Some datasets +provided by this package come as mkinds objects nevertheless.

-

Format

+

See also

-

An R6Class generator object.

-

Fields

+

The S3 printing method print.mkinds

+

Public fields

- - - -
-
list("title")

A full title for the dataset

+

+
title

A full title for the dataset

-
list("sampling")

times The sampling times

+
sampling_times

The sampling times

-
list("time_unit")

The time unit

+
time_unit

The time unit

-
list("observed")

Names of the observed compounds

+
observed

Names of the observed variables

-
list("unit")

The unit of the observations

+
unit

The unit of the observations

-
list("replicates")

The number of replicates

+
replicates

The maximum number of replicates per sampling time

-
list("data")

A dataframe with at least the columns name, time and -value in order to be compatible with mkinfit

-
+
data

A data frame with at least the columns name, time +and value in order to be compatible with mkinfit

+

Methods

@@ -174,10 +177,20 @@ value in order to be compatible with mkinfit


Method new()

- -

Usage

+

Create a new mkinds object

Usage

mkinds$new(title = "", data, time_unit = NA, unit = NA)

+

Arguments

+

+
title

The dataset title

+ +
data

The data

+ +
time_unit

The time unit

+ +
unit

The unit of the observations

+ +


Method clone()

The objects of this class are cloneable with this method.

Usage

@@ -193,13 +206,18 @@ value in order to be compatible with mkinfit

Examples

-mds <- mkinds$new("FOCUS A", FOCUS_2006_A)
+mds <- mkinds$new("FOCUS A", FOCUS_2006_A) +print(mds)
#> <mkinds> with $title: FOCUS A +#> Observed compounds $observed: parent +#> Sampling times $sampling_times: 0, 3, 7, 14, 30, 62, 90, 118 +#> With a maximum of 1 replicates
+
@@ -133,7 +133,7 @@
-

Print mkinds objects.

+

Print mkinds objects

# S3 method for mkinds
diff --git a/man/mkinds.Rd b/man/mkinds.Rd
index 79eb0167..3bbb1c4b 100644
--- a/man/mkinds.Rd
+++ b/man/mkinds.Rd
@@ -1,38 +1,43 @@
 % Generated by roxygen2: do not edit by hand
 % Please edit documentation in R/mkinds.R
-\docType{class}
 \name{mkinds}
 \alias{mkinds}
 \title{A dataset class for mkin}
-\format{An \code{\link{R6Class}} generator object.}
 \description{
-A dataset class for mkin
+At the moment this dataset class is hardly used in mkin. For example,
+mkinfit does not take mkinds datasets as argument, but works with dataframes
+such as the on contained in the data field of mkinds objects. Some datasets
+provided by this package come as mkinds objects nevertheless.
 }
-\section{Fields}{
+\examples{
 
+mds <- mkinds$new("FOCUS A", FOCUS_2006_A)
+print(mds)
 
-\describe{ \item{list("title")}{A full title for the dataset}
+}
+\seealso{
+The S3 printing method \code{\link{print.mkinds}}
+}
+\section{Public fields}{
+\if{html}{\out{
}} +\describe{ +\item{\code{title}}{A full title for the dataset} -\item{list("sampling")}{times The sampling times} +\item{\code{sampling_times}}{The sampling times} -\item{list("time_unit")}{The time unit} +\item{\code{time_unit}}{The time unit} -\item{list("observed")}{Names of the observed compounds} +\item{\code{observed}}{Names of the observed variables} -\item{list("unit")}{The unit of the observations} +\item{\code{unit}}{The unit of the observations} -\item{list("replicates")}{The number of replicates} +\item{\code{replicates}}{The maximum number of replicates per sampling time} -\item{list("data")}{A dataframe with at least the columns name, time and -value in order to be compatible with mkinfit} } +\item{\code{data}}{A data frame with at least the columns name, time +and value in order to be compatible with mkinfit} } - -\examples{ - -mds <- mkinds$new("FOCUS A", FOCUS_2006_A) - +\if{html}{\out{
}} } -\keyword{datasets} \section{Methods}{ \subsection{Public methods}{ \itemize{ @@ -43,10 +48,24 @@ mds <- mkinds$new("FOCUS A", FOCUS_2006_A) \if{html}{\out{
}} \if{html}{\out{}} \subsection{Method \code{new()}}{ +Create a new mkinds object \subsection{Usage}{ \if{html}{\out{
}}\preformatted{mkinds$new(title = "", data, time_unit = NA, unit = NA)}\if{html}{\out{
}} } +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{title}}{The dataset title} + +\item{\code{data}}{The data} + +\item{\code{time_unit}}{The time unit} + +\item{\code{unit}}{The unit of the observations} +} +\if{html}{\out{
}} +} } \if{html}{\out{
}} \if{html}{\out{}} diff --git a/man/print.mkinds.Rd b/man/print.mkinds.Rd index 54dc5a12..51ef3b76 100644 --- a/man/print.mkinds.Rd +++ b/man/print.mkinds.Rd @@ -12,5 +12,5 @@ \item{\dots}{Not used.} } \description{ -Print mkinds objects. +Print mkinds objects } diff --git a/test.log b/test.log index 2db18301..77130814 100644 --- a/test.log +++ b/test.log @@ -2,52 +2,37 @@ Loading mkin Testing mkin ✔ | OK F W S | Context ✔ | 2 | Export dataset for reading into CAKE -✔ | 13 | Results for FOCUS D established in expertise for UBA (Ranke 2014) [3.8 s] +✔ | 13 | Results for FOCUS D established in expertise for UBA (Ranke 2014) [3.7 s] ✔ | 4 | Calculation of FOCUS chi2 error levels [2.3 s] -✔ | 4 | Fitting the SFORB model [1.7 s] +✔ | 4 | Fitting the SFORB model [1.8 s] ✔ | 5 | Calculation of Akaike weights -✔ | 10 | Confidence intervals and p-values [10.2 s] -✔ | 14 | Error model fitting [40.7 s] +✔ | 10 | Confidence intervals and p-values [10.7 s] +✔ | 14 | Error model fitting [42.8 s] ✔ | 6 | Test fitting the decline of metabolites from their maximum [0.8 s] ✔ | 1 | Fitting the logistic model [1.0 s] ✔ | 1 | Test dataset class mkinds used in gmkin -✖ | 11 1 | Special cases of mkinfit calls [2.3 s] -──────────────────────────────────────────────────────────────────────────────── -test_mkinfit_errors.R:64: failure: We get reproducible output if quiet = FALSE -Results have changed from known value recorded in 'DFOP_FOCUS_C_messages.txt'. -2/165 mismatches -x[84]: "Sum of squared residuals at call 57: 4.364077" -y[84]: "Sum of squared residuals at call 57: 4.364078" - -x[105]: "85.00134 -0.7776046 -4.025878 1.248775 " -y[105]: "85.00135 -0.7776046 -4.025878 1.248775 " -──────────────────────────────────────────────────────────────────────────────── +✔ | 12 | Special cases of mkinfit calls [2.5 s] ✔ | 9 | mkinmod model generation and printing [0.2 s] -✔ | 3 | Model predictions with mkinpredict [0.3 s] -✔ | 16 | Evaluations according to 2015 NAFTA guidance [4.3 s] -✔ | 4 | Calculation of maximum time weighted average concentrations (TWAs) [2.2 s] +✔ | 3 | Model predictions with mkinpredict [0.4 s] +✔ | 16 | Evaluations according to 2015 NAFTA guidance [4.4 s] +✔ | 4 | Calculation of maximum time weighted average concentrations (TWAs) [2.3 s] ✔ | 3 | Summary -✖ | 10 1 | Plotting [0.6 s] -──────────────────────────────────────────────────────────────────────────────── -test_plots_summary_twa.R:118: failure: Plotting mkinfit and mmkin objects is reproducible -Figures don't match: plot-errmod-with-sfo-lin-a-obs.svg - -──────────────────────────────────────────────────────────────────────────────── +✔ | 11 | Plotting [0.6 s] ✔ | 4 | AIC calculation ✔ | 2 | Residuals extracted from mkinfit models -✔ | 2 | Complex test case from Schaefer et al. (2007) Piacenza paper [5.6 s] +✔ | 2 | Complex test case from Schaefer et al. (2007) Piacenza paper [5.7 s] ✔ | 1 | Summaries of old mkinfit objects -✔ | 4 | Results for synthetic data established in expertise for UBA (Ranke 2014) [7.4 s] -✔ | 7 1 | Hypothesis tests [33.6 s] +✔ | 4 | Results for synthetic data established in expertise for UBA (Ranke 2014) [7.7 s] +✔ | 7 1 | Hypothesis tests [35.7 s] ──────────────────────────────────────────────────────────────────────────────── test_tests.R:60: skip: We can do a likelihood ratio test using an update specification Reason: This errors out if called by testthat while it works in a normal R session ──────────────────────────────────────────────────────────────────────────────── ══ Results ═════════════════════════════════════════════════════════════════════ -Duration: 117.3 s +Duration: 123.0 s -OK: 136 -Failed: 2 +OK: 138 +Failed: 0 Warnings: 0 Skipped: 1 -- cgit v1.2.1 From 1d01aa6e40bdb3e338638b9239153cf82713d634 Mon Sep 17 00:00:00 2001 From: Johannes Ranke Date: Tue, 31 Mar 2020 10:40:36 +0200 Subject: Update NEWS, static documentation rebuilt by pkgdown --- NEWS.md | 4 +++- docs/news/index.html | 3 ++- 2 files changed, 5 insertions(+), 2 deletions(-) diff --git a/NEWS.md b/NEWS.md index 63cf18bc..8fe50754 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,6 +1,8 @@ # mkin 0.9.49.9 (unreleased) -- 'mkinmod': Do not check for gcc using Sys.which('gcc') any more, as this will often fail even if Rtools are installed +- 'mkinmod': Use pkgbuild::has_compiler instead of Sys.which('gcc'), as the latter will often fail even if Rtools are installed + +- 'mkinds': Use roxygen for documenting fields and methods of this R6 class # mkin 0.9.49.8 (2020-01-09) diff --git a/docs/news/index.html b/docs/news/index.html index b7c814ce..c2b5865f 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -134,7 +134,8 @@ mkin 0.9.49.9 (unreleased) Unreleased
    -
  • ‘mkinmod’: Do not check for gcc using Sys.which(‘gcc’) any more, as this will often fail even if Rtools are installed
  • +
  • ‘mkinmod’: Use pkgbuild::has_compiler instead of Sys.which(‘gcc’), as the latter will often fail even if Rtools are installed

  • +
  • ‘mkinds’: Use roxygen for documenting fields and methods of this R6 class

-- cgit v1.2.1 From 47ba9ea512b82fb8b31da8ec5558f3c0952d86d4 Mon Sep 17 00:00:00 2001 From: Johannes Ranke Date: Thu, 2 Apr 2020 10:58:34 +0200 Subject: Compiled models article, reduce distractions - Added a section with platform specific notes on getting compiled models to work to the compiled models article - Don't return empty SFORB parameter list from endpoints() if there is no SFORB model - Avoid warnings when using standardized = TRUE in plot.mmkin() --- NEWS.md | 10 +- R/endpoints.R | 20 +- R/plot.mmkin.R | 6 +- docs/articles/web_only/compiled_models.html | 171 ++++++-------- docs/news/index.html | 17 +- docs/reference/endpoints.html | 5 +- docs/reference/plot.mmkin.html | 7 + man/endpoints.Rd | 2 +- man/plot.mmkin.Rd | 5 + test.log | 30 +-- tests/testthat/FOCUS_2006_D.csf | 2 +- vignettes/web_only/FOCUS_Z.R | 115 ++++++++++ vignettes/web_only/FOCUS_Z.html | 332 ++++++++++++++++++---------- vignettes/web_only/compiled_models.R | 61 +++++ vignettes/web_only/compiled_models.Rmd | 53 ++++- vignettes/web_only/compiled_models.html | 189 +++++++++------- 16 files changed, 674 insertions(+), 351 deletions(-) create mode 100644 vignettes/web_only/FOCUS_Z.R create mode 100644 vignettes/web_only/compiled_models.R diff --git a/NEWS.md b/NEWS.md index 8fe50754..a2258e77 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,12 @@ -# mkin 0.9.49.9 (unreleased) +# mkin 0.9.49.10 (unreleased) + +- 'endpoints': Don't return the SFORB list component if it's empty. This reduces distraction and complies with the documentation + +- Article in compiled models: Add some platform specific code and suppress warnings about zero values being removed from the FOCUS D dataset + +- 'plot.mmkin': Add the argument 'standardized' to avoid warnings that occurred when it was passed as part of the additional arguments captured by the dots (...) + +# mkin 0.9.49.9 (2020-03-31) - 'mkinmod': Use pkgbuild::has_compiler instead of Sys.which('gcc'), as the latter will often fail even if Rtools are installed diff --git a/R/endpoints.R b/R/endpoints.R index 14beadea..f7ee483a 100644 --- a/R/endpoints.R +++ b/R/endpoints.R @@ -1,12 +1,12 @@ #' Function to calculate endpoints for further use from kinetic models fitted #' with mkinfit -#' +#' #' This function calculates DT50 and DT90 values as well as formation fractions #' from kinetic models fitted with mkinfit. If the SFORB model was specified #' for one of the parents or metabolites, the Eigenvalues are returned. These #' are equivalent to the rate constantes of the DFOP model, but with the #' advantage that the SFORB model can also be used for metabolites. -#' +#' #' @param fit An object of class \code{\link{mkinfit}}. #' @importFrom stats optimize #' @return A list with the components mentioned above. @@ -14,10 +14,10 @@ #' @author Johannes Ranke #' @keywords manip #' @examples -#' +#' #' fit <- mkinfit("FOMC", FOCUS_2006_C, quiet = TRUE) -#' endpoints(fit) -#' +#' endpoints(fit) +#' #' @export endpoints <- function(fit) { # Calculate dissipation times DT50 and DT90 and formation @@ -29,8 +29,9 @@ endpoints <- function(fit) { parms.all <- c(fit$bparms.optim, fit$bparms.fixed) ep$ff <- vector() ep$SFORB <- vector() - ep$distimes <- data.frame(DT50 = rep(NA, length(obs_vars)), - DT90 = rep(NA, length(obs_vars)), + ep$distimes <- data.frame( + DT50 = rep(NA, length(obs_vars)), + DT90 = rep(NA, length(obs_vars)), row.names = obs_vars) for (obs_var in obs_vars) { type = names(fit$mkinmod$map[[obs_var]])[1] @@ -41,8 +42,8 @@ endpoints <- function(fit) { f_values = parms.all[f_names] f_to_sink = 1 - sum(f_values) names(f_to_sink) = ifelse(type == "SFORB", - paste(obs_var, "free", "sink", sep = "_"), - paste(obs_var, "sink", sep = "_")) + paste(obs_var, "free", "sink", sep = "_"), + paste(obs_var, "sink", sep = "_")) for (f_name in f_names) { ep$ff[[sub("f_", "", sub("_to_", "_", f_name))]] = f_values[[f_name]] } @@ -195,5 +196,6 @@ endpoints <- function(fit) { } ep$distimes[obs_var, c("DT50", "DT90")] = c(DT50, DT90) } + if (length(ep$SFORB) == 0) ep$SFORB <- NULL return(ep) } diff --git a/R/plot.mmkin.R b/R/plot.mmkin.R index 182e74ca..15ea86eb 100644 --- a/R/plot.mmkin.R +++ b/R/plot.mmkin.R @@ -15,6 +15,9 @@ #' @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 +#' `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 @@ -51,6 +54,7 @@ #' @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, @@ -136,7 +140,7 @@ plot.mmkin <- function(x, main = "auto", legends = 1, } if (resplot == "time") { - mkinresplot(fit, legend = FALSE, ...) + mkinresplot(fit, legend = FALSE, standardized = standardized, ...) } else { mkinerrplot(fit, legend = FALSE, ...) } diff --git a/docs/articles/web_only/compiled_models.html b/docs/articles/web_only/compiled_models.html index 363f0c38..6daabd5e 100644 --- a/docs/articles/web_only/compiled_models.html +++ b/docs/articles/web_only/compiled_models.html @@ -31,7 +31,7 @@ mkin - 0.9.49.6 + 0.9.49.9
@@ -90,7 +90,7 @@

Performance benefit by using compiled model definitions in mkin

Johannes Ranke

-

2019-11-01

+

2020-04-02

@@ -99,75 +99,49 @@ -
+

-Model that can also be solved with Eigenvalues

-

This evaluation is taken from the example section of mkinfit. When using an mkin version equal to or greater than 0.9-36 and a C compiler (gcc) is available, you will see a message that the model is being compiled from autogenerated C code when defining a model using mkinmod. The mkinmod() function checks for presence of the gcc compiler using

-
Sys.which("gcc")
-
##            gcc 
-## "/usr/bin/gcc"
+How to benefit from compiled models +

When using an mkin version equal to or greater than 0.9-36 and a C compiler is available, you will see a message that the model is being compiled from autogenerated C code when defining a model using mkinmod. Starting from version 0.9.49.9, the mkinmod() function checks for presence of a compiler using

+ +

In previous versions, it used Sys.which("gcc") for this check.

+

On Linux, you need to have the essential build tools like make and gcc or clang installed. On Debian based linux distributions, these will be pulled in by installing the build-essential package.

+

On MacOS, which I do not use personally, I have had reports that a compiler is available by default.

+

On Windows, you need to install Rtools and have the path to its bin directory in your PATH variable. You do not need to modify the PATH variable when installing Rtools. Instead, I would recommend to put the line

+
Sys.setenv(PATH = paste("C:/Rtools/bin", Sys.getenv("PATH"), sep=";"))
+

into your .Rprofile startup file. This is just a text file with some R code that is executed when your R session starts. It has to be named .Rprofile and has to be located in your home directory, which will generally be your Documents folder. You can check the location of the home directory used by R by issuing

+
Sys.getenv("HOME")
+
+
+

+Comparison with Eigenvalue based solutions

First, we build a simple degradation model for a parent compound with one metabolite.

-
library("mkin", quietly = TRUE)
-SFO_SFO <- mkinmod(
-  parent = mkinsub("SFO", "m1"),
-  m1 = mkinsub("SFO"))
+
library("mkin", quietly = TRUE)
+SFO_SFO <- mkinmod(
+  parent = mkinsub("SFO", "m1"),
+  m1 = mkinsub("SFO"))
## Successfully compiled differential equation model from auto-generated C code.
-

We can compare the performance of the Eigenvalue based solution against the compiled version and the R implementation of the differential equations using the benchmark package.

- -
## Lade nötiges Paket: rbenchmark
-
## Warning in mkinfit(SFO_SFO, FOCUS_2006_D, solution_type = "deSolve",
-## use_compiled = FALSE, : Observations with value of zero were removed from
-## the data
-
## Warning in mkinfit(SFO_SFO, FOCUS_2006_D, solution_type = "eigen", quiet =
-## TRUE): Observations with value of zero were removed from the data
-
## Warning in mkinfit(SFO_SFO, FOCUS_2006_D, solution_type = "deSolve", quiet
-## = TRUE): Observations with value of zero were removed from the data
-
## Warning in mkinfit(SFO_SFO, FOCUS_2006_D, solution_type = "deSolve",
-## use_compiled = FALSE, : Observations with value of zero were removed from
-## the data
-
-## Warning in mkinfit(SFO_SFO, FOCUS_2006_D, solution_type = "deSolve",
-## use_compiled = FALSE, : Observations with value of zero were removed from
-## the data
-
-## Warning in mkinfit(SFO_SFO, FOCUS_2006_D, solution_type = "deSolve",
-## use_compiled = FALSE, : Observations with value of zero were removed from
-## the data
-
## Warning in mkinfit(SFO_SFO, FOCUS_2006_D, solution_type = "eigen", quiet =
-## TRUE): Observations with value of zero were removed from the data
-
-## Warning in mkinfit(SFO_SFO, FOCUS_2006_D, solution_type = "eigen", quiet =
-## TRUE): Observations with value of zero were removed from the data
-
-## Warning in mkinfit(SFO_SFO, FOCUS_2006_D, solution_type = "eigen", quiet =
-## TRUE): Observations with value of zero were removed from the data
-
## Warning in mkinfit(SFO_SFO, FOCUS_2006_D, solution_type = "deSolve", quiet
-## = TRUE): Observations with value of zero were removed from the data
-
-## Warning in mkinfit(SFO_SFO, FOCUS_2006_D, solution_type = "deSolve", quiet
-## = TRUE): Observations with value of zero were removed from the data
-
-## Warning in mkinfit(SFO_SFO, FOCUS_2006_D, solution_type = "deSolve", quiet
-## = TRUE): Observations with value of zero were removed from the data
+

We can compare the performance of the Eigenvalue based solution against the compiled version and the R implementation of the differential equations using the benchmark package. In the output of below code, the warnings about zero being removed from the FOCUS D dataset are suppressed.

+
##                    test replications elapsed relative user.self sys.self
-## 3     deSolve, compiled            3   3.143    1.000     3.142        0
-## 1 deSolve, not compiled            3  29.169    9.281    29.154        0
-## 2      Eigenvalue based            3   4.358    1.387     4.356        0
+## 3     deSolve, compiled            3   3.239    1.000     3.237        0
+## 1 deSolve, not compiled            3  29.758    9.187    29.739        0
+## 2      Eigenvalue based            3   4.558    1.407     4.554        0
 ##   user.child sys.child
 ## 3          0         0
 ## 1          0         0
@@ -178,52 +152,32 @@
 

Model that can not be solved with Eigenvalues

This evaluation is also taken from the example section of mkinfit.

-
if (require(rbenchmark)) {
-  FOMC_SFO <- mkinmod(
-    parent = mkinsub("FOMC", "m1"),
-    m1 = mkinsub( "SFO"))
-
-  b.2 <- benchmark(
-    "deSolve, not compiled" = mkinfit(FOMC_SFO, FOCUS_2006_D,
-                                      use_compiled = FALSE, quiet = TRUE),
-    "deSolve, compiled" = mkinfit(FOMC_SFO, FOCUS_2006_D, quiet = TRUE),
-    replications = 3)
-  print(b.2)
-  factor_FOMC_SFO <- round(b.2["1", "relative"])
-} else {
-  factor_FOMC_SFO <- NA
-  print("R package benchmark is not available")
-}
+
if (require(rbenchmark)) {
+  FOMC_SFO <- mkinmod(
+    parent = mkinsub("FOMC", "m1"),
+    m1 = mkinsub( "SFO"))
+
+  b.2 <- benchmark(
+    "deSolve, not compiled" = mkinfit(FOMC_SFO, FOCUS_2006_D,
+                                      use_compiled = FALSE, quiet = TRUE),
+    "deSolve, compiled" = mkinfit(FOMC_SFO, FOCUS_2006_D, quiet = TRUE),
+    replications = 3)
+  print(b.2)
+  factor_FOMC_SFO <- round(b.2["1", "relative"])
+} else {
+  factor_FOMC_SFO <- NA
+  print("R package benchmark is not available")
+}
## Successfully compiled differential equation model from auto-generated C code.
-
## Warning in mkinfit(FOMC_SFO, FOCUS_2006_D, use_compiled = FALSE, quiet =
-## TRUE): Observations with value of zero were removed from the data
-
## Warning in mkinfit(FOMC_SFO, FOCUS_2006_D, quiet = TRUE): Observations with
-## value of zero were removed from the data
-
## Warning in mkinfit(FOMC_SFO, FOCUS_2006_D, use_compiled = FALSE, quiet =
-## TRUE): Observations with value of zero were removed from the data
-
-## Warning in mkinfit(FOMC_SFO, FOCUS_2006_D, use_compiled = FALSE, quiet =
-## TRUE): Observations with value of zero were removed from the data
-
-## Warning in mkinfit(FOMC_SFO, FOCUS_2006_D, use_compiled = FALSE, quiet =
-## TRUE): Observations with value of zero were removed from the data
-
## Warning in mkinfit(FOMC_SFO, FOCUS_2006_D, quiet = TRUE): Observations with
-## value of zero were removed from the data
-
-## Warning in mkinfit(FOMC_SFO, FOCUS_2006_D, quiet = TRUE): Observations with
-## value of zero were removed from the data
-
-## Warning in mkinfit(FOMC_SFO, FOCUS_2006_D, quiet = TRUE): Observations with
-## value of zero were removed from the data
##                    test replications elapsed relative user.self sys.self
-## 2     deSolve, compiled            3   4.840    1.000     4.837        0
-## 1 deSolve, not compiled            3  54.338   11.227    54.309        0
+## 2     deSolve, compiled            3   4.984    1.000     4.981    0.000
+## 1 deSolve, not compiled            3  55.358   11.107    55.326    0.003
 ##   user.child sys.child
 ## 2          0         0
 ## 1          0         0

Here we get a performance benefit of a factor of 11 using the version of the differential equation model compiled from C code!

-

This vignette was built with mkin 0.9.49.6 on

-
## R version 3.6.1 (2019-07-05)
+

This vignette was built with mkin 0.9.49.9 on

+
## R version 3.6.3 (2020-02-29)
 ## Platform: x86_64-pc-linux-gnu (64-bit)
 ## Running under: Debian GNU/Linux 10 (buster)
## CPU model: AMD Ryzen 7 1700 Eight-Core Processor
@@ -236,7 +190,8 @@

Contents

diff --git a/docs/news/index.html b/docs/news/index.html index c2b5865f..fc9a0765 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -129,9 +129,19 @@
-
+

-mkin 0.9.49.9 (unreleased) Unreleased +mkin 0.9.49.10 (unreleased) Unreleased +

+
    +
  • ‘endpoints’: Don’t return the SFORB list component if it’s empty. This reduces distraction and complies with the documentation

  • +
  • Article in compiled models: Add some platform specific code and suppress warnings about zero values being removed from the FOCUS D dataset

  • +
  • ‘plot.mmkin’: Add the argument ‘standardized’ to avoid warnings that occurred when it was passed as part of the additional arguments captured by the dots (…)

  • +
+
+
+

+mkin 0.9.49.9 (2020-03-31) 2020-03-31

  • ‘mkinmod’: Use pkgbuild::has_compiler instead of Sys.which(‘gcc’), as the latter will often fail even if Rtools are installed

  • @@ -756,7 +766,8 @@

    Contents

    @@ -171,9 +171,6 @@ advantage that the SFORB model can also be used for metabolites.

    endpoints(fit)
#> $ff #> logical(0) #> -#> $SFORB -#> logical(0) -#> #> $distimes #> DT50 DT90 DT50back #> parent 1.785233 15.1479 4.559973 diff --git a/docs/reference/plot.mmkin.html b/docs/reference/plot.mmkin.html index 9d41b4c1..be60f228 100644 --- a/docs/reference/plot.mmkin.html +++ b/docs/reference/plot.mmkin.html @@ -149,6 +149,7 @@ the fit of at least one model to the same dataset is shown.

main = "auto", legends = 1, resplot = c("time", "errmod"), + standardized = FALSE, show_errmin = TRUE, errmin_var = "All data", errmin_digits = 3, @@ -179,6 +180,12 @@ column.

+ + + + diff --git a/man/endpoints.Rd b/man/endpoints.Rd index 13182369..be180737 100644 --- a/man/endpoints.Rd +++ b/man/endpoints.Rd @@ -26,7 +26,7 @@ The function is used internally by \code{\link{summary.mkinfit}}. \examples{ fit <- mkinfit("FOMC", FOCUS_2006_C, quiet = TRUE) - endpoints(fit) + endpoints(fit) } \author{ diff --git a/man/plot.mmkin.Rd b/man/plot.mmkin.Rd index f14e0362..982e8db6 100644 --- a/man/plot.mmkin.Rd +++ b/man/plot.mmkin.Rd @@ -10,6 +10,7 @@ of an mmkin object} main = "auto", legends = 1, resplot = c("time", "errmod"), + standardized = FALSE, show_errmin = TRUE, errmin_var = "All data", errmin_digits = 3, @@ -31,6 +32,10 @@ column.} \code{\link{mkinresplot}}, or as squared residuals against predicted values, with the error model, using \code{\link{mkinerrplot}}.} +\item{standardized}{Should the residuals be standardized? This option +is passed to \code{\link{mkinresplot}}, it only takes effect if +`resplot = "time"`.} + \item{show_errmin}{Should the chi2 error level be shown on top of the plots to the left?} diff --git a/test.log b/test.log index 77130814..84b13a10 100644 --- a/test.log +++ b/test.log @@ -2,35 +2,35 @@ Loading mkin Testing mkin ✔ | OK F W S | Context ✔ | 2 | Export dataset for reading into CAKE -✔ | 13 | Results for FOCUS D established in expertise for UBA (Ranke 2014) [3.7 s] -✔ | 4 | Calculation of FOCUS chi2 error levels [2.3 s] -✔ | 4 | Fitting the SFORB model [1.8 s] +✔ | 13 | Results for FOCUS D established in expertise for UBA (Ranke 2014) [3.5 s] +✔ | 4 | Calculation of FOCUS chi2 error levels [2.2 s] +✔ | 4 | Fitting the SFORB model [1.7 s] ✔ | 5 | Calculation of Akaike weights -✔ | 10 | Confidence intervals and p-values [10.7 s] -✔ | 14 | Error model fitting [42.8 s] -✔ | 6 | Test fitting the decline of metabolites from their maximum [0.8 s] -✔ | 1 | Fitting the logistic model [1.0 s] +✔ | 10 | Confidence intervals and p-values [9.6 s] +✔ | 14 | Error model fitting [38.4 s] +✔ | 6 | Test fitting the decline of metabolites from their maximum [0.7 s] +✔ | 1 | Fitting the logistic model [0.9 s] ✔ | 1 | Test dataset class mkinds used in gmkin -✔ | 12 | Special cases of mkinfit calls [2.5 s] +✔ | 12 | Special cases of mkinfit calls [2.2 s] ✔ | 9 | mkinmod model generation and printing [0.2 s] -✔ | 3 | Model predictions with mkinpredict [0.4 s] -✔ | 16 | Evaluations according to 2015 NAFTA guidance [4.4 s] -✔ | 4 | Calculation of maximum time weighted average concentrations (TWAs) [2.3 s] +✔ | 3 | Model predictions with mkinpredict [0.3 s] +✔ | 16 | Evaluations according to 2015 NAFTA guidance [4.2 s] +✔ | 4 | Calculation of maximum time weighted average concentrations (TWAs) [2.2 s] ✔ | 3 | Summary ✔ | 11 | Plotting [0.6 s] ✔ | 4 | AIC calculation ✔ | 2 | Residuals extracted from mkinfit models -✔ | 2 | Complex test case from Schaefer et al. (2007) Piacenza paper [5.7 s] +✔ | 2 | Complex test case from Schaefer et al. (2007) Piacenza paper [5.3 s] ✔ | 1 | Summaries of old mkinfit objects -✔ | 4 | Results for synthetic data established in expertise for UBA (Ranke 2014) [7.7 s] -✔ | 7 1 | Hypothesis tests [35.7 s] +✔ | 4 | Results for synthetic data established in expertise for UBA (Ranke 2014) [7.1 s] +✔ | 7 1 | Hypothesis tests [32.5 s] ──────────────────────────────────────────────────────────────────────────────── test_tests.R:60: skip: We can do a likelihood ratio test using an update specification Reason: This errors out if called by testthat while it works in a normal R session ──────────────────────────────────────────────────────────────────────────────── ══ Results ═════════════════════════════════════════════════════════════════════ -Duration: 123.0 s +Duration: 112.1 s OK: 138 Failed: 0 diff --git a/tests/testthat/FOCUS_2006_D.csf b/tests/testthat/FOCUS_2006_D.csf index a7f8edaf..fe5e481a 100644 --- a/tests/testthat/FOCUS_2006_D.csf +++ b/tests/testthat/FOCUS_2006_D.csf @@ -5,7 +5,7 @@ Description: MeasurementUnits: % AR TimeUnits: days Comments: Created using mkin::CAKE_export -Date: 2020-03-31 +Date: 2020-04-01 Optimiser: IRLS [Data] diff --git a/vignettes/web_only/FOCUS_Z.R b/vignettes/web_only/FOCUS_Z.R new file mode 100644 index 00000000..0c19794e --- /dev/null +++ b/vignettes/web_only/FOCUS_Z.R @@ -0,0 +1,115 @@ +## ---- include = FALSE--------------------------------------------------------- +require(knitr) +options(digits = 5) +opts_chunk$set(engine='R', tidy = FALSE) + +## ---- echo = TRUE, fig = TRUE, fig.width = 8, fig.height = 7------------------ +library(mkin, quietly = TRUE) +LOD = 0.5 +FOCUS_2006_Z = data.frame( + t = c(0, 0.04, 0.125, 0.29, 0.54, 1, 2, 3, 4, 7, 10, 14, 21, + 42, 61, 96, 124), + Z0 = c(100, 81.7, 70.4, 51.1, 41.2, 6.6, 4.6, 3.9, 4.6, 4.3, 6.8, + 2.9, 3.5, 5.3, 4.4, 1.2, 0.7), + Z1 = c(0, 18.3, 29.6, 46.3, 55.1, 65.7, 39.1, 36, 15.3, 5.6, 1.1, + 1.6, 0.6, 0.5 * LOD, NA, NA, NA), + Z2 = c(0, NA, 0.5 * LOD, 2.6, 3.8, 15.3, 37.2, 31.7, 35.6, 14.5, + 0.8, 2.1, 1.9, 0.5 * LOD, NA, NA, NA), + Z3 = c(0, NA, NA, NA, NA, 0.5 * LOD, 9.2, 13.1, 22.3, 28.4, 32.5, + 25.2, 17.2, 4.8, 4.5, 2.8, 4.4)) + +FOCUS_2006_Z_mkin <- mkin_wide_to_long(FOCUS_2006_Z) + +## ----FOCUS_2006_Z_fits_1, echo=TRUE, fig.height=6----------------------------- +Z.2a <- mkinmod(Z0 = mkinsub("SFO", "Z1"), + Z1 = mkinsub("SFO")) +m.Z.2a <- mkinfit(Z.2a, FOCUS_2006_Z_mkin, quiet = TRUE) +plot_sep(m.Z.2a) +summary(m.Z.2a, data = FALSE)$bpar + +## ----FOCUS_2006_Z_fits_2, echo=TRUE, fig.height=6----------------------------- +Z.2a.ff <- mkinmod(Z0 = mkinsub("SFO", "Z1"), + Z1 = mkinsub("SFO"), + use_of_ff = "max") + +m.Z.2a.ff <- mkinfit(Z.2a.ff, FOCUS_2006_Z_mkin, quiet = TRUE) +plot_sep(m.Z.2a.ff) +summary(m.Z.2a.ff, data = FALSE)$bpar + +## ----FOCUS_2006_Z_fits_3, echo=TRUE, fig.height=6----------------------------- +Z.3 <- mkinmod(Z0 = mkinsub("SFO", "Z1", sink = FALSE), + Z1 = mkinsub("SFO"), use_of_ff = "max") +m.Z.3 <- mkinfit(Z.3, FOCUS_2006_Z_mkin, quiet = TRUE) +plot_sep(m.Z.3) +summary(m.Z.3, data = FALSE)$bpar + +## ----FOCUS_2006_Z_fits_5, echo=TRUE, fig.height=7----------------------------- +Z.5 <- mkinmod(Z0 = mkinsub("SFO", "Z1", sink = FALSE), + Z1 = mkinsub("SFO", "Z2", sink = FALSE), + Z2 = mkinsub("SFO"), use_of_ff = "max") +m.Z.5 <- mkinfit(Z.5, FOCUS_2006_Z_mkin, quiet = TRUE) +plot_sep(m.Z.5) + +## ----FOCUS_2006_Z_fits_6, echo=TRUE, fig.height=8----------------------------- +Z.FOCUS <- mkinmod(Z0 = mkinsub("SFO", "Z1", sink = FALSE), + Z1 = mkinsub("SFO", "Z2", sink = FALSE), + Z2 = mkinsub("SFO", "Z3"), + Z3 = mkinsub("SFO"), + use_of_ff = "max") +m.Z.FOCUS <- mkinfit(Z.FOCUS, FOCUS_2006_Z_mkin, + parms.ini = m.Z.5$bparms.ode, + quiet = TRUE) +plot_sep(m.Z.FOCUS) +summary(m.Z.FOCUS, data = FALSE)$bpar +endpoints(m.Z.FOCUS) + +## ----FOCUS_2006_Z_fits_7, echo=TRUE, fig.height=8----------------------------- +Z.mkin.1 <- mkinmod(Z0 = mkinsub("SFO", "Z1", sink = FALSE), + Z1 = mkinsub("SFO", "Z2", sink = FALSE), + Z2 = mkinsub("SFO", "Z3"), + Z3 = mkinsub("SFORB")) +m.Z.mkin.1 <- mkinfit(Z.mkin.1, FOCUS_2006_Z_mkin, quiet = TRUE) +plot_sep(m.Z.mkin.1) +summary(m.Z.mkin.1, data = FALSE)$cov.unscaled + +## ----FOCUS_2006_Z_fits_9, echo=TRUE, fig.height=8----------------------------- +Z.mkin.3 <- mkinmod(Z0 = mkinsub("SFORB", "Z1", sink = FALSE), + Z1 = mkinsub("SFO", "Z2", sink = FALSE), + Z2 = mkinsub("SFO")) +m.Z.mkin.3 <- mkinfit(Z.mkin.3, FOCUS_2006_Z_mkin, quiet = TRUE) +plot_sep(m.Z.mkin.3) + +## ----FOCUS_2006_Z_fits_10, echo=TRUE, fig.height=8---------------------------- +Z.mkin.4 <- mkinmod(Z0 = mkinsub("SFORB", "Z1", sink = FALSE), + Z1 = mkinsub("SFO", "Z2", sink = FALSE), + Z2 = mkinsub("SFO", "Z3"), + Z3 = mkinsub("SFO")) +m.Z.mkin.4 <- mkinfit(Z.mkin.4, FOCUS_2006_Z_mkin, + parms.ini = m.Z.mkin.3$bparms.ode, + quiet = TRUE) +plot_sep(m.Z.mkin.4) + +## ----FOCUS_2006_Z_fits_11, echo=TRUE, fig.height=8---------------------------- +Z.mkin.5 <- mkinmod(Z0 = mkinsub("SFORB", "Z1", sink = FALSE), + Z1 = mkinsub("SFO", "Z2", sink = FALSE), + Z2 = mkinsub("SFO", "Z3"), + Z3 = mkinsub("SFORB")) +m.Z.mkin.5 <- mkinfit(Z.mkin.5, FOCUS_2006_Z_mkin, + parms.ini = m.Z.mkin.4$bparms.ode[1:4], + quiet = TRUE) +plot_sep(m.Z.mkin.5) + +## ----FOCUS_2006_Z_fits_11a, echo=TRUE----------------------------------------- +m.Z.mkin.5a <- mkinfit(Z.mkin.5, FOCUS_2006_Z_mkin, + parms.ini = c(m.Z.mkin.5$bparms.ode[1:7], + k_Z3_bound_free = 0), + fixed_parms = "k_Z3_bound_free", + quiet = TRUE) +plot_sep(m.Z.mkin.5a) + +## ----FOCUS_2006_Z_fits_11b, echo=TRUE----------------------------------------- +mkinparplot(m.Z.mkin.5a) + +## ----FOCUS_2006_Z_fits_11b_endpoints, echo=TRUE------------------------------- +endpoints(m.Z.mkin.5a) + diff --git a/vignettes/web_only/FOCUS_Z.html b/vignettes/web_only/FOCUS_Z.html index d7f0f88c..e8e6e2b4 100644 --- a/vignettes/web_only/FOCUS_Z.html +++ b/vignettes/web_only/FOCUS_Z.html @@ -1,17 +1,17 @@ - + - + - + Example evaluation of FOCUS dataset Z @@ -69,8 +69,6 @@ overflow: auto; margin-left: 2%; position: fixed; border: 1px solid #ccc; -webkit-border-radius: 6px; -moz-border-radius: 6px; border-radius: 6px; } @@ -98,10 +96,15 @@ font-size: 12px; .tocify-subheader .tocify-subheader { text-indent: 30px; } - .tocify-subheader .tocify-subheader .tocify-subheader { text-indent: 40px; } +.tocify-subheader .tocify-subheader .tocify-subheader .tocify-subheader { +text-indent: 50px; +} +.tocify-subheader .tocify-subheader .tocify-subheader .tocify-subheader .tocify-subheader { +text-indent: 60px; +} .tocify .tocify-item > a, .tocify .nav-list .nav-header { margin: 0px; @@ -504,13 +507,13 @@ float: none; item.append($("", { - "text": self.text() + "html": self.html() })); } else { - item.text(self.text()); + item.html(self.html()); } @@ -1280,12 +1283,12 @@ window.initializeCodeFolding = function(show) { var currentIndex = 1; // select all R code blocks - var rCodeBlocks = $('pre.r, pre.python, pre.bash, pre.sql, pre.cpp, pre.stan'); + var rCodeBlocks = $('pre.r, pre.python, pre.bash, pre.sql, pre.cpp, pre.stan, pre.julia'); rCodeBlocks.each(function() { // create a collapsable div to wrap the code in var div = $('
'); - if (show) + if (show || $(this)[0].classList.contains('fold-show')) div.addClass('in'); var id = 'rcode-643E0F36' + currentIndex++; div.attr('id', id); @@ -1387,9 +1390,7 @@ h6 { - - -
- - - - +.tabset-dropdown > .nav-tabs { + display: inline-table; + max-height: 500px; + min-height: 44px; + overflow-y: auto; + background: white; + border: 1px solid #ddd; + border-radius: 4px; +} +.tabset-dropdown > .nav-tabs > li.active:before { + content: ""; + font-family: 'Glyphicons Halflings'; + display: inline-block; + padding: 10px; + border-right: 1px solid #ddd; +} +.tabset-dropdown > .nav-tabs.nav-tabs-open > li.active:before { + content: ""; + border: none; +} +.tabset-dropdown > .nav-tabs.nav-tabs-open:before { + content: ""; + font-family: 'Glyphicons Halflings'; + display: inline-block; + padding: 10px; + border-right: 1px solid #ddd; +} - + + + + + + + +
+ +
@@ -1547,8 +1582,8 @@ div.tocify {

Example evaluation of FOCUS dataset Z

-

Johannes Ranke

-

2018-09-14

+

Johannes Ranke

+

2020-04-02

@@ -1579,44 +1614,53 @@ FOCUS_2006_Z_mkin <- mkin_wide_to_long(FOCUS_2006_Z)
Z.2a <- mkinmod(Z0 = mkinsub("SFO", "Z1"),
                 Z1 = mkinsub("SFO"))
## Successfully compiled differential equation model from auto-generated C code.
-
m.Z.2a <- mkinfit(Z.2a, FOCUS_2006_Z_mkin, quiet = TRUE)
-plot_sep(m.Z.2a)
-

+
m.Z.2a <- mkinfit(Z.2a, FOCUS_2006_Z_mkin, quiet = TRUE)
+
## Warning in mkinfit(Z.2a, FOCUS_2006_Z_mkin, quiet = TRUE): Observations with
+## value of zero were removed from the data
+
plot_sep(m.Z.2a)
+

summary(m.Z.2a, data = FALSE)$bpar
-
##             Estimate se_notrans    t value     Pr(>t) Lower Upper
-## Z0_0      9.7015e+01   3.553140 2.7304e+01 1.6793e-21    NA    NA
-## k_Z0_sink 1.2790e-11   0.226895 5.6368e-11 5.0000e-01    NA    NA
-## k_Z0_Z1   2.2360e+00   0.165073 1.3546e+01 7.3938e-14    NA    NA
-## k_Z1_sink 4.8212e-01   0.065854 7.3212e+00 3.5520e-08    NA    NA
+
##             Estimate se_notrans    t value     Pr(>t)    Lower    Upper
+## Z0_0      9.7015e+01   3.394528 2.8580e+01 6.4978e-21 91.66556 102.3642
+## k_Z0_sink 1.6067e-10   0.225471 7.1261e-10 5.0000e-01  0.00000      Inf
+## k_Z0_Z1   2.2360e+00   0.159156 1.4049e+01 1.1405e-13  1.95303   2.5600
+## k_Z1_sink 4.8212e-01   0.065492 7.3616e+00 5.1697e-08  0.40341   0.5762
+## sigma     4.8041e+00   0.637651 7.5341e+00 3.4463e-08  3.52677   6.0815

As obvious from the parameter summary (the component of the summary), the kinetic rate constant from parent compound Z to sink is very small and the t-test for this parameter suggests that it is not significantly different from zero. This suggests, in agreement with the analysis in the FOCUS kinetics report, to simplify the model by removing the pathway to sink.

A similar result can be obtained when formation fractions are used in the model formulation:

Z.2a.ff <- mkinmod(Z0 = mkinsub("SFO", "Z1"),
                    Z1 = mkinsub("SFO"),
                    use_of_ff = "max")
## Successfully compiled differential equation model from auto-generated C code.
-
m.Z.2a.ff <- mkinfit(Z.2a.ff, FOCUS_2006_Z_mkin, quiet = TRUE)
-plot_sep(m.Z.2a.ff)
-

+
m.Z.2a.ff <- mkinfit(Z.2a.ff, FOCUS_2006_Z_mkin, quiet = TRUE)
+
## Warning in mkinfit(Z.2a.ff, FOCUS_2006_Z_mkin, quiet = TRUE): Observations with
+## value of zero were removed from the data
+
plot_sep(m.Z.2a.ff)
+

summary(m.Z.2a.ff, data = FALSE)$bpar
-
##            Estimate se_notrans t value     Pr(>t) Lower Upper
-## Z0_0       97.01488   3.553145 27.3039 1.6793e-21    NA    NA
-## k_Z0        2.23601   0.216849 10.3114 3.6623e-11    NA    NA
-## k_Z1        0.48212   0.065854  7.3211 3.5520e-08    NA    NA
-## f_Z0_to_Z1  1.00000   0.101473  9.8548 9.7068e-11    NA    NA
+
##            Estimate se_notrans t value     Pr(>t)    Lower    Upper
+## Z0_0       97.01488   3.301084 29.3888 3.2971e-21 91.66556 102.3642
+## k_Z0        2.23601   0.207078 10.7979 3.3309e-11  1.95303   2.5600
+## k_Z1        0.48212   0.063265  7.6207 2.8155e-08  0.40341   0.5762
+## f_Z0_to_Z1  1.00000   0.094764 10.5525 5.3560e-11  0.00000   1.0000
+## sigma       4.80411   0.635638  7.5579 3.2592e-08  3.52677   6.0815

Here, the ilr transformed formation fraction fitted in the model takes a very large value, and the backtransformed formation fraction from parent Z to Z1 is practically unity. Here, the covariance matrix used for the calculation of confidence intervals is not returned as the model is overparameterised.

A simplified model is obtained by removing the pathway to the sink.

In the following, we use the parameterisation with formation fractions in order to be able to compare with the results in the FOCUS guidance, and as it makes it easier to use parameters obtained in a previous fit when adding a further metabolite.

Z.3 <- mkinmod(Z0 = mkinsub("SFO", "Z1", sink = FALSE),
                Z1 = mkinsub("SFO"), use_of_ff = "max")
## Successfully compiled differential equation model from auto-generated C code.
-
m.Z.3 <- mkinfit(Z.3, FOCUS_2006_Z_mkin, quiet = TRUE)
-plot_sep(m.Z.3)
-

+
m.Z.3 <- mkinfit(Z.3, FOCUS_2006_Z_mkin, quiet = TRUE)
+
## Warning in mkinfit(Z.3, FOCUS_2006_Z_mkin, quiet = TRUE): Observations with
+## value of zero were removed from the data
+
plot_sep(m.Z.3)
+

summary(m.Z.3, data = FALSE)$bpar
-
##      Estimate se_notrans t value     Pr(>t)    Lower   Upper
-## Z0_0 97.01488   2.681772  36.176 2.3636e-25 91.52152 102.508
-## k_Z0  2.23601   0.146861  15.225 2.2464e-15  1.95453   2.558
-## k_Z1  0.48212   0.042687  11.294 3.0686e-12  0.40216   0.578
+
##       Estimate se_notrans t value     Pr(>t)    Lower    Upper
+## Z0_0  97.01488   2.597342  37.352 2.0106e-24 91.67597 102.3538
+## k_Z0   2.23601   0.146904  15.221 9.1477e-15  1.95354   2.5593
+## k_Z1   0.48212   0.041727  11.554 4.8268e-12  0.40355   0.5760
+## sigma  4.80411   0.620208   7.746 1.6110e-08  3.52925   6.0790

As there is only one transformation product for Z0 and no pathway to sink, the formation fraction is internally fixed to unity.

@@ -1626,9 +1670,11 @@ plot_sep(m.Z.3) Z1 = mkinsub("SFO", "Z2", sink = FALSE), Z2 = mkinsub("SFO"), use_of_ff = "max")
## Successfully compiled differential equation model from auto-generated C code.
-
m.Z.5 <- mkinfit(Z.5, FOCUS_2006_Z_mkin, quiet = TRUE)
-plot_sep(m.Z.5)
-

+
m.Z.5 <- mkinfit(Z.5, FOCUS_2006_Z_mkin, quiet = TRUE)
+
## Warning in mkinfit(Z.5, FOCUS_2006_Z_mkin, quiet = TRUE): Observations with
+## value of zero were removed from the data
+
plot_sep(m.Z.5)
+

Finally, metabolite Z3 is added to the model. We use the optimised differential equation parameter values from the previous fit in order to accelerate the optimization.

Z.FOCUS <- mkinmod(Z0 = mkinsub("SFO", "Z1", sink = FALSE),
                    Z1 = mkinsub("SFO", "Z2", sink = FALSE),
@@ -1639,32 +1685,30 @@ plot_sep(m.Z.5)
m.Z.FOCUS <- mkinfit(Z.FOCUS, FOCUS_2006_Z_mkin,
                      parms.ini = m.Z.5$bparms.ode,
                      quiet = TRUE)
-
## Warning in mkinfit(Z.FOCUS, FOCUS_2006_Z_mkin, parms.ini = m.Z.5$bparms.ode, : Optimisation by method Port did not converge:
-## false convergence (8)
+
## Warning in mkinfit(Z.FOCUS, FOCUS_2006_Z_mkin, parms.ini = m.Z.5$bparms.ode, :
+## Observations with value of zero were removed from the data
plot_sep(m.Z.FOCUS)
-

+

summary(m.Z.FOCUS, data = FALSE)$bpar
##             Estimate se_notrans t value     Pr(>t)     Lower      Upper
-## Z0_0       96.837112   2.058861 47.0343 5.5877e-44 92.703779 100.970445
-## k_Z0        2.215368   0.118098 18.7587 7.6563e-25  1.990525   2.465609
-## k_Z1        0.478302   0.029289 16.3302 3.3408e-22  0.422977   0.540864
-## k_Z2        0.451617   0.044214 10.2144 3.1133e-14  0.371034   0.549702
-## k_Z3        0.058693   0.014296  4.1056 7.2924e-05  0.035994   0.095705
-## f_Z2_to_Z3  0.471516   0.057057  8.2639 2.8156e-11  0.360381   0.585548
+## Z0_0 96.838599 1.994271 48.5584 4.0281e-42 92.826628 100.850570 +## k_Z0 2.215405 0.118459 18.7019 1.0415e-23 1.989466 2.467003 +## k_Z1 0.478298 0.028257 16.9268 6.2399e-22 0.424701 0.538660 +## k_Z2 0.451618 0.042137 10.7177 1.6306e-14 0.374328 0.544866 +## k_Z3 0.058693 0.015246 3.8499 1.7803e-04 0.034805 0.098977 +## f_Z2_to_Z3 0.471509 0.058352 8.0804 9.6629e-11 0.357739 0.588318 +## sigma 3.984431 0.383402 10.3923 4.5575e-14 3.213126 4.755736
endpoints(m.Z.FOCUS)
## $ff
 ##   Z2_Z3 Z2_sink 
-## 0.47152 0.52848 
-## 
-## $SFORB
-## logical(0)
+## 0.47151 0.52849 
 ## 
 ## $distimes
 ##        DT50    DT90
 ## Z0  0.31288  1.0394
-## Z1  1.44918  4.8141
+## Z1  1.44919  4.8141
 ## Z2  1.53481  5.0985
-## Z3 11.80973 39.2311
+## Z3 11.80963 39.2308

This fit corresponds to the final result chosen in Appendix 7 of the FOCUS report. Confidence intervals returned by mkin are based on internally transformed parameters, however.

@@ -1676,9 +1720,11 @@ plot_sep(m.Z.5) Z2 = mkinsub("SFO", "Z3"), Z3 = mkinsub("SFORB"))
## Successfully compiled differential equation model from auto-generated C code.
-
m.Z.mkin.1 <- mkinfit(Z.mkin.1, FOCUS_2006_Z_mkin, quiet = TRUE)
-plot_sep(m.Z.mkin.1)
-

+
m.Z.mkin.1 <- mkinfit(Z.mkin.1, FOCUS_2006_Z_mkin, quiet = TRUE)
+
## Warning in mkinfit(Z.mkin.1, FOCUS_2006_Z_mkin, quiet = TRUE): Observations with
+## value of zero were removed from the data
+
plot_sep(m.Z.mkin.1)
+

summary(m.Z.mkin.1, data = FALSE)$cov.unscaled
## NULL

Therefore, a further stepwise model building is performed starting from the stage of parent and two metabolites, starting from the assumption that the model fit for the parent compound can be improved by using the SFORB model.

@@ -1686,9 +1732,11 @@ plot_sep(m.Z.mkin.1) Z1 = mkinsub("SFO", "Z2", sink = FALSE), Z2 = mkinsub("SFO"))
## Successfully compiled differential equation model from auto-generated C code.
-
m.Z.mkin.3 <- mkinfit(Z.mkin.3, FOCUS_2006_Z_mkin, quiet = TRUE)
-plot_sep(m.Z.mkin.3)
-

+
m.Z.mkin.3 <- mkinfit(Z.mkin.3, FOCUS_2006_Z_mkin, quiet = TRUE)
+
## Warning in mkinfit(Z.mkin.3, FOCUS_2006_Z_mkin, quiet = TRUE): Observations with
+## value of zero were removed from the data
+
plot_sep(m.Z.mkin.3)
+

This results in a much better representation of the behaviour of the parent compound Z0.

Finally, Z3 is added as well. These models appear overparameterised (no covariance matrix returned) if the sink for Z1 is left in the models.

Z.mkin.4 <- mkinmod(Z0 = mkinsub("SFORB", "Z1", sink = FALSE),
@@ -1698,9 +1746,11 @@ plot_sep(m.Z.mkin.3)
## Successfully compiled differential equation model from auto-generated C code.
m.Z.mkin.4 <- mkinfit(Z.mkin.4, FOCUS_2006_Z_mkin,
                       parms.ini = m.Z.mkin.3$bparms.ode,
-                      quiet = TRUE)
-plot_sep(m.Z.mkin.4)
-

+ quiet = TRUE) +
## Warning in mkinfit(Z.mkin.4, FOCUS_2006_Z_mkin, parms.ini = m.Z.mkin.
+## 3$bparms.ode, : Observations with value of zero were removed from the data
+
plot_sep(m.Z.mkin.4)
+

The error level of the fit, but especially of metabolite Z3, can be improved if the SFORB model is chosen for this metabolite, as this model is capable of representing the tailing of the metabolite decline phase.

Z.mkin.5 <- mkinmod(Z0 = mkinsub("SFORB", "Z1", sink = FALSE),
                     Z1 = mkinsub("SFO", "Z2", sink = FALSE),
@@ -1709,21 +1759,25 @@ plot_sep(m.Z.mkin.4)
## Successfully compiled differential equation model from auto-generated C code.
m.Z.mkin.5 <- mkinfit(Z.mkin.5, FOCUS_2006_Z_mkin,
                       parms.ini = m.Z.mkin.4$bparms.ode[1:4],
-                      quiet = TRUE)
-plot_sep(m.Z.mkin.5)
-

+ quiet = TRUE) +
## Warning in mkinfit(Z.mkin.5, FOCUS_2006_Z_mkin, parms.ini = m.Z.mkin.
+## 4$bparms.ode[1:4], : Observations with value of zero were removed from the data
+
plot_sep(m.Z.mkin.5)
+

The summary view of the backtransformed parameters shows that we get no confidence intervals due to overparameterisation. As the optimized is excessively small, it seems reasonable to fix it to zero.

m.Z.mkin.5a <- mkinfit(Z.mkin.5, FOCUS_2006_Z_mkin,
                        parms.ini = c(m.Z.mkin.5$bparms.ode[1:7],
                                      k_Z3_bound_free = 0),
                        fixed_parms = "k_Z3_bound_free",
-                       quiet = TRUE)
-plot_sep(m.Z.mkin.5a)
-

+ quiet = TRUE) +
## Warning in mkinfit(Z.mkin.5, FOCUS_2006_Z_mkin, parms.ini = c(m.Z.mkin.
+## 5$bparms.ode[1:7], : Observations with value of zero were removed from the data
+
plot_sep(m.Z.mkin.5a)
+

As expected, the residual plots for Z0 and Z3 are more random than in the case of the all SFO model for which they were shown above. In conclusion, the model is proposed as the best-fit model for the dataset from Appendix 7 of the FOCUS report.

A graphical representation of the confidence intervals can finally be obtained.

mkinparplot(m.Z.mkin.5a)
-

+

The endpoints obtained with this model are

endpoints(m.Z.mkin.5a)
## $ff
@@ -1732,14 +1786,14 @@ plot_sep(m.Z.mkin.5a)
## ## $SFORB ## Z0_b1 Z0_b2 Z3_b1 Z3_b2 -## 2.4471382 0.0075127 0.0800075 0.0000000 +## 2.4471363 0.0075126 0.0800072 0.0000000 ## ## $distimes ## DT50 DT90 DT50_Z0_b1 DT50_Z0_b2 DT50_Z3_b1 DT50_Z3_b2 -## Z0 0.3043 1.1848 0.28325 92.264 NA NA +## Z0 0.3043 1.1848 0.28325 92.265 NA NA ## Z1 1.5148 5.0320 NA NA NA NA ## Z2 1.6414 5.4526 NA NA NA NA -## Z3 NA NA NA NA 8.6635 Inf +## Z3 NA NA NA NA 8.6636 Inf

It is clear the degradation rate of Z3 towards the end of the experiment is very low as DT50_Z3_b2 (the second Eigenvalue of the system of two differential equations representing the SFORB system for Z3, corresponding to the slower rate constant of the DFOP model) is reported to be infinity. However, this appears to be a feature of the data.

@@ -1772,6 +1826,54 @@ $(document).ready(function () { + + + + + + + + + - - - - + + + + + + + +
+ +
@@ -1613,25 +1582,36 @@ div.tocify {

Performance benefit by using compiled model definitions in mkin

-

Johannes Ranke

-

2019-04-04

+

Johannes Ranke

+

2020-04-02

-
-

Model that can also be solved with Eigenvalues

-

This evaluation is taken from the example section of mkinfit. When using an mkin version equal to or greater than 0.9-36 and a C compiler (gcc) is available, you will see a message that the model is being compiled from autogenerated C code when defining a model using mkinmod. The mkinmod() function checks for presence of the gcc compiler using

-
Sys.which("gcc")
-
##            gcc 
-## "/usr/bin/gcc"
+
+

How to benefit from compiled models

+

When using an mkin version equal to or greater than 0.9-36 and a C compiler is available, you will see a message that the model is being compiled from autogenerated C code when defining a model using mkinmod. Starting from version 0.9.49.9, the mkinmod() function checks for presence of a compiler using

+
pkgbuild::has_compiler()
+

In previous versions, it used Sys.which("gcc") for this check.

+
+

Platform specific notes

+

On Linux, you need to have the essential build tools like make and gcc or clang installed. On Debian based linux distributions, these will be pulled in by installing the build-essential package.

+

On MacOS, which I do not use personally, I have had reports that a compiler is available by default.

+

On Windows, you need to install Rtools and have the path to its bin directory in your PATH variable. You do not need to modify the PATH variable when installing Rtools. Instead, I would recommend to put the line

+
Sys.setenv(PATH = paste("C:/Rtools/bin", Sys.getenv("PATH"), sep=";"))
+

into your .Rprofile startup file. This is just a text file with some R code that is executed when your R session starts. It has to be named .Rprofile and has to be located in your home directory, which will generally be your Documents folder. You can check the location of the home directory used by R by issuing

+
Sys.getenv("HOME")
+
+
+
+

Comparison with Eigenvalue based solutions

First, we build a simple degradation model for a parent compound with one metabolite.

library("mkin", quietly = TRUE)
 SFO_SFO <- mkinmod(
   parent = mkinsub("SFO", "m1"),
   m1 = mkinsub("SFO"))
## Successfully compiled differential equation model from auto-generated C code.
-

We can compare the performance of the Eigenvalue based solution against the compiled version and the R implementation of the differential equations using the benchmark package.

+

We can compare the performance of the Eigenvalue based solution against the compiled version and the R implementation of the differential equations using the benchmark package. In the output of below code, the warnings about zero being removed from the FOCUS D dataset are suppressed.

if (require(rbenchmark)) {
   b.1 <- benchmark(
     "deSolve, not compiled" = mkinfit(SFO_SFO, FOCUS_2006_D,
@@ -1648,16 +1628,15 @@ SFO_SFO <- mkinmod(
   factor_SFO_SFO <- NA
   print("R package rbenchmark is not available")
 }
-
## Loading required package: rbenchmark
##                    test replications elapsed relative user.self sys.self
-## 3     deSolve, compiled            3   3.533    1.000     3.531        0
-## 1 deSolve, not compiled            3  46.050   13.034    46.030        0
-## 2      Eigenvalue based            3   5.068    1.434     5.066        0
+## 3     deSolve, compiled            3   3.148    1.000     3.146    0.000
+## 1 deSolve, not compiled            3  28.920    9.187    28.904    0.001
+## 2      Eigenvalue based            3   4.442    1.411     4.439    0.000
 ##   user.child sys.child
 ## 3          0         0
 ## 1          0         0
 ## 2          0         0
-

We see that using the compiled model is by a factor of around 13 faster than using the R version with the default ode solver, and it is even faster than the Eigenvalue based solution implemented in R which does not need iterative solution of the ODEs.

+

We see that using the compiled model is by a factor of around 9 faster than using the R version with the default ode solver, and it is even faster than the Eigenvalue based solution implemented in R which does not need iterative solution of the ODEs.

Model that can not be solved with Eigenvalues

@@ -1680,16 +1659,16 @@ SFO_SFO <- mkinmod( }
## Successfully compiled differential equation model from auto-generated C code.
##                    test replications elapsed relative user.self sys.self
-## 2     deSolve, compiled            3   4.934    1.000     4.931        0
-## 1 deSolve, not compiled            3  72.993   14.794    72.961        0
+## 2     deSolve, compiled            3   4.879    1.000     4.877        0
+## 1 deSolve, not compiled            3  53.551   10.976    53.525        0
 ##   user.child sys.child
 ## 2          0         0
 ## 1          0         0
-

Here we get a performance benefit of a factor of 15 using the version of the differential equation model compiled from C code!

-

This vignette was built with mkin 0.9.49.1 on

-
## R version 3.5.3 (2019-03-11)
+

Here we get a performance benefit of a factor of 11 using the version of the differential equation model compiled from C code!

+

This vignette was built with mkin 0.9.49.9 on

+
## R version 3.6.3 (2020-02-29)
 ## Platform: x86_64-pc-linux-gnu (64-bit)
-## Running under: Debian GNU/Linux 9 (stretch)
+## Running under: Debian GNU/Linux 10 (buster)
## CPU model: AMD Ryzen 7 1700 Eight-Core Processor
@@ -1713,6 +1692,54 @@ $(document).ready(function () { + + + + + + + + +

Should the residuals plotted against time, using mkinresplot, or as squared residuals against predicted values, with the error model, using mkinerrplot.

standardized

Should the residuals be standardized? This option +is passed to mkinresplot, it only takes effect if +`resplot = "time"`.

show_errmin