diff options
46 files changed, 1114 insertions, 113 deletions
| diff --git a/DESCRIPTION b/DESCRIPTION index b0bcc39d..0bc78ed2 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,8 +1,8 @@  Package: mkin  Type: Package  Title: Kinetic Evaluation of Chemical Degradation Data -Version: 0.9.49.8 -Date: 2019-11-01 +Version: 0.9.49.9 +Date: 2020-01-09  Authors@R: c(person("Johannes", "Ranke", role = c("aut", "cre", "cph"),                      email = "jranke@uni-bremen.de",                      comment = c(ORCID = "0000-0003-4371-6538")), @@ -12,11 +12,10 @@ Authors@R: c(person("Johannes", "Ranke", role = c("aut", "cre", "cph"),  Description: Calculation routines based on the FOCUS Kinetics Report (2006,    2014).  Includes a function for conveniently defining differential equation    models, model solution based on eigenvalues if possible or using numerical -  solvers and a choice of the optimisation methods made available by the 'FME' -  package.  If a C compiler (on windows: 'Rtools') is installed, differential -  equation models are solved using compiled C functions.  Please note that no -  warranty is implied for correctness of results or fitness for a particular -  purpose. +  solvers.  If a C compiler (on windows: 'Rtools') is installed, differential +  equation models are solved using automatically generated C functions.  Please +  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  Suggests: knitr, rbenchmark, tikzDevice, testthat, rmarkdown, covr, vdiffr, diff --git a/GNUmakefile b/GNUmakefile index 496bb252..58d40e52 100644 --- a/GNUmakefile +++ b/GNUmakefile @@ -12,7 +12,7 @@ WINBIN  := $(PKGSRC)_$(PKGVERS).zip  RBIN ?= $(shell dirname "`which R`")  # Specify package and static documentation directories for subversion on r-forge -RFSVN ?= $(HOME)/svn/kinfit.r-forge +RFSVN ?= $(HOME)/svn/r-forge/kinfit  RFDIR ?= $(RFSVN)/pkg/mkin  SDDIR ?= $(RFSVN)/www/mkin_static @@ -3,9 +3,13 @@  S3method("[",mmkin)  S3method(AIC,mmkin)  S3method(BIC,mmkin) +S3method(aw,mkinfit) +S3method(aw,mmkin)  S3method(confint,mkinfit) +S3method(loftest,mkinfit)  S3method(logLik,mkinfit)  S3method(lrtest,mkinfit) +S3method(lrtest,mmkin)  S3method(mkinpredict,mkinfit)  S3method(mkinpredict,mkinmod)  S3method(nobs,mkinfit) @@ -28,10 +32,12 @@ export(IORE.solution)  export(SFO.solution)  export(SFORB.solution)  export(add_err) +export(aw)  export(backtransform_odeparms)  export(endpoints)  export(ilr)  export(invilr) +export(loftest)  export(logistic.solution)  export(lrtest)  export(max_twa_dfop) @@ -73,8 +79,11 @@ importFrom(parallel,parLapply)  importFrom(stats,AIC)  importFrom(stats,BIC)  importFrom(stats,aggregate) +importFrom(stats,coef)  importFrom(stats,cov2cor)  importFrom(stats,dist) +importFrom(stats,dnorm) +importFrom(stats,lm)  importFrom(stats,logLik)  importFrom(stats,nlminb)  importFrom(stats,nobs) @@ -1,5 +1,9 @@  # mkin 0.9.49.8 (unreleased) +- 'aw': Generic function for calculating Akaike weights, methods for mkinfit objects and mmkin columns + +- 'loftest': Add a lack-of-fit test +  - 'plot_res', 'plot_sep' and 'mkinerrplot': Add the possibility to show standardized residuals and make it the default for fits with error models other than 'const'  - 'lrtest.mkinfit': Improve naming of the compared fits in the case of fixed parameters @@ -10,7 +14,7 @@  - Fix a bug introduced in 0.9.49.6 that occurred if the direct optimisation yielded a higher likelihood than the three-step optimisation in the d_3 algorithm, which caused the fitted parameters of the three-step optimisation to be returned instead of the parameters of the direct optimisation -- Add an 'nobs' method for mkinfit methods, enabling the default 'BIC' method from the stats package. Also, add a 'BIC' method for mmkin column objects. +- Add a 'nobs' method for mkinfit objects, enabling the default 'BIC' method from the stats package. Also, add a 'BIC' method for mmkin column objects.  # mkin 0.9.49.6 (2019-10-31) @@ -0,0 +1,58 @@ +#' Calculate Akaike weights for model averaging +#' +#' Akaike weights are calculated based on the relative +#' expected Kullback-Leibler information as specified +#' by Burnham and Anderson (2004). +#' +#' @param object An [mmkin] column object, containing two or more +#'   [mkinfit] models that have been fitted to the same data, +#'   or an mkinfit object. In the latter case, further mkinfit +#'   objects fitted to the same data should be specified +#'   as dots arguments. +#' @param \dots Not used in the method for [mmkin] column objects, +#'   further [mkinfit] objects in the method for mkinfit objects. +#' @references Burnham KP and Anderson DR (2004) Multimodel +#'   Inference: Understanding AIC and BIC in Model Selection. +#'   *Sociological Methods & Research* **33**(2) 261-304 +#' @md +#' @examples +#' \dontrun{ +#' f_sfo <- mkinfit("SFO", FOCUS_2006_D, quiet = TRUE) +#' f_dfop <- mkinfit("DFOP", FOCUS_2006_D, quiet = TRUE) +#' aw_sfo_dfop <- aw(f_sfo, f_dfop) +#' sum(aw_sfo_dfop) +#' aw_sfo_dfop # SFO gets more weight as it has less parameters and a similar fit +#' f <- mmkin(c("SFO", "FOMC", "DFOP"), list("FOCUS D" = FOCUS_2006_D), cores = 1, quiet = TRUE) +#' aw(f) +#' sum(aw(f)) +#' aw(f[c("SFO", "DFOP")]) +#' } +#' @export +aw <- function(object, ...) UseMethod("aw") + +#' @export +#' @rdname aw +aw.mkinfit <- function(object, ...) { +  oo <- list(...) +  data_object <- object$data[c("time", "variable", "observed")] +  for (i in seq_along(oo)) { +    if (!inherits(oo[[i]], "mkinfit")) stop("Please supply only mkinfit objects") +    data_other_object <- oo[[i]]$data[c("time", "variable", "observed")] +    if (!identical(data_object, data_other_object)) { +      stop("It seems that the mkinfit objects have not all been fitted to the same data") +    } +  } +  all_objects <- list(object, ...) +  AIC_all <- sapply(all_objects, AIC) +  delta_i <- AIC_all - min(AIC_all) +  denom <- sum(exp(-delta_i/2)) +  w_i <- exp(-delta_i/2) / denom +  return(w_i) +} + +#' @export +#' @rdname aw +aw.mmkin <- function(object, ...) { +  if (ncol(object) > 1) stop("Please supply an mmkin column object") +  do.call(aw, object) +} diff --git a/R/loftest.R b/R/loftest.R new file mode 100644 index 00000000..29721e23 --- /dev/null +++ b/R/loftest.R @@ -0,0 +1,112 @@ +#' Lack-of-fit test for models fitted to data with replicates +#' +#' This is a generic function with a method currently only defined for mkinfit +#' objects. It fits an anova model to the data contained in the object and +#' compares the likelihoods using the likelihood ratio test +#' \code{\link[lmtest]{lrtest.default}} from the lmtest package. +#' +#' The anova model is interpreted as the simplest form of an mkinfit model, +#' assuming only a constant variance about the means, but not enforcing any +#' structure of the means, so we have one model parameter for every mean +#' of replicate samples. +#' +#' @param object A model object with a defined loftest method +#' @param \dots Not used +#' @export +loftest <- function(object, ...) { +  UseMethod("loftest") +} + +#' @rdname loftest +#' @importFrom stats logLik lm dnorm coef +#' @seealso lrtest +#' @examples +#' \dontrun{ +#' test_data <- subset(synthetic_data_for_UBA_2014[[12]]$data, name == "parent") +#' sfo_fit <- mkinfit("SFO", test_data, quiet = TRUE) +#' plot_res(sfo_fit) # We see a clear pattern in the residuals +#' loftest(sfo_fit)  # We have a clear lack of fit +#' # +#' # We try a different model (the one that was used to generate the data) +#' dfop_fit <- mkinfit("DFOP", test_data, quiet = TRUE) +#' plot_res(dfop_fit) # We don't see systematic deviations, but heteroscedastic residuals +#' # therefore we should consider adapting the error model, although we have +#' loftest(dfop_fit) # no lack of fit +#' # +#' # This is the anova model used internally for the comparison +#' test_data_anova <- test_data +#' test_data_anova$time <- as.factor(test_data_anova$time) +#' anova_fit <- lm(value ~ time, data = test_data_anova) +#' summary(anova_fit) +#' logLik(anova_fit) # We get the same likelihood and degrees of freedom +#' # +#' test_data_2 <- synthetic_data_for_UBA_2014[[12]]$data +#' m_synth_SFO_lin <- mkinmod(parent = list(type = "SFO", to = "M1"), +#'   M1 = list(type = "SFO", to = "M2"), +#'   M2 = list(type = "SFO"), use_of_ff = "max") +#' sfo_lin_fit <- mkinfit(m_synth_SFO_lin, test_data_2, quiet = TRUE) +#' plot_res(sfo_lin_fit) # not a good model, we try parallel formation +#' loftest(sfo_lin_fit) +#' # +#' m_synth_SFO_par <- mkinmod(parent = list(type = "SFO", to = c("M1", "M2")), +#'   M1 = list(type = "SFO"), +#'   M2 = list(type = "SFO"), use_of_ff = "max") +#' sfo_par_fit <- mkinfit(m_synth_SFO_par, test_data_2, quiet = TRUE) +#' plot_res(sfo_par_fit) # much better for metabolites +#' loftest(sfo_par_fit) +#' # +#' m_synth_DFOP_par <- mkinmod(parent = list(type = "DFOP", to = c("M1", "M2")), +#'   M1 = list(type = "SFO"), +#'   M2 = list(type = "SFO"), use_of_ff = "max") +#' dfop_par_fit <- mkinfit(m_synth_DFOP_par, test_data_2, quiet = TRUE) +#' plot_res(dfop_par_fit) # No visual lack of fit +#' loftest(dfop_par_fit)  # no lack of fit found by the test +#' # +#' # The anova model used for comparison in the case of transformation products +#' test_data_anova_2 <- dfop_par_fit$data +#' test_data_anova_2$variable <- as.factor(test_data_anova_2$variable) +#' test_data_anova_2$time <- as.factor(test_data_anova_2$time) +#' anova_fit_2 <- lm(observed ~ time:variable - 1, data = test_data_anova_2) +#' summary(anova_fit_2) +#' } +#' @export +loftest.mkinfit <- function(object, ...) { + +  name_function <- function(x) { +    object_name <- paste(x$mkinmod$name, "with error model", x$err_mod) +    if (length(x$bparms.fixed) > 0) { +      object_name <- paste(object_name, +        "and fixed parameter(s)", +        paste(names(x$bparms.fixed), collapse = ", ")) +    } +    return(object_name) +  } + +  # Check if we have replicates in the data +  if (max(aggregate(object$data$observed, +    by = list(object$data$variable, object$data$time), length)$x) == 1) { +    stop("Not defined for fits to data without replicates") +  } + +  data_anova <- object$data +  data_anova$time <- as.factor(data_anova$time) +  data_anova$variable <- as.factor(data_anova$variable) +  if (nlevels(data_anova$variable) == 1) { +    object_2 <- lm(observed ~ time - 1, data = data_anova) +  } else { +    object_2 <- lm(observed ~ variable:time - 1, +      data = data_anova) +  } + +  object_2$mkinmod <- list(name = "ANOVA") +  object_2$err_mod <- "const" +  sigma_mle <- sqrt(sum(residuals(object_2)^2)/nobs(object_2)) +  object_2$logLik <- sum(dnorm(x = object_2$residuals, +      mean = 0, sd = sigma_mle, log = TRUE)) +  object_2$data <- object$data # to make the nobs.mkinfit method work +  object_2$bparms.optim <- coef(object_2) +  object_2$errparms <- 1 # We have estimated one error model parameter +  class(object_2) <- "mkinfit" + +  lmtest::lrtest.default(object_2, object, name = name_function) +} diff --git a/R/logLik.mkinfit.R b/R/logLik.mkinfit.R index cadc0d0a..1c025893 100644 --- a/R/logLik.mkinfit.R +++ b/R/logLik.mkinfit.R @@ -1,15 +1,15 @@  #' Calculated the log-likelihood of a fitted mkinfit object -#'  +#'  #' This function returns the product of the likelihood densities of each  #' observed value, as calculated as part of the fitting procedure using  #' \code{\link{dnorm}}, i.e. assuming normal distribution, and with the means  #' predicted by the degradation model, and the standard deviations predicted by  #' the error model. -#'  +#'  #' The total number of estimated parameters returned with the value of the  #' likelihood is calculated as the sum of fitted degradation model parameters  #' and the fitted error model parameters. -#'  +#'  #' @param object An object of class \code{\link{mkinfit}}.  #' @param \dots For compatibility with the generic method  #' @return An object of class \code{\link{logLik}} with the number of estimated @@ -19,7 +19,7 @@  #' @seealso Compare the AIC of columns of \code{\link{mmkin}} objects using  #'   \code{\link{AIC.mmkin}}.  #' @examples -#'  +#'  #'   \dontrun{  #'   sfo_sfo <- mkinmod(  #'     parent = mkinsub("SFO", to = "m1"), @@ -31,11 +31,12 @@  #'   f_tc <- mkinfit(sfo_sfo, d_t, error_model = "tc", quiet = TRUE)  #'   AIC(f_nw, f_obs, f_tc)  #'   } -#'  +#'  #' @export  logLik.mkinfit <- function(object, ...) {    val <- object$logLik    # Number of estimated parameters    attr(val, "df") <- length(object$bparms.optim) + length(object$errparms) +  class(val) <- "logLik"    return(val)  } diff --git a/R/lrtest.mkinfit.R b/R/lrtest.mkinfit.R index a5689830..c3f4d38e 100644 --- a/R/lrtest.mkinfit.R +++ b/R/lrtest.mkinfit.R @@ -19,7 +19,8 @@ lmtest::lrtest  #' lower number of fitted parameters (null hypothesis).  #'  #' @importFrom stats logLik update -#' @param object An \code{\link{mkinfit}} object +#' @param object An \code{\link{mkinfit}} object, or an \code{\link{mmkin}} column +#'  object containing two fits to the same data.  #' @param object_2 Optionally, another mkinfit object fitted to the same data.  #' @param \dots Argument to \code{\link{mkinfit}}, passed to  #'   \code{\link{update.mkinfit}} for creating the alternative fitted object. @@ -36,7 +37,7 @@ lmtest::lrtest  #' #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)))  #' } @@ -68,3 +69,10 @@ lrtest.mkinfit <- function(object, object_2 = NULL, ...) {      lmtest::lrtest.default(object_2, object, name = name_function)    }  } + +#' @rdname lrtest.mkinfit +#' @export +lrtest.mmkin <- function(object, ...) { +  if (nrow(object) != 2 | ncol(object) > 1) stop("Only works for a column containing two mkinfit objects") +  lrtest(object[[1, 1]], object[[2, 1]]) +} @@ -1,10 +1,10 @@  #' Fit one or more kinetic models with one or more state variables to one or  #' more datasets -#'  +#'  #' This function calls \code{\link{mkinfit}} on all combinations of models and  #' datasets specified in its first two arguments. -#'  -#' @param models Either a character vector of shorthand names like  +#' +#' @param 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.  #' @param datasets An optionally named list of datasets suitable as observed @@ -24,28 +24,28 @@  #'   plotting.  #' @keywords optimize  #' @examples -#'  +#'  #' \dontrun{  #' m_synth_SFO_lin <- mkinmod(parent = mkinsub("SFO", "M1"),  #'                            M1 = mkinsub("SFO", "M2"),  #'                            M2 = mkinsub("SFO"), use_of_ff = "max") -#'  +#'  #' m_synth_FOMC_lin <- mkinmod(parent = mkinsub("FOMC", "M1"),  #'                             M1 = mkinsub("SFO", "M2"),  #'                             M2 = mkinsub("SFO"), use_of_ff = "max") -#'  +#'  #' models <- list(SFO_lin = m_synth_SFO_lin, FOMC_lin = m_synth_FOMC_lin)  #' datasets <- lapply(synthetic_data_for_UBA_2014[1:3], function(x) x$data)  #' names(datasets) <- paste("Dataset", 1:3) -#'  +#'  #' time_default <- system.time(fits.0 <- mmkin(models, datasets, quiet = TRUE))  #' time_1 <- system.time(fits.4 <- mmkin(models, datasets, cores = 1, quiet = TRUE)) -#'  +#'  #' time_default  #' time_1 -#'  +#'  #' endpoints(fits.0[["SFO_lin", 2]]) -#'  +#'  #' # plot.mkinfit handles rows or columns of mmkin result objects  #' plot(fits.0[1, ])  #' plot(fits.0[1, ], obs_var = c("M1", "M2")) @@ -58,7 +58,7 @@  #' # allow to plot the observed variables separately  #' plot(fits.0[1, 1])  #' } -#'  +#'  #' @export mmkin  mmkin <- function(models = c("SFO", "FOMC", "DFOP"), datasets,                    cores = round(detectCores()/2), cluster = NULL, ...) diff --git a/R/plot.mmkin.R b/R/plot.mmkin.R index eefafe12..182e74ca 100644 --- a/R/plot.mmkin.R +++ b/R/plot.mmkin.R @@ -1,13 +1,13 @@  #' Plot model fits (observed and fitted) and the residuals for a row or column  #' of an mmkin object -#'  +#'  #' When x is a row selected from an mmkin object (\code{\link{[.mmkin}}), the  #' same model fitted for at least one dataset is shown. When it is a column,  #' the fit of at least one model to the same dataset is shown. -#'  +#'  #' If the current plot device is a \code{\link[tikzDevice]{tikz}} device, then  #' latex is being used for the formatting of the chi2 error level. -#'  +#'  #' @param x An object of class \code{\link{mmkin}}, with either one row or one  #'   column.  #' @param main The main title placed on the outer margin of the plot. @@ -24,12 +24,13 @@  #' @param cex Passed to the plot functions and \code{\link{mtext}}.  #' @param rel.height.middle The relative height of the middle plot, if more  #'   than two rows of plots are shown. +#' @param ymax Maximum y axis value for \code{\link{plot.mkinfit}}.  #' @param \dots Further arguments passed to \code{\link{plot.mkinfit}} and  #'   \code{\link{mkinresplot}}.  #' @return The function is called for its side effect.  #' @author Johannes Ranke  #' @examples -#'  +#'  #'   \dontrun{  #'   # Only use one core not to offend CRAN checks  #'   fits <- mmkin(c("FOMC", "HS"), @@ -37,22 +38,23 @@  #'                 cores = 1, quiet = TRUE, error_model = "tc")  #'   plot(fits[, "FOCUS C"])  #'   plot(fits["FOMC", ]) -#'  +#'  #'   # We can also plot a single fit, if we like the way plot.mmkin works, but then the plot  #'   # height should be smaller than the plot width (this is not possible for the html pages  #'   # generated by pkgdown, as far as I know).  #'   plot(fits["FOMC", "FOCUS C"]) # same as plot(fits[1, 2]) -#'  +#'  #'   # Show the error models  #'   plot(fits["FOMC", ], resplot = "errmod")  #'   } -#'  +#'  #' @export -plot.mmkin <- function(x, main = "auto", legends = 1,  +plot.mmkin <- function(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, ...) { +                       cex = 0.7, rel.height.middle = 0.9, +                       ymax = "auto", ...) {    n.m <- nrow(x)    n.d <- ncol(x) @@ -107,7 +109,11 @@ plot.mmkin <- function(x, main = "auto", legends = 1,      }      fit <- x[[i.fit]] -    plot(fit, legend = legends == i.fit, ...) +    if (ymax == "auto") { +      plot(fit, legend = legends == i.fit, ...) +    } else { +      plot(fit, legend = legends == i.fit, ylim = c(0, ymax), ...) +    }      title(main, outer = TRUE, line = -2) diff --git a/R/sigma_twocomp.R b/R/sigma_twocomp.R index c9a15aa8..1e012d15 100644 --- a/R/sigma_twocomp.R +++ b/R/sigma_twocomp.R @@ -1,4 +1,4 @@ -#' Two component error model +#' Two-component error model  #'   #' Function describing the standard deviation of the measurement error in  #' dependence of the measured value \eqn{y}: diff --git a/README.html b/README.html index f4b33afe..d7ebe451 100644 --- a/README.html +++ b/README.html @@ -367,7 +367,7 @@ summary {  <div id="mkin" class="section level1">  <h1>mkin</h1> -<p><a href="https://cran.r-project.org/package=mkin"><img src="data:image/svg+xml; charset=utf-8;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMjAiPgogIDxsaW5lYXJHcmFkaWVudCBpZD0iYiIgeDI9IjAiIHkyPSIxMDAlIj4KICAgIDxzdG9wIG9mZnNldD0iMCIgc3RvcC1jb2xvcj0iI2JiYiIgc3RvcC1vcGFjaXR5PSIuMSIvPgogICAgPHN0b3Agb2Zmc2V0PSIxIiBzdG9wLW9wYWNpdHk9Ii4xIi8+CiAgPC9saW5lYXJHcmFkaWVudD4KICA8bWFzayBpZD0iYSI+CiAgICA8cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjIwIiByeD0iMyIgZmlsbD0iI2ZmZiIvPgogIDwvbWFzaz4KICA8ZyBtYXNrPSJ1cmwoI2EpIj4KICAgIDxwYXRoIGZpbGw9IiM1NTUiIGQ9Ik0wIDBoNDN2MjBIMHoiLz4KICAgIDxwYXRoIGZpbGw9IiM0YzEiIGQ9Ik00MyAwaDc5LjV2MjBINDN6Ii8+CiAgICA8cGF0aCBmaWxsPSJ1cmwoI2IpIiBkPSJNMCAwaDEwMHYyMEgweiIvPgogIDwvZz4KICA8ZyBmaWxsPSIjZmZmIiB0ZXh0LWFuY2hvcj0ibWlkZGxlIgogICAgIGZvbnQtZmFtaWx5PSJEZWphVnUgU2FucyxWZXJkYW5hLEdlbmV2YSxzYW5zLXNlcmlmIiBmb250LXNpemU9IjExIj4KICAgIDx0ZXh0IHg9IjIxLjUiIHk9IjE1IiBmaWxsPSIjMDEwMTAxIiBmaWxsLW9wYWNpdHk9Ii4zIj4KICAgICAgQ1JBTgogICAgPC90ZXh0PgogICAgPHRleHQgeD0iMjEuNSIgeT0iMTQiPgogICAgICBDUkFOCiAgICA8L3RleHQ+CiAgICA8dGV4dCB4PSI3MC41IiB5PSIxNSIgZmlsbD0iIzAxMDEwMSIgZmlsbC1vcGFjaXR5PSIuMyI+CiAgICAgIDAuOS40OS42CiAgICA8L3RleHQ+CiAgICA8dGV4dCB4PSI3MC41IiB5PSIxNCI+CiAgICAgIDAuOS40OS42CiAgICA8L3RleHQ+CiAgPC9nPgo8L3N2Zz4=" /></a> <a href="https://travis-ci.com/jranke/mkin"><img src="data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSI4MSIgaGVpZ2h0PSIyMCI+PGxpbmVhckdyYWRpZW50IGlkPSJhIiB4Mj0iMCIgeTI9IjEwMCUiPjxzdG9wIG9mZnNldD0iMCIgc3RvcC1jb2xvcj0iI2JiYiIgc3RvcC1vcGFjaXR5PSIuMSIvPjxzdG9wIG9mZnNldD0iMSIgc3RvcC1vcGFjaXR5PSIuMSIvPjwvbGluZWFyR3JhZGllbnQ+PHJlY3Qgcng9IjMiIHdpZHRoPSI4MSIgaGVpZ2h0PSIyMCIgZmlsbD0iIzU1NSIvPjxyZWN0IHJ4PSIzIiB4PSIzNyIgd2lkdGg9IjQ0IiBoZWlnaHQ9IjIwIiBmaWxsPSIjZTA1ZDQ0Ii8+PHBhdGggZmlsbD0iI2UwNWQ0NCIgZD0iTTM3IDBoNHYyMGgtNHoiLz48cmVjdCByeD0iMyIgd2lkdGg9IjgxIiBoZWlnaHQ9IjIwIiBmaWxsPSJ1cmwoI2EpIi8+PGcgZmlsbD0iI2ZmZiIgdGV4dC1hbmNob3I9Im1pZGRsZSIgZm9udC1mYW1pbHk9IkRlamFWdSBTYW5zLFZlcmRhbmEsR2VuZXZhLHNhbnMtc2VyaWYiIGZvbnQtc2l6ZT0iMTEiPjx0ZXh0IHg9IjE5LjUiIHk9IjE1IiBmaWxsPSIjMDEwMTAxIiBmaWxsLW9wYWNpdHk9Ii4zIj5idWlsZDwvdGV4dD48dGV4dCB4PSIxOS41IiB5PSIxNCI+YnVpbGQ8L3RleHQ+PHRleHQgeD0iNTgiIHk9IjE1IiBmaWxsPSIjMDEwMTAxIiBmaWxsLW9wYWNpdHk9Ii4zIj5mYWlsaW5nPC90ZXh0Pjx0ZXh0IHg9IjU4IiB5PSIxNCI+ZmFpbGluZzwvdGV4dD48L2c+PC9zdmc+" alt="Build Status" /></a> <a href="https://codecov.io/github/jranke/mkin"><img src="data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMTIiIGhlaWdodD0iMjAiPgogICAgPGxpbmVhckdyYWRpZW50IGlkPSJiIiB4Mj0iMCIgeTI9IjEwMCUiPgogICAgICAgIDxzdG9wIG9mZnNldD0iMCIgc3RvcC1jb2xvcj0iI2JiYiIgc3RvcC1vcGFjaXR5PSIuMSIgLz4KICAgICAgICA8c3RvcCBvZmZzZXQ9IjEiIHN0b3Atb3BhY2l0eT0iLjEiIC8+CiAgICA8L2xpbmVhckdyYWRpZW50PgogICAgPG1hc2sgaWQ9ImEiPgogICAgICAgIDxyZWN0IHdpZHRoPSIxMTIiIGhlaWdodD0iMjAiIHJ4PSIzIiBmaWxsPSIjZmZmIiAvPgogICAgPC9tYXNrPgogICAgPGcgbWFzaz0idXJsKCNhKSI+CiAgICAgICAgPHBhdGggZmlsbD0iIzU1NSIgZD0iTTAgMGg3NnYyMEgweiIgLz4KICAgICAgICA8cGF0aCBmaWxsPSIjYTFiOTBlIiBkPSJNNzYgMGgzNnYyMEg3NnoiIC8+CiAgICAgICAgPHBhdGggZmlsbD0idXJsKCNiKSIgZD0iTTAgMGgxMTJ2MjBIMHoiIC8+CiAgICA8L2c+CiAgICA8ZyBmaWxsPSIjZmZmIiB0ZXh0LWFuY2hvcj0ibWlkZGxlIiBmb250LWZhbWlseT0iRGVqYVZ1IFNhbnMsVmVyZGFuYSxHZW5ldmEsc2Fucy1zZXJpZiIgZm9udC1zaXplPSIxMSI+CiAgICAgICAgPHRleHQgeD0iNDYiIHk9IjE1IiBmaWxsPSIjMDEwMTAxIiBmaWxsLW9wYWNpdHk9Ii4zIj5jb2RlY292PC90ZXh0PgogICAgICAgIDx0ZXh0IHg9IjQ2IiB5PSIxNCI+Y29kZWNvdjwvdGV4dD4KICAgICAgICA8dGV4dCB4PSI5MyIgeT0iMTUiIGZpbGw9IiMwMTAxMDEiIGZpbGwtb3BhY2l0eT0iLjMiPjkxJTwvdGV4dD4KICAgICAgICA8dGV4dCB4PSI5MyIgeT0iMTQiPjkxJTwvdGV4dD4KICAgIDwvZz4KICAgIDxzdmcgdmlld0JveD0iMTIwIC04IDYwIDYwIj4KICAgICAgICA8cGF0aCBkPSJNMjMuMDEzIDBDMTAuMzMzLjAwOS4wMSAxMC4yMiAwIDIyLjc2MnYuMDU4bDMuOTE0IDIuMjc1LjA1My0uMDM2YTExLjI5MSAxMS4yOTEgMCAwIDEgOC4zNTItMS43NjcgMTAuOTExIDEwLjkxMSAwIDAgMSA1LjUgMi43MjZsLjY3My42MjQuMzgtLjgyOGMuMzY4LS44MDIuNzkzLTEuNTU2IDEuMjY0LTIuMjQuMTktLjI3Ni4zOTgtLjU1NC42MzctLjg1MWwuMzkzLS40OS0uNDg0LS40MDRhMTYuMDggMTYuMDggMCAwIDAtNy40NTMtMy40NjYgMTYuNDgyIDE2LjQ4MiAwIDAgMC03LjcwNS40NDlDNy4zODYgMTAuNjgzIDE0LjU2IDUuMDE2IDIzLjAzIDUuMDFjNC43NzkgMCA5LjI3MiAxLjg0IDEyLjY1MSA1LjE4IDIuNDEgMi4zODIgNC4wNjkgNS4zNSA0LjgwNyA4LjU5MWExNi41MyAxNi41MyAwIDAgMC00Ljc5Mi0uNzIzbC0uMjkyLS4wMDJhMTYuNzA3IDE2LjcwNyAwIDAgMC0xLjkwMi4xNGwtLjA4LjAxMmMtLjI4LjAzNy0uNTI0LjA3NC0uNzQ4LjExNS0uMTEuMDE5LS4yMTguMDQxLS4zMjcuMDYzLS4yNTcuMDUyLS41MS4xMDgtLjc1LjE2OWwtLjI2NS4wNjdhMTYuMzkgMTYuMzkgMCAwIDAtLjkyNi4yNzZsLS4wNTYuMDE4Yy0uNjgyLjIzLTEuMzYuNTExLTIuMDE2LjgzOGwtLjA1Mi4wMjZjLS4yOS4xNDUtLjU4NC4zMDUtLjg5OS40OWwtLjA2OS4wNGExNS41OTYgMTUuNTk2IDAgMCAwLTQuMDYxIDMuNDY2bC0uMTQ1LjE3NWMtLjI5LjM2LS41MjEuNjY2LS43MjMuOTYtLjE3LjI0Ny0uMzQuNTEzLS41NTIuODY0bC0uMTE2LjE5OWMtLjE3LjI5Mi0uMzIuNTctLjQ0OS44MjRsLS4wMy4wNTdhMTYuMTE2IDE2LjExNiAwIDAgMC0uODQzIDIuMDI5bC0uMDM0LjEwMmExNS42NSAxNS42NSAwIDAgMC0uNzg2IDUuMTc0bC4wMDMuMjE0YTIxLjUyMyAyMS41MjMgMCAwIDAgLjA0Ljc1NGMuMDA5LjExOS4wMi4yMzcuMDMyLjM1NS4wMTQuMTQ1LjAzMi4yOS4wNDkuNDMybC4wMS4wOGMuMDEuMDY3LjAxNy4xMzMuMDI2LjE5Ny4wMzQuMjQyLjA3NC40OC4xMTkuNzIuNDYzIDIuNDE5IDEuNjIgNC44MzYgMy4zNDUgNi45OWwuMDc4LjA5OC4wOC0uMDk1Yy42ODgtLjgxIDIuMzk1LTMuMzggMi41MzktNC45MjJsLjAwMy0uMDI5LS4wMTQtLjAyNWExMC43MjcgMTAuNzI3IDAgMCAxLTEuMjI2LTQuOTU2YzAtNS43NiA0LjU0NS0xMC41NDQgMTAuMzQzLTEwLjg5bC4zODEtLjAxNGExMS40MDMgMTEuNDAzIDAgMCAxIDYuNjUxIDEuOTU3bC4wNTQuMDM2IDMuODYyLTIuMjM3LjA1LS4wM3YtLjA1NmMuMDA2LTYuMDgtMi4zODQtMTEuNzkzLTYuNzI5LTE2LjA4OUMzNC45MzIgMi4zNjEgMjkuMTYgMCAyMy4wMTMgMCIgZmlsbD0iI0YwMUY3QSIgZmlsbC1ydWxlPSJldmVub2RkIi8+CiAgICA8L3N2Zz4KPC9zdmc+" alt="codecov" /></a></p> +<p><a href="https://cran.r-project.org/package=mkin"><img src="data:image/svg+xml; charset=utf-8;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMjAiPgogIDxsaW5lYXJHcmFkaWVudCBpZD0iYiIgeDI9IjAiIHkyPSIxMDAlIj4KICAgIDxzdG9wIG9mZnNldD0iMCIgc3RvcC1jb2xvcj0iI2JiYiIgc3RvcC1vcGFjaXR5PSIuMSIvPgogICAgPHN0b3Agb2Zmc2V0PSIxIiBzdG9wLW9wYWNpdHk9Ii4xIi8+CiAgPC9saW5lYXJHcmFkaWVudD4KICA8bWFzayBpZD0iYSI+CiAgICA8cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjIwIiByeD0iMyIgZmlsbD0iI2ZmZiIvPgogIDwvbWFzaz4KICA8ZyBtYXNrPSJ1cmwoI2EpIj4KICAgIDxwYXRoIGZpbGw9IiM1NTUiIGQ9Ik0wIDBoNDN2MjBIMHoiLz4KICAgIDxwYXRoIGZpbGw9IiM0YzEiIGQ9Ik00MyAwaDc5LjV2MjBINDN6Ii8+CiAgICA8cGF0aCBmaWxsPSJ1cmwoI2IpIiBkPSJNMCAwaDEwMHYyMEgweiIvPgogIDwvZz4KICA8ZyBmaWxsPSIjZmZmIiB0ZXh0LWFuY2hvcj0ibWlkZGxlIgogICAgIGZvbnQtZmFtaWx5PSJEZWphVnUgU2FucyxWZXJkYW5hLEdlbmV2YSxzYW5zLXNlcmlmIiBmb250LXNpemU9IjExIj4KICAgIDx0ZXh0IHg9IjIxLjUiIHk9IjE1IiBmaWxsPSIjMDEwMTAxIiBmaWxsLW9wYWNpdHk9Ii4zIj4KICAgICAgQ1JBTgogICAgPC90ZXh0PgogICAgPHRleHQgeD0iMjEuNSIgeT0iMTQiPgogICAgICBDUkFOCiAgICA8L3RleHQ+CiAgICA8dGV4dCB4PSI3MC41IiB5PSIxNSIgZmlsbD0iIzAxMDEwMSIgZmlsbC1vcGFjaXR5PSIuMyI+CiAgICAgIDAuOS40OS43CiAgICA8L3RleHQ+CiAgICA8dGV4dCB4PSI3MC41IiB5PSIxNCI+CiAgICAgIDAuOS40OS43CiAgICA8L3RleHQ+CiAgPC9nPgo8L3N2Zz4=" /></a> <a href="https://travis-ci.com/jranke/mkin"><img src="data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSI5MCIgaGVpZ2h0PSIyMCI+PGxpbmVhckdyYWRpZW50IGlkPSJhIiB4Mj0iMCIgeTI9IjEwMCUiPjxzdG9wIG9mZnNldD0iMCIgc3RvcC1jb2xvcj0iI2JiYiIgc3RvcC1vcGFjaXR5PSIuMSIvPjxzdG9wIG9mZnNldD0iMSIgc3RvcC1vcGFjaXR5PSIuMSIvPjwvbGluZWFyR3JhZGllbnQ+PHJlY3Qgcng9IjMiIHdpZHRoPSI5MCIgaGVpZ2h0PSIyMCIgZmlsbD0iIzU1NSIvPjxyZWN0IHJ4PSIzIiB4PSIzNyIgd2lkdGg9IjUzIiBoZWlnaHQ9IjIwIiBmaWxsPSIjNGMxIi8+PHBhdGggZmlsbD0iIzRjMSIgZD0iTTM3IDBoNHYyMGgtNHoiLz48cmVjdCByeD0iMyIgd2lkdGg9IjkwIiBoZWlnaHQ9IjIwIiBmaWxsPSJ1cmwoI2EpIi8+PGcgZmlsbD0iI2ZmZiIgdGV4dC1hbmNob3I9Im1pZGRsZSIgZm9udC1mYW1pbHk9IkRlamFWdSBTYW5zLFZlcmRhbmEsR2VuZXZhLHNhbnMtc2VyaWYiIGZvbnQtc2l6ZT0iMTEiPjx0ZXh0IHg9IjE5LjUiIHk9IjE1IiBmaWxsPSIjMDEwMTAxIiBmaWxsLW9wYWNpdHk9Ii4zIj5idWlsZDwvdGV4dD48dGV4dCB4PSIxOS41IiB5PSIxNCI+YnVpbGQ8L3RleHQ+PHRleHQgeD0iNjIuNSIgeT0iMTUiIGZpbGw9IiMwMTAxMDEiIGZpbGwtb3BhY2l0eT0iLjMiPnBhc3Npbmc8L3RleHQ+PHRleHQgeD0iNjIuNSIgeT0iMTQiPnBhc3Npbmc8L3RleHQ+PC9nPjwvc3ZnPg==" alt="Build Status" /></a> <a href="https://codecov.io/github/jranke/mkin"><img src="data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMTIiIGhlaWdodD0iMjAiPgogICAgPGxpbmVhckdyYWRpZW50IGlkPSJiIiB4Mj0iMCIgeTI9IjEwMCUiPgogICAgICAgIDxzdG9wIG9mZnNldD0iMCIgc3RvcC1jb2xvcj0iI2JiYiIgc3RvcC1vcGFjaXR5PSIuMSIgLz4KICAgICAgICA8c3RvcCBvZmZzZXQ9IjEiIHN0b3Atb3BhY2l0eT0iLjEiIC8+CiAgICA8L2xpbmVhckdyYWRpZW50PgogICAgPG1hc2sgaWQ9ImEiPgogICAgICAgIDxyZWN0IHdpZHRoPSIxMTIiIGhlaWdodD0iMjAiIHJ4PSIzIiBmaWxsPSIjZmZmIiAvPgogICAgPC9tYXNrPgogICAgPGcgbWFzaz0idXJsKCNhKSI+CiAgICAgICAgPHBhdGggZmlsbD0iIzU1NSIgZD0iTTAgMGg3NnYyMEgweiIgLz4KICAgICAgICA8cGF0aCBmaWxsPSIjYTFiOTBlIiBkPSJNNzYgMGgzNnYyMEg3NnoiIC8+CiAgICAgICAgPHBhdGggZmlsbD0idXJsKCNiKSIgZD0iTTAgMGgxMTJ2MjBIMHoiIC8+CiAgICA8L2c+CiAgICA8ZyBmaWxsPSIjZmZmIiB0ZXh0LWFuY2hvcj0ibWlkZGxlIiBmb250LWZhbWlseT0iRGVqYVZ1IFNhbnMsVmVyZGFuYSxHZW5ldmEsc2Fucy1zZXJpZiIgZm9udC1zaXplPSIxMSI+CiAgICAgICAgPHRleHQgeD0iNDYiIHk9IjE1IiBmaWxsPSIjMDEwMTAxIiBmaWxsLW9wYWNpdHk9Ii4zIj5jb2RlY292PC90ZXh0PgogICAgICAgIDx0ZXh0IHg9IjQ2IiB5PSIxNCI+Y29kZWNvdjwvdGV4dD4KICAgICAgICA8dGV4dCB4PSI5MyIgeT0iMTUiIGZpbGw9IiMwMTAxMDEiIGZpbGwtb3BhY2l0eT0iLjMiPjkxJTwvdGV4dD4KICAgICAgICA8dGV4dCB4PSI5MyIgeT0iMTQiPjkxJTwvdGV4dD4KICAgIDwvZz4KICAgIDxzdmcgdmlld0JveD0iMTIwIC04IDYwIDYwIj4KICAgICAgICA8cGF0aCBkPSJNMjMuMDEzIDBDMTAuMzMzLjAwOS4wMSAxMC4yMiAwIDIyLjc2MnYuMDU4bDMuOTE0IDIuMjc1LjA1My0uMDM2YTExLjI5MSAxMS4yOTEgMCAwIDEgOC4zNTItMS43NjcgMTAuOTExIDEwLjkxMSAwIDAgMSA1LjUgMi43MjZsLjY3My42MjQuMzgtLjgyOGMuMzY4LS44MDIuNzkzLTEuNTU2IDEuMjY0LTIuMjQuMTktLjI3Ni4zOTgtLjU1NC42MzctLjg1MWwuMzkzLS40OS0uNDg0LS40MDRhMTYuMDggMTYuMDggMCAwIDAtNy40NTMtMy40NjYgMTYuNDgyIDE2LjQ4MiAwIDAgMC03LjcwNS40NDlDNy4zODYgMTAuNjgzIDE0LjU2IDUuMDE2IDIzLjAzIDUuMDFjNC43NzkgMCA5LjI3MiAxLjg0IDEyLjY1MSA1LjE4IDIuNDEgMi4zODIgNC4wNjkgNS4zNSA0LjgwNyA4LjU5MWExNi41MyAxNi41MyAwIDAgMC00Ljc5Mi0uNzIzbC0uMjkyLS4wMDJhMTYuNzA3IDE2LjcwNyAwIDAgMC0xLjkwMi4xNGwtLjA4LjAxMmMtLjI4LjAzNy0uNTI0LjA3NC0uNzQ4LjExNS0uMTEuMDE5LS4yMTguMDQxLS4zMjcuMDYzLS4yNTcuMDUyLS41MS4xMDgtLjc1LjE2OWwtLjI2NS4wNjdhMTYuMzkgMTYuMzkgMCAwIDAtLjkyNi4yNzZsLS4wNTYuMDE4Yy0uNjgyLjIzLTEuMzYuNTExLTIuMDE2LjgzOGwtLjA1Mi4wMjZjLS4yOS4xNDUtLjU4NC4zMDUtLjg5OS40OWwtLjA2OS4wNGExNS41OTYgMTUuNTk2IDAgMCAwLTQuMDYxIDMuNDY2bC0uMTQ1LjE3NWMtLjI5LjM2LS41MjEuNjY2LS43MjMuOTYtLjE3LjI0Ny0uMzQuNTEzLS41NTIuODY0bC0uMTE2LjE5OWMtLjE3LjI5Mi0uMzIuNTctLjQ0OS44MjRsLS4wMy4wNTdhMTYuMTE2IDE2LjExNiAwIDAgMC0uODQzIDIuMDI5bC0uMDM0LjEwMmExNS42NSAxNS42NSAwIDAgMC0uNzg2IDUuMTc0bC4wMDMuMjE0YTIxLjUyMyAyMS41MjMgMCAwIDAgLjA0Ljc1NGMuMDA5LjExOS4wMi4yMzcuMDMyLjM1NS4wMTQuMTQ1LjAzMi4yOS4wNDkuNDMybC4wMS4wOGMuMDEuMDY3LjAxNy4xMzMuMDI2LjE5Ny4wMzQuMjQyLjA3NC40OC4xMTkuNzIuNDYzIDIuNDE5IDEuNjIgNC44MzYgMy4zNDUgNi45OWwuMDc4LjA5OC4wOC0uMDk1Yy42ODgtLjgxIDIuMzk1LTMuMzggMi41MzktNC45MjJsLjAwMy0uMDI5LS4wMTQtLjAyNWExMC43MjcgMTAuNzI3IDAgMCAxLTEuMjI2LTQuOTU2YzAtNS43NiA0LjU0NS0xMC41NDQgMTAuMzQzLTEwLjg5bC4zODEtLjAxNGExMS40MDMgMTEuNDAzIDAgMCAxIDYuNjUxIDEuOTU3bC4wNTQuMDM2IDMuODYyLTIuMjM3LjA1LS4wM3YtLjA1NmMuMDA2LTYuMDgtMi4zODQtMTEuNzkzLTYuNzI5LTE2LjA4OUMzNC45MzIgMi4zNjEgMjkuMTYgMCAyMy4wMTMgMCIgZmlsbD0iI0YwMUY3QSIgZmlsbC1ydWxlPSJldmVub2RkIi8+CiAgICA8L3N2Zz4KPC9zdmc+" alt="codecov" /></a></p>  <p>The R package <strong>mkin</strong> provides calculation routines for the analysis of chemical degradation data, including <b>m</b>ulticompartment <b>kin</b>etics as needed for modelling the formation and decline of transformation products, or if several compartments are involved.</p>  <div id="installation" class="section level2">  <h2>Installation</h2> @@ -393,14 +393,14 @@ summary {  <li>As of version 0.9-39, fitting of several models to several datasets, optionally in parallel, is supported, see for example <a href="https://pkgdown.jrwb.de/mkin/reference/plot.mmkin.html"><code>plot.mmkin</code></a>.</li>  <li>Model solution (forward modelling) in the function <a href="https://pkgdown.jrwb.de/mkin/reference/mkinpredict.html"><code>mkinpredict</code></a> is performed either using the analytical solution for the case of parent only degradation, an eigenvalue based solution if only simple first-order (SFO) or SFORB kinetics are used in the model, or using a numeric solver from the <code>deSolve</code> package (default is <code>lsoda</code>).</li>  <li>If a C compiler is installed, the kinetic models are compiled from automatically generated C code, see <a href="https://pkgdown.jrwb.de/mkin/articles/web_only/compiled_models.html">vignette <code>compiled_models</code></a>. The autogeneration of C code was inspired by the <a href="https://github.com/karlines/ccSolve"><code>ccSolve</code></a> package. Thanks to Karline Soetaert for her work on that.</li> -<li>By default, kinetic rate constants and kinetic formation fractions are transformed internally using <a href="https://pkgdown.jrwb.de/mkin/reference/transform_odeparms.html"><code>transform_odeparms</code></a> so their estimators can more reasonably be expected to follow a normal distribution. This has the side effect that no constraints are needed in the optimisation. Thanks to René Lehmann for the nice cooperation on this, especially the isometric logration transformation that is now used for the formation fractions.</li> +<li>By default, kinetic rate constants and kinetic formation fractions are transformed internally using <a href="https://pkgdown.jrwb.de/mkin/reference/transform_odeparms.html"><code>transform_odeparms</code></a> so their estimators can more reasonably be expected to follow a normal distribution. This has the side effect that no constraints are needed in the optimisation. Thanks to René Lehmann for the nice cooperation on this, especially the isometric log-ratio transformation that is now used for the formation fractions.</li>  <li>A side effect of this is that when parameter estimates are backtransformed to match the model definition, confidence intervals calculated from standard errors are also backtransformed to the correct scale, and will not include meaningless values like negative rate constants or formation fractions adding up to more than 1, which can not occur in a single experiment with a single defined radiolabel position.</li>  <li>The usual one-sided t-test for significant difference from zero is nevertheless shown based on estimators for the untransformed parameters.</li>  <li>Summary and plotting functions. The <code>summary</code> of an <code>mkinfit</code> object is in fact a full report that should give enough information to be able to approximately reproduce the fit with other tools.</li>  <li>The chi-squared error level as defined in the FOCUS kinetics guidance (see below) is calculated for each observed variable.</li>  <li>When a metabolite decline phase is not described well by SFO kinetics, SFORB kinetics can be used for the metabolite.</li>  <li>Three different error models can be selected using the argument <code>error_model</code> to the <a href="https://pkgdown.jrwb.de/mkin/reference/mkinfit.html"><code>mkinfit</code></a> function.</li> -<li>Iteratively reweighted least squares fitting is now obsolete, and the variance by variable error model should now be specified as <code>error_model = "obs"</code>.</li> +<li>The ‘variance by variable’ error model which is often fitted using Iteratively Reweighted Least Squares (IRLS) should now be specified as <code>error_model = "obs"</code>.</li>  <li>A two-component error model similar to the one proposed by <a href="https://pkgdown.jrwb.de/mkin/reference/sigma_twocomp.html">Rocke and Lorenzato</a> can be selected using the argument <code>error_model = "tc"</code>.</li>  </ul>  </div> @@ -414,8 +414,8 @@ summary {  </div>  <div id="credits-and-historical-remarks" class="section level2">  <h2>Credits and historical remarks</h2> -<p><code>mkin</code> would not be possible without the underlying software stack consisting of R and the packages <a href="https://cran.r-project.org/package=deSolve">deSolve</a> and <a href="https://cran.r-project.org/package=FME">FME</a>, to say the least.</p> -<p>It could not have been written without me being introduced to regulatory fate modelling of pesticides by Adrian Gurney during my time at Harlan Laboratories Ltd (formerly RCC Ltd). <code>mkin</code> greatly profits from and largely follows the work done by the <a href="http://esdac.jrc.ec.europa.eu/projects/degradation-kinetics">FOCUS Degradation Kinetics Workgroup</a>, as detailed in their guidance document from 2006, slightly updated in 2011 and in 2014.</p> +<p><code>mkin</code> would not be possible without the underlying software stack consisting of, among others, R and the package <a href="https://cran.r-project.org/package=deSolve">deSolve</a>. In previous version, <code>mkin</code> was also using the functionality of the <a href="https://cran.r-project.org/package=FME">FME</a> package. Please refer to the <a href="https://cran.r-project.org/package=mkin">package page on CRAN</a> for the full list of imported and suggested R packages. Also, <a href="https://debian.org">Debian Linux</a>, the vim editor and the <a href="https://github.com/jalvesaq/Nvim-R">Nvim-R</a> plugin have been invaluable in its development.</p> +<p><code>mkin</code> could not have been written without me being introduced to regulatory fate modelling of pesticides by Adrian Gurney during my time at Harlan Laboratories Ltd (formerly RCC Ltd). <code>mkin</code> greatly profits from and largely follows the work done by the <a href="http://esdac.jrc.ec.europa.eu/projects/degradation-kinetics">FOCUS Degradation Kinetics Workgroup</a>, as detailed in their guidance document from 2006, slightly updated in 2011 and in 2014.</p>  <p>Also, it was inspired by the first version of KinGUI developed by BayerCropScience, which is based on the MatLab runtime environment.</p>  <p>The companion package <a href="http://kinfit.r-forge.r-project.org/kinfit_static/index.html">kinfit</a> (now deprecated) was <a href="https://r-forge.r-project.org/scm/viewvc.php?view=rev&root=kinfit&revision=2">started in 2008</a> and <a href="https://cran.r-project.org/src/contrib/Archive/kinfit/">first published</a> on CRAN on 01 May 2010.</p>  <p>The first <code>mkin</code> code was <a href="https://r-forge.r-project.org/scm/viewvc.php?view=rev&root=kinfit&revision=8">published on 11 May 2010</a> and the <a href="https://cran.r-project.org/src/contrib/Archive/mkin">first CRAN version</a> on 18 May 2010.</p> @@ -423,9 +423,24 @@ summary {  <p>Somewhat in parallel, Syngenta has sponsored the development of an <code>mkin</code> and KinGUII based GUI application called CAKE, which also adds IRLS and MCMC, is more limited in the model formulation, but puts more weight on usability. CAKE is available for download from the <a href="https://www.tessella.com/showcase/computer-assisted-kinetic-evaluation">CAKE website</a>, where you can also find a zip archive of the R scripts derived from <code>mkin</code>, published under the GPL license.</p>  <p>Finally, there is <a href="http://github.com/zhenglei-gao/KineticEval">KineticEval</a>, which contains a further development of the scripts used for KinGUII, so the different tools will hopefully be able to learn from each other in the future as well.</p>  </div> +<div id="references" class="section level2"> +<h2>References</h2> +<table> +<tr> +<td> +Ranke J, Meinecke S (2019) Error Models for the Kinetic Evaluation of Chemical Degradation Data <i>Environments</i> <b>6</b> (12) 124 <a href="https://doi.org/10.3390/environments6120124">doi:10.3390/environments6120124</a> +</td> +</tr> +<tr> +<td> +Ranke J, Wöltjen J, Meinecke S (2018) Comparison of software tools for kinetic evaluation of chemical degradation data <i>Environmental Sciences Europe</i> <b>30</b> 17 <a href="https://doi.org/10.1186/s12302-018-0145-1">doi:10.1186/s12302-018-0145-1</a> +</td> +</tr> +</table> +</div>  <div id="development" class="section level2">  <h2>Development</h2> -<p>Contributions are welcome! Your <a href="https://help.github.com/articles/fork-a-repo">mkin fork</a> is just a mouse click away… The master branch on github should always be in good shape, I implement new features in separate branches now. If you prefer subversion, project members for the <a href="http://r-forge.r-project.org/R/?group_id=615">r-forge project</a> are welcome as well. Generally, the source code of the latest CRAN version should be available there. You can also browse the source code at <a href="http://cgit.jrwb.de/mkin">cgit.jrwb.de/mkin</a>.</p> +<p>Contributions are welcome!</p>  </div>  </div> @@ -71,7 +71,7 @@ and at [R-Forge](http://kinfit.r-forge.r-project.org/mkin_static/index.html).    so their estimators can more reasonably be expected to follow    a normal distribution. This has the side effect that no constraints    are needed in the optimisation. Thanks to René Lehmann for the nice -  cooperation on this, especially the isometric logration transformation +  cooperation on this, especially the isometric log-ratio transformation    that is now used for the formation fractions.  * A side effect of this is that when parameter estimates are backtransformed    to match the model definition, confidence intervals calculated from @@ -91,9 +91,9 @@ and at [R-Forge](http://kinfit.r-forge.r-project.org/mkin_static/index.html).  * Three different error models can be selected using the argument `error_model`    to the [`mkinfit`](https://pkgdown.jrwb.de/mkin/reference/mkinfit.html)    function. -* Iteratively reweighted least squares fitting is now obsolete, and the -  variance by variable error model should now be specified as `error_model -  = "obs"`. +* The 'variance by variable' error model which is often fitted using +  Iteratively Reweighted Least Squares (IRLS) should now be specified as +  `error_model = "obs"`.  * A two-component error model similar to the one proposed by    [Rocke and Lorenzato](https://pkgdown.jrwb.de/mkin/reference/sigma_twocomp.html)    can be selected using the argument `error_model = "tc"`. @@ -111,11 +111,16 @@ and one for the [github master branch](https://github.com/jranke/mkin/blob/maste  ## Credits and historical remarks -`mkin` would not be possible without the underlying software stack consisting -of R and the packages [deSolve](https://cran.r-project.org/package=deSolve) -and [FME](https://cran.r-project.org/package=FME), to say the least. +`mkin` would not be possible without the underlying software stack consisting of, +among others, R and the package [deSolve](https://cran.r-project.org/package=deSolve). +In previous version, `mkin` was also using the functionality of the +[FME](https://cran.r-project.org/package=FME) package. Please refer to the +[package page on CRAN](https://cran.r-project.org/package=mkin) for the full list +of imported and suggested R packages. Also, [Debian Linux](https://debian.org), +the vim editor and the [Nvim-R](https://github.com/jalvesaq/Nvim-R) plugin have +been invaluable in its development. -It could not have been written without me being introduced to regulatory fate +`mkin` could not have been written without me being introduced to regulatory fate  modelling of pesticides by Adrian Gurney during my time at Harlan Laboratories  Ltd (formerly RCC Ltd). `mkin` greatly profits from and largely follows  the work done by the @@ -157,14 +162,24 @@ Finally, there is  a further development of the scripts used for KinGUII, so the different tools  will hopefully be able to learn from each other in the future as well. +## References + +<table> +  <tr><td>Ranke J, Meinecke S (2019) +  Error Models for the Kinetic Evaluation of Chemical Degradation Data +  <i>Environments</i> +  <b>6</b> (12) 124 +  <a href='https://doi.org/10.3390/environments6120124'>doi:10.3390/environments6120124</a> +  </td></tr> + +  <tr><td>Ranke J, Wöltjen J, Meinecke S (2018) +  Comparison of software tools for kinetic evaluation of chemical degradation data +  <i>Environmental Sciences Europe</i> +  <b>30</b> 17 +  <a href='https://doi.org/10.1186/s12302-018-0145-1'>doi:10.1186/s12302-018-0145-1</a> +  </td></tr> +</table>  ## Development -Contributions are welcome! Your -[mkin fork](https://help.github.com/articles/fork-a-repo) is just a mouse click -away... The master branch on github should always be in good shape, I implement -new features in separate branches now. If you prefer subversion, project -members for the -[r-forge project](http://r-forge.r-project.org/R/?group_id=615) are welcome as well. -Generally, the source code of the latest CRAN version should be available there. -You can also browse the source code at [cgit.jrwb.de/mkin](http://cgit.jrwb.de/mkin). +Contributions are welcome! diff --git a/_pkgdown.yml b/_pkgdown.yml index c222a817..6bb05b3e 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -22,8 +22,10 @@ reference:        - confint.mkinfit        - update.mkinfit        - lrtest.mkinfit +      - loftest        - mkinerrmin        - endpoints +      - aw        - CAKE_export    - title: Work with mmkin objects      desc: Functions working with aggregated results @@ -6,5 +6,5 @@  * checking for LF line-endings in source and make files and shell scripts  * checking for empty or unneeded directories  * looking to see if a ‘data/datalist’ file should be added -* building ‘mkin_0.9.49.8.tar.gz’ +* building ‘mkin_0.9.49.9.tar.gz’ @@ -1,5 +1,5 @@  * using log directory ‘/home/jranke/git/mkin/mkin.Rcheck’ -* using R version 3.6.1 (2019-07-05) +* using R version 3.6.2 (2019-12-12)  * using platform: x86_64-pc-linux-gnu (64-bit)  * using session charset: UTF-8  * using options ‘--no-tests --as-cran’ @@ -63,6 +63,7 @@ Maintainer: ‘Johannes Ranke <jranke@uni-bremen.de>’  * checking package vignettes in ‘inst/doc’ ... OK  * checking re-building of vignette outputs ... OK  * checking PDF version of manual ... OK +* checking for detritus in the temp directory ... OK  * DONE  Status: OK diff --git a/docs/404.html b/docs/404.html index 2a71e496..3658a137 100644 --- a/docs/404.html +++ b/docs/404.html @@ -67,7 +67,7 @@        </button>        <span class="navbar-brand">          <a class="navbar-link" href="https://pkgdown.jrwb.de/mkin/index.html">mkin</a> -        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.8</span> +        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.9</span>        </span>      </div> diff --git a/docs/articles/index.html b/docs/articles/index.html index ac5f5df1..3e181a2c 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -67,7 +67,7 @@        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.8</span> +        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.9</span>        </span>      </div> diff --git a/docs/authors.html b/docs/authors.html index fb50f268..2bb2557a 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -67,7 +67,7 @@        </button>        <span class="navbar-brand">          <a class="navbar-link" href="index.html">mkin</a> -        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.8</span> +        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.9</span>        </span>      </div> diff --git a/docs/index.html b/docs/index.html index 231ef39f..fe334eb8 100644 --- a/docs/index.html +++ b/docs/index.html @@ -14,11 +14,10 @@  <meta property="og:description" content="Calculation routines based on the FOCUS Kinetics Report (2006,    2014).  Includes a function for conveniently defining differential equation    models, model solution based on eigenvalues if possible or using numerical -  solvers and a choice of the optimisation methods made available by the FME -  package.  If a C compiler (on windows: Rtools) is installed, differential -  equation models are solved using compiled C functions.  Please note that no -  warranty is implied for correctness of results or fitness for a particular -  purpose."> +  solvers.  If a C compiler (on windows: Rtools) is installed, differential +  equation models are solved using automatically generated C functions.  Please +  note that no warranty is implied for correctness of results or fitness for a +  particular purpose.">  <meta name="twitter:card" content="summary">  <!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]>  <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> @@ -38,7 +37,7 @@        </button>        <span class="navbar-brand">          <a class="navbar-link" href="index.html">mkin</a> -        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.8</span> +        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.9</span>        </span>      </div> @@ -127,14 +126,14 @@  <li>As of version 0.9-39, fitting of several models to several datasets, optionally in parallel, is supported, see for example <a href="https://pkgdown.jrwb.de/mkin/reference/plot.mmkin.html"><code>plot.mmkin</code></a>.</li>  <li>Model solution (forward modelling) in the function <a href="https://pkgdown.jrwb.de/mkin/reference/mkinpredict.html"><code>mkinpredict</code></a> is performed either using the analytical solution for the case of parent only degradation, an eigenvalue based solution if only simple first-order (SFO) or SFORB kinetics are used in the model, or using a numeric solver from the <code>deSolve</code> package (default is <code>lsoda</code>).</li>  <li>If a C compiler is installed, the kinetic models are compiled from automatically generated C code, see <a href="https://pkgdown.jrwb.de/mkin/articles/web_only/compiled_models.html">vignette <code>compiled_models</code></a>. The autogeneration of C code was inspired by the <a href="https://github.com/karlines/ccSolve"><code>ccSolve</code></a> package. Thanks to Karline Soetaert for her work on that.</li> -<li>By default, kinetic rate constants and kinetic formation fractions are transformed internally using <a href="https://pkgdown.jrwb.de/mkin/reference/transform_odeparms.html"><code>transform_odeparms</code></a> so their estimators can more reasonably be expected to follow a normal distribution. This has the side effect that no constraints are needed in the optimisation. Thanks to René Lehmann for the nice cooperation on this, especially the isometric logration transformation that is now used for the formation fractions.</li> +<li>By default, kinetic rate constants and kinetic formation fractions are transformed internally using <a href="https://pkgdown.jrwb.de/mkin/reference/transform_odeparms.html"><code>transform_odeparms</code></a> so their estimators can more reasonably be expected to follow a normal distribution. This has the side effect that no constraints are needed in the optimisation. Thanks to René Lehmann for the nice cooperation on this, especially the isometric log-ratio transformation that is now used for the formation fractions.</li>  <li>A side effect of this is that when parameter estimates are backtransformed to match the model definition, confidence intervals calculated from standard errors are also backtransformed to the correct scale, and will not include meaningless values like negative rate constants or formation fractions adding up to more than 1, which can not occur in a single experiment with a single defined radiolabel position.</li>  <li>The usual one-sided t-test for significant difference from zero is nevertheless shown based on estimators for the untransformed parameters.</li>  <li>Summary and plotting functions. The <code>summary</code> of an <code>mkinfit</code> object is in fact a full report that should give enough information to be able to approximately reproduce the fit with other tools.</li>  <li>The chi-squared error level as defined in the FOCUS kinetics guidance (see below) is calculated for each observed variable.</li>  <li>When a metabolite decline phase is not described well by SFO kinetics, SFORB kinetics can be used for the metabolite.</li>  <li>Three different error models can be selected using the argument <code>error_model</code> to the <a href="https://pkgdown.jrwb.de/mkin/reference/mkinfit.html"><code>mkinfit</code></a> function.</li> -<li>Iteratively reweighted least squares fitting is now obsolete, and the variance by variable error model should now be specified as <code>error_model = "obs"</code>.</li> +<li>The ‘variance by variable’ error model which is often fitted using Iteratively Reweighted Least Squares (IRLS) should now be specified as <code>error_model = "obs"</code>.</li>  <li>A two-component error model similar to the one proposed by <a href="https://pkgdown.jrwb.de/mkin/reference/sigma_twocomp.html">Rocke and Lorenzato</a> can be selected using the argument <code>error_model = "tc"</code>.</li>  </ul>  </div> @@ -151,8 +150,8 @@  <div id="credits-and-historical-remarks" class="section level2">  <h2 class="hasAnchor">  <a href="#credits-and-historical-remarks" class="anchor"></a>Credits and historical remarks</h2> -<p><code>mkin</code> would not be possible without the underlying software stack consisting of R and the packages <a href="https://cran.r-project.org/package=deSolve">deSolve</a> and <a href="https://cran.r-project.org/package=FME">FME</a>, to say the least.</p> -<p>It could not have been written without me being introduced to regulatory fate modelling of pesticides by Adrian Gurney during my time at Harlan Laboratories Ltd (formerly RCC Ltd). <code>mkin</code> greatly profits from and largely follows the work done by the <a href="http://esdac.jrc.ec.europa.eu/projects/degradation-kinetics">FOCUS Degradation Kinetics Workgroup</a>, as detailed in their guidance document from 2006, slightly updated in 2011 and in 2014.</p> +<p><code>mkin</code> would not be possible without the underlying software stack consisting of, among others, R and the package <a href="https://cran.r-project.org/package=deSolve">deSolve</a>. In previous version, <code>mkin</code> was also using the functionality of the <a href="https://cran.r-project.org/package=FME">FME</a> package. Please refer to the <a href="https://cran.r-project.org/package=mkin">package page on CRAN</a> for the full list of imported and suggested R packages. Also, <a href="https://debian.org">Debian Linux</a>, the vim editor and the <a href="https://github.com/jalvesaq/Nvim-R">Nvim-R</a> plugin have been invaluable in its development.</p> +<p><code>mkin</code> could not have been written without me being introduced to regulatory fate modelling of pesticides by Adrian Gurney during my time at Harlan Laboratories Ltd (formerly RCC Ltd). <code>mkin</code> greatly profits from and largely follows the work done by the <a href="http://esdac.jrc.ec.europa.eu/projects/degradation-kinetics">FOCUS Degradation Kinetics Workgroup</a>, as detailed in their guidance document from 2006, slightly updated in 2011 and in 2014.</p>  <p>Also, it was inspired by the first version of KinGUI developed by BayerCropScience, which is based on the MatLab runtime environment.</p>  <p>The companion package <a href="http://kinfit.r-forge.r-project.org/kinfit_static/index.html">kinfit</a> (now deprecated) was <a href="https://r-forge.r-project.org/scm/viewvc.php?view=rev&root=kinfit&revision=2">started in 2008</a> and <a href="https://cran.r-project.org/src/contrib/Archive/kinfit/">first published</a> on CRAN on 01 May 2010.</p>  <p>The first <code>mkin</code> code was <a href="https://r-forge.r-project.org/scm/viewvc.php?view=rev&root=kinfit&revision=8">published on 11 May 2010</a> and the <a href="https://cran.r-project.org/src/contrib/Archive/mkin">first CRAN version</a> on 18 May 2010.</p> @@ -160,10 +159,28 @@  <p>Somewhat in parallel, Syngenta has sponsored the development of an <code>mkin</code> and KinGUII based GUI application called CAKE, which also adds IRLS and MCMC, is more limited in the model formulation, but puts more weight on usability. CAKE is available for download from the <a href="https://www.tessella.com/showcase/computer-assisted-kinetic-evaluation">CAKE website</a>, where you can also find a zip archive of the R scripts derived from <code>mkin</code>, published under the GPL license.</p>  <p>Finally, there is <a href="http://github.com/zhenglei-gao/KineticEval">KineticEval</a>, which contains a further development of the scripts used for KinGUII, so the different tools will hopefully be able to learn from each other in the future as well.</p>  </div> +<div id="references" class="section level2"> +<h2 class="hasAnchor"> +<a href="#references" class="anchor"></a>References</h2> +<table class="table"> +<tr><td>Ranke J, Meinecke S (2019) +  Error Models for the Kinetic Evaluation of Chemical Degradation Data +  <i>Environments</i> +  <b>6</b> (12) 124 +  <a href="https://doi.org/10.3390/environments6120124">doi:10.3390/environments6120124</a> +  </td></tr> +<tr><td>Ranke J, Wöltjen J, Meinecke S (2018) +  Comparison of software tools for kinetic evaluation of chemical degradation data +  <i>Environmental Sciences Europe</i> +  <b>30</b> 17 +  <a href="https://doi.org/10.1186/s12302-018-0145-1">doi:10.1186/s12302-018-0145-1</a> +  </td></tr> +</table> +</div>  <div id="development" class="section level2">  <h2 class="hasAnchor">  <a href="#development" class="anchor"></a>Development</h2> -<p>Contributions are welcome! Your <a href="https://help.github.com/articles/fork-a-repo">mkin fork</a> is just a mouse click away… The master branch on github should always be in good shape, I implement new features in separate branches now. If you prefer subversion, project members for the <a href="http://r-forge.r-project.org/R/?group_id=615">r-forge project</a> are welcome as well. Generally, the source code of the latest CRAN version should be available there. You can also browse the source code at <a href="http://cgit.jrwb.de/mkin">cgit.jrwb.de/mkin</a>.</p> +<p>Contributions are welcome!</p>  </div>  </div>    </div> diff --git a/docs/news/index.html b/docs/news/index.html index 48ba25e5..3327e48f 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -67,7 +67,7 @@        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.8</span> +        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.9</span>        </span>      </div> @@ -134,6 +134,8 @@  <a href="#mkin-0-9-49-8-unreleased" class="anchor"></a>mkin 0.9.49.8 (unreleased)<small> Unreleased </small>  </h1>  <ul> +<li><p>‘aw’: Generic function for calculating Akaike weights, methods for mkinfit objects and mmkin columns</p></li> +<li><p>‘loftest’: Add a lack-of-fit test</p></li>  <li><p>‘plot_res’, ‘plot_sep’ and ‘mkinerrplot’: Add the possibility to show standardized residuals and make it the default for fits with error models other than ‘const’</p></li>  <li><p>‘lrtest.mkinfit’: Improve naming of the compared fits in the case of fixed parameters</p></li>  <li><p>‘confint.mkinfit’: Make the quadratic approximation the default, as the likelihood profiling takes a lot of time, especially if the fit has more than three parameters</p></li> @@ -145,7 +147,7 @@  </h1>  <ul>  <li><p>Fix a bug introduced in 0.9.49.6 that occurred if the direct optimisation yielded a higher likelihood than the three-step optimisation in the d_3 algorithm, which caused the fitted parameters of the three-step optimisation to be returned instead of the parameters of the direct optimisation</p></li> -<li><p>Add an ‘nobs’ method for mkinfit methods, enabling the default ‘BIC’ method from the stats package. Also, add a ‘BIC’ method for mmkin column objects.</p></li> +<li><p>Add a ‘nobs’ method for mkinfit objects, enabling the default ‘BIC’ method from the stats package. Also, add a ‘BIC’ method for mmkin column objects.</p></li>  </ul>  </div>      <div id="mkin-0-9-49-6-2019-10-31" class="section level1"> diff --git a/docs/reference/aw.html b/docs/reference/aw.html new file mode 100644 index 00000000..22201229 --- /dev/null +++ b/docs/reference/aw.html @@ -0,0 +1,214 @@ +<!-- Generated by pkgdown: do not edit by hand --> +<!DOCTYPE html> +<html lang="en"> +  <head> +  <meta charset="utf-8"> +<meta http-equiv="X-UA-Compatible" content="IE=edge"> +<meta name="viewport" content="width=device-width, initial-scale=1.0"> + +<title>Calculate Akaike weights for model averaging — aw • mkin</title> + + +<!-- jquery --> +<script src="https://cdnjs.cloudflare.com/ajax/libs/jquery/3.3.1/jquery.min.js" integrity="sha256-FgpCb/KJQlLNfOu91ta32o/NMZxltwRo8QtmkMRdAu8=" crossorigin="anonymous"></script> +<!-- Bootstrap --> + +<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.3.7/css/bootstrap.min.css" integrity="sha256-916EbMg70RQy9LHiGkXzG8hSg9EdNy97GazNG/aiY1w=" crossorigin="anonymous" /> + +<script src="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.3.7/js/bootstrap.min.js" integrity="sha256-U5ZEeKfGNOja007MMD3YBI0A3OSZOQbeG6z2f2Y0hu8=" crossorigin="anonymous"></script> + +<!-- Font Awesome icons --> +<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.7.1/css/all.min.css" integrity="sha256-nAmazAk6vS34Xqo0BSrTb+abbtFlgsFK7NKSi6o7Y78=" crossorigin="anonymous" /> +<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.7.1/css/v4-shims.min.css" integrity="sha256-6qHlizsOWFskGlwVOKuns+D1nB6ssZrHQrNj1wGplHc=" crossorigin="anonymous" /> + +<!-- clipboard.js --> +<script src="https://cdnjs.cloudflare.com/ajax/libs/clipboard.js/2.0.4/clipboard.min.js" integrity="sha256-FiZwavyI2V6+EXO1U+xzLG3IKldpiTFf3153ea9zikQ=" crossorigin="anonymous"></script> + +<!-- headroom.js --> +<script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.9.4/headroom.min.js" integrity="sha256-DJFC1kqIhelURkuza0AvYal5RxMtpzLjFhsnVIeuk+U=" crossorigin="anonymous"></script> +<script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.9.4/jQuery.headroom.min.js" integrity="sha256-ZX/yNShbjqsohH1k95liqY9Gd8uOiE1S4vZc+9KQ1K4=" crossorigin="anonymous"></script> + +<!-- pkgdown --> +<link href="../pkgdown.css" rel="stylesheet"> +<script src="../pkgdown.js"></script> + + + + +<meta property="og:title" content="Calculate Akaike weights for model averaging — aw" /> +<meta property="og:description" content="Akaike weights are calculated based on the relative +expected Kullback-Leibler information as specified +by Burnham and Anderson (2004)." /> +<meta name="twitter:card" content="summary" /> + + + + +<!-- mathjax --> +<script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script> +<script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script> + +<!--[if lt IE 9]> +<script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> +<script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> +<![endif]--> + + + +  </head> + +  <body> +    <div class="container template-reference-topic"> +      <header> +      <div class="navbar navbar-default navbar-fixed-top" role="navigation"> +  <div class="container"> +    <div class="navbar-header"> +      <button type="button" class="navbar-toggle collapsed" data-toggle="collapse" data-target="#navbar" aria-expanded="false"> +        <span class="sr-only">Toggle navigation</span> +        <span class="icon-bar"></span> +        <span class="icon-bar"></span> +        <span class="icon-bar"></span> +      </button> +      <span class="navbar-brand"> +        <a class="navbar-link" href="../index.html">mkin</a> +        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.8</span> +      </span> +    </div> + +    <div id="navbar" class="navbar-collapse collapse"> +      <ul class="nav navbar-nav"> +        <li> +  <a href="../reference/index.html">Functions and data</a> +</li> +<li class="dropdown"> +  <a href="#" class="dropdown-toggle" data-toggle="dropdown" role="button" aria-expanded="false"> +    Articles +      +    <span class="caret"></span> +  </a> +  <ul class="dropdown-menu" role="menu"> +    <li> +      <a href="../articles/mkin.html">Introduction to mkin</a> +    </li> +    <li> +      <a href="../articles/FOCUS_D.html">Example evaluation of FOCUS Example Dataset D</a> +    </li> +    <li> +      <a href="../articles/FOCUS_L.html">Example evaluation of FOCUS Laboratory Data L1 to L3</a> +    </li> +    <li> +      <a href="../articles/web_only/FOCUS_Z.html">Example evaluation of FOCUS Example Dataset Z</a> +    </li> +    <li> +      <a href="../articles/web_only/compiled_models.html">Performance benefit by using compiled model definitions in mkin</a> +    </li> +    <li> +      <a href="../articles/twa.html">Calculation of time weighted average concentrations with mkin</a> +    </li> +    <li> +      <a href="../articles/web_only/NAFTA_examples.html">Example evaluation of NAFTA SOP Attachment examples</a> +    </li> +  </ul> +</li> +<li> +  <a href="../news/index.html">News</a> +</li> +      </ul> +      <ul class="nav navbar-nav navbar-right"> +         +      </ul> +       +    </div><!--/.nav-collapse --> +  </div><!--/.container --> +</div><!--/.navbar --> + +       + +      </header> + +<div class="row"> +  <div class="col-md-9 contents"> +    <div class="page-header"> +    <h1>Calculate Akaike weights for model averaging</h1> +     +    <div class="hidden name"><code>aw.Rd</code></div> +    </div> + +    <div class="ref-description"> +    <p>Akaike weights are calculated based on the relative +expected Kullback-Leibler information as specified +by Burnham and Anderson (2004).</p> +    </div> + +    <pre class="usage"><span class='fu'>aw</span>(<span class='no'>object</span>, <span class='no'>...</span>) + +<span class='co'># S3 method for mkinfit</span> +<span class='fu'>aw</span>(<span class='no'>object</span>, <span class='no'>...</span>) + +<span class='co'># S3 method for mmkin</span> +<span class='fu'>aw</span>(<span class='no'>object</span>, <span class='no'>...</span>)</pre> + +    <h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2> +    <table class="ref-arguments"> +    <colgroup><col class="name" /><col class="desc" /></colgroup> +    <tr> +      <th>object</th> +      <td><p>An <a href='mmkin.html'>mmkin</a> column object, containing two or more +<a href='mkinfit.html'>mkinfit</a> models that have been fitted to the same data, +or an mkinfit object. In the latter case, further mkinfit +objects fitted to the same data should be specified +as dots arguments.</p></td> +    </tr> +    <tr> +      <th>...</th> +      <td><p>Not used in the method for <a href='mmkin.html'>mmkin</a> column objects, +further <a href='mkinfit.html'>mkinfit</a> objects in the method for mkinfit objects.</p></td> +    </tr> +    </table> + +    <h2 class="hasAnchor" id="references"><a class="anchor" href="#references"></a>References</h2> + +    <p>Burnham KP and Anderson DR (2004) Multimodel +Inference: Understanding AIC and BIC in Model Selection. +<em>Sociological Methods & Research</em> <strong>33</strong>(2) 261-304</p> + +    <h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2> +    <pre class="examples"><div class='input'><span class='co'># \dontrun{</span> +<span class='no'>f_sfo</span> <span class='kw'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span>(<span class='st'>"SFO"</span>, <span class='no'>FOCUS_2006_D</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) +<span class='no'>f_dfop</span> <span class='kw'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span>(<span class='st'>"DFOP"</span>, <span class='no'>FOCUS_2006_D</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) +<span class='no'>aw_sfo_dfop</span> <span class='kw'><-</span> <span class='fu'>aw</span>(<span class='no'>f_sfo</span>, <span class='no'>f_dfop</span>) +<span class='fu'><a href='https://rdrr.io/r/base/sum.html'>sum</a></span>(<span class='no'>aw_sfo_dfop</span>)</div><div class='output co'>#> [1] 1</div><div class='input'><span class='no'>aw_sfo_dfop</span> <span class='co'># SFO gets more weight as it has less parameters and a similar fit</span></div><div class='output co'>#> [1] 0.5970258 0.4029742</div><div class='input'><span class='no'>f</span> <span class='kw'><-</span> <span class='fu'><a href='mmkin.html'>mmkin</a></span>(<span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='st'>"SFO"</span>, <span class='st'>"FOMC"</span>, <span class='st'>"DFOP"</span>), <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='st'>"FOCUS D"</span> <span class='kw'>=</span> <span class='no'>FOCUS_2006_D</span>), <span class='kw'>cores</span> <span class='kw'>=</span> <span class='fl'>1</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) +<span class='fu'>aw</span>(<span class='no'>f</span>)</div><div class='output co'>#> [1] 0.4808722 0.1945539 0.3245740</div><div class='input'><span class='fu'><a href='https://rdrr.io/r/base/sum.html'>sum</a></span>(<span class='fu'>aw</span>(<span class='no'>f</span>))</div><div class='output co'>#> [1] 1</div><div class='input'><span class='fu'>aw</span>(<span class='no'>f</span>[<span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='st'>"SFO"</span>, <span class='st'>"DFOP"</span>)])</div><div class='output co'>#> [1] 0.5970258 0.4029742</div><div class='input'># } +</div></pre> +  </div> +  <div class="col-md-3 hidden-xs hidden-sm" id="sidebar"> +    <h2>Contents</h2> +    <ul class="nav nav-pills nav-stacked"> +      <li><a href="#arguments">Arguments</a></li> +      <li><a href="#references">References</a></li> +      <li><a href="#examples">Examples</a></li> +    </ul> + +  </div> +</div> + + +      <footer> +      <div class="copyright"> +  <p>Developed by Johannes Ranke.</p> +</div> + +<div class="pkgdown"> +  <p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.4.1.</p> +</div> + +      </footer> +   </div> + +   + + +  </body> +</html> + + diff --git a/docs/reference/index.html b/docs/reference/index.html index 1c9975e0..6ccc9255 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -67,7 +67,7 @@        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.8</span> +        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.9</span>        </span>      </div> @@ -209,12 +209,18 @@ more datasets</p></td>        </tr><tr>          <td> -          <p><code><a href="lrtest.mkinfit.html">lrtest(<i><mkinfit></i>)</a></code> </p> +          <p><code><a href="lrtest.mkinfit.html">lrtest(<i><mkinfit></i>)</a></code> <code><a href="lrtest.mkinfit.html">lrtest(<i><mmkin></i>)</a></code> </p>          </td>          <td><p>Likelihood ratio test for mkinfit models</p></td>        </tr><tr>          <td> +          <p><code><a href="loftest.html">loftest()</a></code> </p> +        </td> +        <td><p>Lack-of-fit test for models fitted to data with replicates</p></td> +      </tr><tr> +         +        <td>            <p><code><a href="mkinerrmin.html">mkinerrmin()</a></code> </p>          </td>          <td><p>Calculate the minimum error to assume in order to pass the variance test</p></td> @@ -228,6 +234,12 @@ with mkinfit</p></td>        </tr><tr>          <td> +          <p><code><a href="aw.html">aw()</a></code> </p> +        </td> +        <td><p>Calculate Akaike weights for model averaging</p></td> +      </tr><tr> +         +        <td>            <p><code><a href="CAKE_export.html">CAKE_export()</a></code> </p>          </td>          <td><p>Export a list of datasets format to a CAKE study file</p></td> @@ -432,7 +444,7 @@ kinetic models fitted with mkinfit</p></td>          <td>            <p><code><a href="sigma_twocomp.html">sigma_twocomp()</a></code> </p>          </td> -        <td><p>Two component error model</p></td> +        <td><p>Two-component error model</p></td>        </tr><tr>          <td> diff --git a/docs/reference/loftest-1.png b/docs/reference/loftest-1.pngBinary files differ new file mode 100644 index 00000000..3d20f41e --- /dev/null +++ b/docs/reference/loftest-1.png diff --git a/docs/reference/loftest-2.png b/docs/reference/loftest-2.pngBinary files differ new file mode 100644 index 00000000..be8bf815 --- /dev/null +++ b/docs/reference/loftest-2.png diff --git a/docs/reference/loftest-3.png b/docs/reference/loftest-3.pngBinary files differ new file mode 100644 index 00000000..c66c95f1 --- /dev/null +++ b/docs/reference/loftest-3.png diff --git a/docs/reference/loftest-4.png b/docs/reference/loftest-4.pngBinary files differ new file mode 100644 index 00000000..da86d97f --- /dev/null +++ b/docs/reference/loftest-4.png diff --git a/docs/reference/loftest-5.png b/docs/reference/loftest-5.pngBinary files differ new file mode 100644 index 00000000..54b176e7 --- /dev/null +++ b/docs/reference/loftest-5.png diff --git a/docs/reference/loftest.html b/docs/reference/loftest.html new file mode 100644 index 00000000..757f0bbe --- /dev/null +++ b/docs/reference/loftest.html @@ -0,0 +1,343 @@ +<!-- Generated by pkgdown: do not edit by hand --> +<!DOCTYPE html> +<html lang="en"> +  <head> +  <meta charset="utf-8"> +<meta http-equiv="X-UA-Compatible" content="IE=edge"> +<meta name="viewport" content="width=device-width, initial-scale=1.0"> + +<title>Lack-of-fit test for models fitted to data with replicates — loftest • mkin</title> + + +<!-- jquery --> +<script src="https://cdnjs.cloudflare.com/ajax/libs/jquery/3.3.1/jquery.min.js" integrity="sha256-FgpCb/KJQlLNfOu91ta32o/NMZxltwRo8QtmkMRdAu8=" crossorigin="anonymous"></script> +<!-- Bootstrap --> + +<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.3.7/css/bootstrap.min.css" integrity="sha256-916EbMg70RQy9LHiGkXzG8hSg9EdNy97GazNG/aiY1w=" crossorigin="anonymous" /> + +<script src="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.3.7/js/bootstrap.min.js" integrity="sha256-U5ZEeKfGNOja007MMD3YBI0A3OSZOQbeG6z2f2Y0hu8=" crossorigin="anonymous"></script> + +<!-- Font Awesome icons --> +<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.7.1/css/all.min.css" integrity="sha256-nAmazAk6vS34Xqo0BSrTb+abbtFlgsFK7NKSi6o7Y78=" crossorigin="anonymous" /> +<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.7.1/css/v4-shims.min.css" integrity="sha256-6qHlizsOWFskGlwVOKuns+D1nB6ssZrHQrNj1wGplHc=" crossorigin="anonymous" /> + +<!-- clipboard.js --> +<script src="https://cdnjs.cloudflare.com/ajax/libs/clipboard.js/2.0.4/clipboard.min.js" integrity="sha256-FiZwavyI2V6+EXO1U+xzLG3IKldpiTFf3153ea9zikQ=" crossorigin="anonymous"></script> + +<!-- headroom.js --> +<script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.9.4/headroom.min.js" integrity="sha256-DJFC1kqIhelURkuza0AvYal5RxMtpzLjFhsnVIeuk+U=" crossorigin="anonymous"></script> +<script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.9.4/jQuery.headroom.min.js" integrity="sha256-ZX/yNShbjqsohH1k95liqY9Gd8uOiE1S4vZc+9KQ1K4=" crossorigin="anonymous"></script> + +<!-- pkgdown --> +<link href="../pkgdown.css" rel="stylesheet"> +<script src="../pkgdown.js"></script> + + + + +<meta property="og:title" content="Lack-of-fit test for models fitted to data with replicates — loftest" /> +<meta property="og:description" content="This is a generic function with a method currently only defined for mkinfit +objects. It fits an anova model to the data contained in the object and +compares the likelihoods using the likelihood ratio test +lrtest.default from the lmtest package." /> +<meta name="twitter:card" content="summary" /> + + + + +<!-- mathjax --> +<script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script> +<script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script> + +<!--[if lt IE 9]> +<script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> +<script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> +<![endif]--> + + + +  </head> + +  <body> +    <div class="container template-reference-topic"> +      <header> +      <div class="navbar navbar-default navbar-fixed-top" role="navigation"> +  <div class="container"> +    <div class="navbar-header"> +      <button type="button" class="navbar-toggle collapsed" data-toggle="collapse" data-target="#navbar" aria-expanded="false"> +        <span class="sr-only">Toggle navigation</span> +        <span class="icon-bar"></span> +        <span class="icon-bar"></span> +        <span class="icon-bar"></span> +      </button> +      <span class="navbar-brand"> +        <a class="navbar-link" href="../index.html">mkin</a> +        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.8</span> +      </span> +    </div> + +    <div id="navbar" class="navbar-collapse collapse"> +      <ul class="nav navbar-nav"> +        <li> +  <a href="../reference/index.html">Functions and data</a> +</li> +<li class="dropdown"> +  <a href="#" class="dropdown-toggle" data-toggle="dropdown" role="button" aria-expanded="false"> +    Articles +      +    <span class="caret"></span> +  </a> +  <ul class="dropdown-menu" role="menu"> +    <li> +      <a href="../articles/mkin.html">Introduction to mkin</a> +    </li> +    <li> +      <a href="../articles/FOCUS_D.html">Example evaluation of FOCUS Example Dataset D</a> +    </li> +    <li> +      <a href="../articles/FOCUS_L.html">Example evaluation of FOCUS Laboratory Data L1 to L3</a> +    </li> +    <li> +      <a href="../articles/web_only/FOCUS_Z.html">Example evaluation of FOCUS Example Dataset Z</a> +    </li> +    <li> +      <a href="../articles/web_only/compiled_models.html">Performance benefit by using compiled model definitions in mkin</a> +    </li> +    <li> +      <a href="../articles/twa.html">Calculation of time weighted average concentrations with mkin</a> +    </li> +    <li> +      <a href="../articles/web_only/NAFTA_examples.html">Example evaluation of NAFTA SOP Attachment examples</a> +    </li> +  </ul> +</li> +<li> +  <a href="../news/index.html">News</a> +</li> +      </ul> +      <ul class="nav navbar-nav navbar-right"> +         +      </ul> +       +    </div><!--/.nav-collapse --> +  </div><!--/.container --> +</div><!--/.navbar --> + +       + +      </header> + +<div class="row"> +  <div class="col-md-9 contents"> +    <div class="page-header"> +    <h1>Lack-of-fit test for models fitted to data with replicates</h1> +     +    <div class="hidden name"><code>loftest.Rd</code></div> +    </div> + +    <div class="ref-description"> +    <p>This is a generic function with a method currently only defined for mkinfit +objects. It fits an anova model to the data contained in the object and +compares the likelihoods using the likelihood ratio test +<code><a href='https://rdrr.io/pkg/lmtest/man/lrtest.html'>lrtest.default</a></code> from the lmtest package.</p> +    </div> + +    <pre class="usage"><span class='fu'>loftest</span>(<span class='no'>object</span>, <span class='no'>...</span>) + +<span class='co'># S3 method for mkinfit</span> +<span class='fu'>loftest</span>(<span class='no'>object</span>, <span class='no'>...</span>)</pre> + +    <h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2> +    <table class="ref-arguments"> +    <colgroup><col class="name" /><col class="desc" /></colgroup> +    <tr> +      <th>object</th> +      <td><p>A model object with a defined loftest method</p></td> +    </tr> +    <tr> +      <th>...</th> +      <td><p>Not used</p></td> +    </tr> +    </table> + +    <h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2> + +    <p>The anova model is interpreted as the simplest form of an mkinfit model, +assuming only a constant variance about the means, but not enforcing any +structure of the means, so we have one model parameter for every mean +of replicate samples.</p> +    <h2 class="hasAnchor" id="see-also"><a class="anchor" href="#see-also"></a>See also</h2> + +    <div class='dont-index'><p>lrtest</p></div> + +    <h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2> +    <pre class="examples"><div class='input'><span class='co'># \dontrun{</span> +<span class='no'>test_data</span> <span class='kw'><-</span> <span class='fu'><a href='https://rdrr.io/r/base/subset.html'>subset</a></span>(<span class='no'>synthetic_data_for_UBA_2014</span><span class='kw'>[[</span><span class='fl'>12</span>]]$<span class='no'>data</span>, <span class='no'>name</span> <span class='kw'>==</span> <span class='st'>"parent"</span>) +<span class='no'>sfo_fit</span> <span class='kw'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span>(<span class='st'>"SFO"</span>, <span class='no'>test_data</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) +<span class='fu'><a href='plot.mkinfit.html'>plot_res</a></span>(<span class='no'>sfo_fit</span>) <span class='co'># We see a clear pattern in the residuals</span></div><div class='img'><img src='loftest-1.png' alt='' width='700' height='433' /></div><div class='input'><span class='fu'>loftest</span>(<span class='no'>sfo_fit</span>)  <span class='co'># We have a clear lack of fit</span></div><div class='output co'>#> Likelihood ratio test +#>  +#> Model 1: ANOVA with error model const +#> Model 2: SFO with error model const +#>   #Df  LogLik Df  Chisq Pr(>Chisq)     +#> 1  10 -40.710                          +#> 2   3 -63.954 -7 46.487  7.027e-08 *** +#> --- +#> Signif. codes:  0 ‘***’ 0.001 ‘**’ 0.01 ‘*’ 0.05 ‘.’ 0.1 ‘ ’ 1</div><div class='input'><span class='co'>#</span> +<span class='co'># We try a different model (the one that was used to generate the data)</span> +<span class='no'>dfop_fit</span> <span class='kw'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span>(<span class='st'>"DFOP"</span>, <span class='no'>test_data</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) +<span class='fu'><a href='plot.mkinfit.html'>plot_res</a></span>(<span class='no'>dfop_fit</span>) <span class='co'># We don't see systematic deviations, but heteroscedastic residuals</span></div><div class='img'><img src='loftest-2.png' alt='' width='700' height='433' /></div><div class='input'><span class='co'># therefore we should consider adapting the error model, although we have</span> +<span class='fu'>loftest</span>(<span class='no'>dfop_fit</span>) <span class='co'># no lack of fit</span></div><div class='output co'>#> Likelihood ratio test +#>  +#> Model 1: ANOVA with error model const +#> Model 2: DFOP with error model const +#>   #Df  LogLik Df Chisq Pr(>Chisq) +#> 1  10 -40.710                     +#> 2   5 -42.453 -5 3.485     0.6257</div><div class='input'><span class='co'>#</span> +<span class='co'># This is the anova model used internally for the comparison</span> +<span class='no'>test_data_anova</span> <span class='kw'><-</span> <span class='no'>test_data</span> +<span class='no'>test_data_anova</span>$<span class='no'>time</span> <span class='kw'><-</span> <span class='fu'><a href='https://rdrr.io/r/base/factor.html'>as.factor</a></span>(<span class='no'>test_data_anova</span>$<span class='no'>time</span>) +<span class='no'>anova_fit</span> <span class='kw'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/lm.html'>lm</a></span>(<span class='no'>value</span> ~ <span class='no'>time</span>, <span class='kw'>data</span> <span class='kw'>=</span> <span class='no'>test_data_anova</span>) +<span class='fu'><a href='https://rdrr.io/r/base/summary.html'>summary</a></span>(<span class='no'>anova_fit</span>)</div><div class='output co'>#>  +#> Call: +#> lm(formula = value ~ time, data = test_data_anova) +#>  +#> Residuals: +#>     Min      1Q  Median      3Q     Max  +#> -6.1000 -0.5625  0.0000  0.5625  6.1000  +#>  +#> Coefficients: +#>             Estimate Std. Error t value Pr(>|t|)     +#> (Intercept)  103.150      2.323  44.409 7.44e-12 *** +#> time1        -19.950      3.285  -6.073 0.000185 *** +#> time3        -50.800      3.285 -15.465 8.65e-08 *** +#> time7        -68.500      3.285 -20.854 6.28e-09 *** +#> time14       -79.750      3.285 -24.278 1.63e-09 *** +#> time28       -86.000      3.285 -26.181 8.35e-10 *** +#> time60       -94.900      3.285 -28.891 3.48e-10 *** +#> time90       -98.500      3.285 -29.986 2.49e-10 *** +#> time120     -100.450      3.285 -30.580 2.09e-10 *** +#> --- +#> Signif. codes:  0 ‘***’ 0.001 ‘**’ 0.01 ‘*’ 0.05 ‘.’ 0.1 ‘ ’ 1 +#>  +#> Residual standard error: 3.285 on 9 degrees of freedom +#> Multiple R-squared:  0.9953,	Adjusted R-squared:  0.9912  +#> F-statistic: 240.5 on 8 and 9 DF,  p-value: 1.417e-09 +#> </div><div class='input'><span class='fu'><a href='https://rdrr.io/r/stats/logLik.html'>logLik</a></span>(<span class='no'>anova_fit</span>) <span class='co'># We get the same likelihood and degrees of freedom</span></div><div class='output co'>#> 'log Lik.' -40.71015 (df=10)</div><div class='input'><span class='co'>#</span> +<span class='no'>test_data_2</span> <span class='kw'><-</span> <span class='no'>synthetic_data_for_UBA_2014</span><span class='kw'>[[</span><span class='fl'>12</span>]]$<span class='no'>data</span> +<span class='no'>m_synth_SFO_lin</span> <span class='kw'><-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span>(<span class='kw'>parent</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='kw'>type</span> <span class='kw'>=</span> <span class='st'>"SFO"</span>, <span class='kw'>to</span> <span class='kw'>=</span> <span class='st'>"M1"</span>), +  <span class='kw'>M1</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='kw'>type</span> <span class='kw'>=</span> <span class='st'>"SFO"</span>, <span class='kw'>to</span> <span class='kw'>=</span> <span class='st'>"M2"</span>), +  <span class='kw'>M2</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='kw'>type</span> <span class='kw'>=</span> <span class='st'>"SFO"</span>), <span class='kw'>use_of_ff</span> <span class='kw'>=</span> <span class='st'>"max"</span>)</div><div class='output co'>#> <span class='message'>Successfully compiled differential equation model from auto-generated C code.</span></div><div class='input'><span class='no'>sfo_lin_fit</span> <span class='kw'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span>(<span class='no'>m_synth_SFO_lin</span>, <span class='no'>test_data_2</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) +<span class='fu'><a href='plot.mkinfit.html'>plot_res</a></span>(<span class='no'>sfo_lin_fit</span>) <span class='co'># not a good model, we try parallel formation</span></div><div class='img'><img src='loftest-3.png' alt='' width='700' height='433' /></div><div class='input'><span class='fu'>loftest</span>(<span class='no'>sfo_lin_fit</span>)</div><div class='output co'>#> Likelihood ratio test +#>  +#> Model 1: ANOVA with error model const +#> Model 2: m_synth_SFO_lin with error model const and fixed parameter(s) M1_0, M2_0 +#>   #Df   LogLik  Df  Chisq Pr(>Chisq)     +#> 1  28  -93.606                           +#> 2   7 -171.927 -21 156.64  < 2.2e-16 *** +#> --- +#> Signif. codes:  0 ‘***’ 0.001 ‘**’ 0.01 ‘*’ 0.05 ‘.’ 0.1 ‘ ’ 1</div><div class='input'><span class='co'>#</span> +<span class='no'>m_synth_SFO_par</span> <span class='kw'><-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span>(<span class='kw'>parent</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='kw'>type</span> <span class='kw'>=</span> <span class='st'>"SFO"</span>, <span class='kw'>to</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='st'>"M1"</span>, <span class='st'>"M2"</span>)), +  <span class='kw'>M1</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='kw'>type</span> <span class='kw'>=</span> <span class='st'>"SFO"</span>), +  <span class='kw'>M2</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='kw'>type</span> <span class='kw'>=</span> <span class='st'>"SFO"</span>), <span class='kw'>use_of_ff</span> <span class='kw'>=</span> <span class='st'>"max"</span>)</div><div class='output co'>#> <span class='message'>Successfully compiled differential equation model from auto-generated C code.</span></div><div class='input'><span class='no'>sfo_par_fit</span> <span class='kw'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span>(<span class='no'>m_synth_SFO_par</span>, <span class='no'>test_data_2</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) +<span class='fu'><a href='plot.mkinfit.html'>plot_res</a></span>(<span class='no'>sfo_par_fit</span>) <span class='co'># much better for metabolites</span></div><div class='img'><img src='loftest-4.png' alt='' width='700' height='433' /></div><div class='input'><span class='fu'>loftest</span>(<span class='no'>sfo_par_fit</span>)</div><div class='output co'>#> Likelihood ratio test +#>  +#> Model 1: ANOVA with error model const +#> Model 2: m_synth_SFO_par with error model const and fixed parameter(s) M1_0, M2_0 +#>   #Df   LogLik  Df  Chisq Pr(>Chisq)     +#> 1  28  -93.606                           +#> 2   7 -156.331 -21 125.45  < 2.2e-16 *** +#> --- +#> Signif. codes:  0 ‘***’ 0.001 ‘**’ 0.01 ‘*’ 0.05 ‘.’ 0.1 ‘ ’ 1</div><div class='input'><span class='co'>#</span> +<span class='no'>m_synth_DFOP_par</span> <span class='kw'><-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span>(<span class='kw'>parent</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='kw'>type</span> <span class='kw'>=</span> <span class='st'>"DFOP"</span>, <span class='kw'>to</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='st'>"M1"</span>, <span class='st'>"M2"</span>)), +  <span class='kw'>M1</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='kw'>type</span> <span class='kw'>=</span> <span class='st'>"SFO"</span>), +  <span class='kw'>M2</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span>(<span class='kw'>type</span> <span class='kw'>=</span> <span class='st'>"SFO"</span>), <span class='kw'>use_of_ff</span> <span class='kw'>=</span> <span class='st'>"max"</span>)</div><div class='output co'>#> <span class='message'>Successfully compiled differential equation model from auto-generated C code.</span></div><div class='input'><span class='no'>dfop_par_fit</span> <span class='kw'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span>(<span class='no'>m_synth_DFOP_par</span>, <span class='no'>test_data_2</span>, <span class='kw'>quiet</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>) +<span class='fu'><a href='plot.mkinfit.html'>plot_res</a></span>(<span class='no'>dfop_par_fit</span>) <span class='co'># No visual lack of fit</span></div><div class='img'><img src='loftest-5.png' alt='' width='700' height='433' /></div><div class='input'><span class='fu'>loftest</span>(<span class='no'>dfop_par_fit</span>)  <span class='co'># no lack of fit found by the test</span></div><div class='output co'>#> Likelihood ratio test +#>  +#> Model 1: ANOVA with error model const +#> Model 2: m_synth_DFOP_par with error model const and fixed parameter(s) M1_0, M2_0 +#>   #Df   LogLik  Df  Chisq Pr(>Chisq) +#> 1  28  -93.606                       +#> 2   9 -102.763 -19 18.313     0.5016</div><div class='input'><span class='co'>#</span> +<span class='co'># The anova model used for comparison in the case of transformation products</span> +<span class='no'>test_data_anova_2</span> <span class='kw'><-</span> <span class='no'>dfop_par_fit</span>$<span class='no'>data</span> +<span class='no'>test_data_anova_2</span>$<span class='no'>variable</span> <span class='kw'><-</span> <span class='fu'><a href='https://rdrr.io/r/base/factor.html'>as.factor</a></span>(<span class='no'>test_data_anova_2</span>$<span class='no'>variable</span>) +<span class='no'>test_data_anova_2</span>$<span class='no'>time</span> <span class='kw'><-</span> <span class='fu'><a href='https://rdrr.io/r/base/factor.html'>as.factor</a></span>(<span class='no'>test_data_anova_2</span>$<span class='no'>time</span>) +<span class='no'>anova_fit_2</span> <span class='kw'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/lm.html'>lm</a></span>(<span class='no'>observed</span> ~ <span class='no'>time</span>:<span class='no'>variable</span> - <span class='fl'>1</span>, <span class='kw'>data</span> <span class='kw'>=</span> <span class='no'>test_data_anova_2</span>) +<span class='fu'><a href='https://rdrr.io/r/base/summary.html'>summary</a></span>(<span class='no'>anova_fit_2</span>)</div><div class='output co'>#>  +#> Call: +#> lm(formula = observed ~ time:variable - 1, data = test_data_anova_2) +#>  +#> Residuals: +#>     Min      1Q  Median      3Q     Max  +#> -6.1000 -0.5875  0.0000  0.5875  6.1000  +#>  +#> Coefficients: (2 not defined because of singularities) +#>                        Estimate Std. Error t value Pr(>|t|)     +#> time0:variableparent    103.150      1.573  65.562  < 2e-16 *** +#> time1:variableparent     83.200      1.573  52.882  < 2e-16 *** +#> time3:variableparent     52.350      1.573  33.274  < 2e-16 *** +#> time7:variableparent     34.650      1.573  22.024  < 2e-16 *** +#> time14:variableparent    23.400      1.573  14.873 6.35e-14 *** +#> time28:variableparent    17.150      1.573  10.901 5.47e-11 *** +#> time60:variableparent     8.250      1.573   5.244 1.99e-05 *** +#> time90:variableparent     4.650      1.573   2.956 0.006717 **  +#> time120:variableparent    2.700      1.573   1.716 0.098507 .   +#> time0:variableM1             NA         NA      NA       NA     +#> time1:variableM1         11.850      1.573   7.532 6.93e-08 *** +#> time3:variableM1         22.700      1.573  14.428 1.26e-13 *** +#> time7:variableM1         33.050      1.573  21.007  < 2e-16 *** +#> time14:variableM1        31.250      1.573  19.863  < 2e-16 *** +#> time28:variableM1        18.900      1.573  12.013 7.02e-12 *** +#> time60:variableM1         7.550      1.573   4.799 6.28e-05 *** +#> time90:variableM1         3.850      1.573   2.447 0.021772 *   +#> time120:variableM1        2.050      1.573   1.303 0.204454     +#> time0:variableM2             NA         NA      NA       NA     +#> time1:variableM2          6.700      1.573   4.259 0.000254 *** +#> time3:variableM2         16.750      1.573  10.646 8.93e-11 *** +#> time7:variableM2         25.800      1.573  16.399 6.89e-15 *** +#> time14:variableM2        28.600      1.573  18.178 6.35e-16 *** +#> time28:variableM2        25.400      1.573  16.144 9.85e-15 *** +#> time60:variableM2        21.600      1.573  13.729 3.81e-13 *** +#> time90:variableM2        17.800      1.573  11.314 2.51e-11 *** +#> time120:variableM2       14.100      1.573   8.962 2.79e-09 *** +#> --- +#> Signif. codes:  0 ‘***’ 0.001 ‘**’ 0.01 ‘*’ 0.05 ‘.’ 0.1 ‘ ’ 1 +#>  +#> Residual standard error: 2.225 on 25 degrees of freedom +#> Multiple R-squared:  0.9979,	Adjusted R-squared:  0.9957  +#> F-statistic: 469.2 on 25 and 25 DF,  p-value: < 2.2e-16 +#> </div><div class='input'># } +</div></pre> +  </div> +  <div class="col-md-3 hidden-xs hidden-sm" id="sidebar"> +    <h2>Contents</h2> +    <ul class="nav nav-pills nav-stacked"> +      <li><a href="#arguments">Arguments</a></li> +      <li><a href="#details">Details</a></li> +      <li><a href="#see-also">See also</a></li> +      <li><a href="#examples">Examples</a></li> +    </ul> + +  </div> +</div> + + +      <footer> +      <div class="copyright"> +  <p>Developed by Johannes Ranke.</p> +</div> + +<div class="pkgdown"> +  <p>Site built with <a href="https://pkgdown.r-lib.org/">pkgdown</a> 1.4.1.</p> +</div> + +      </footer> +   </div> + +   + + +  </body> +</html> + + diff --git a/docs/reference/lrtest.mkinfit.html b/docs/reference/lrtest.mkinfit.html index 1d82eb74..70157db9 100644 --- a/docs/reference/lrtest.mkinfit.html +++ b/docs/reference/lrtest.mkinfit.html @@ -145,14 +145,18 @@ and can be expressed by fixing the parameters of the other.</p>      </div>      <pre class="usage"><span class='co'># S3 method for mkinfit</span> -<span class='fu'><a href='https://rdrr.io/pkg/lmtest/man/lrtest.html'>lrtest</a></span>(<span class='no'>object</span>, <span class='kw'>object_2</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='no'>...</span>)</pre> +<span class='fu'><a href='https://rdrr.io/pkg/lmtest/man/lrtest.html'>lrtest</a></span>(<span class='no'>object</span>, <span class='kw'>object_2</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='no'>...</span>) + +<span class='co'># S3 method for mmkin</span> +<span class='fu'><a href='https://rdrr.io/pkg/lmtest/man/lrtest.html'>lrtest</a></span>(<span class='no'>object</span>, <span class='no'>...</span>)</pre>      <h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2>      <table class="ref-arguments">      <colgroup><col class="name" /><col class="desc" /></colgroup>      <tr>        <th>object</th> -      <td><p>An <code><a href='mkinfit.html'>mkinfit</a></code> object</p></td> +      <td><p>An <code><a href='mkinfit.html'>mkinfit</a></code> object, or an <code><a href='mmkin.html'>mmkin</a></code> column +object containing two fits to the same data.</p></td>      </tr>      <tr>        <th>object_2</th> diff --git a/docs/reference/parms.html b/docs/reference/parms.html index e3c52c53..2162fdc0 100644 --- a/docs/reference/parms.html +++ b/docs/reference/parms.html @@ -71,7 +71,7 @@ considering the error structure that was assumed for the fit." />        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.8</span> +        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.9</span>        </span>      </div> diff --git a/docs/reference/plot.mmkin.html b/docs/reference/plot.mmkin.html index 8b68cfae..18907aa2 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." />        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.6</span> +        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.8</span>        </span>      </div> @@ -147,7 +147,7 @@ the fit of at least one model to the same dataset is shown.</p>  <span class='fu'><a href='https://rdrr.io/r/graphics/plot.html'>plot</a></span>(<span class='no'>x</span>, <span class='kw'>main</span> <span class='kw'>=</span> <span class='st'>"auto"</span>, <span class='kw'>legends</span> <span class='kw'>=</span> <span class='fl'>1</span>,    <span class='kw'>resplot</span> <span class='kw'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span>(<span class='st'>"time"</span>, <span class='st'>"errmod"</span>), <span class='kw'>show_errmin</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>,    <span class='kw'>errmin_var</span> <span class='kw'>=</span> <span class='st'>"All data"</span>, <span class='kw'>errmin_digits</span> <span class='kw'>=</span> <span class='fl'>3</span>, <span class='kw'>cex</span> <span class='kw'>=</span> <span class='fl'>0.7</span>, -  <span class='kw'>rel.height.middle</span> <span class='kw'>=</span> <span class='fl'>0.9</span>, <span class='no'>...</span>)</pre> +  <span class='kw'>rel.height.middle</span> <span class='kw'>=</span> <span class='fl'>0.9</span>, <span class='kw'>ymax</span> <span class='kw'>=</span> <span class='st'>"auto"</span>, <span class='no'>...</span>)</pre>      <h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2>      <table class="ref-arguments"> @@ -196,6 +196,10 @@ chi2 error percentage.</p></td>  than two rows of plots are shown.</p></td>      </tr>      <tr> +      <th>ymax</th> +      <td><p>Maximum y axis value for <code><a href='plot.mkinfit.html'>plot.mkinfit</a></code>.</p></td> +    </tr> +    <tr>        <th>...</th>        <td><p>Further arguments passed to <code><a href='plot.mkinfit.html'>plot.mkinfit</a></code> and  <code><a href='mkinresplot.html'>mkinresplot</a></code>.</p></td> diff --git a/docs/reference/sigma_twocomp.html b/docs/reference/sigma_twocomp.html index d95e1c28..1795e6c3 100644 --- a/docs/reference/sigma_twocomp.html +++ b/docs/reference/sigma_twocomp.html @@ -6,7 +6,7 @@  <meta http-equiv="X-UA-Compatible" content="IE=edge">  <meta name="viewport" content="width=device-width, initial-scale=1.0"> -<title>Two component error model — sigma_twocomp • mkin</title> +<title>Two-component error model — sigma_twocomp • mkin</title>  <!-- jquery --> @@ -35,7 +35,7 @@ -<meta property="og:title" content="Two component error model — sigma_twocomp" /> +<meta property="og:title" content="Two-component error model — sigma_twocomp" />  <meta property="og:description" content="Function describing the standard deviation of the measurement error in  dependence of the measured value \(y\):" />  <meta name="twitter:card" content="summary" /> @@ -70,7 +70,7 @@ dependence of the measured value \(y\):" />        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.6</span> +        <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.9.49.8</span>        </span>      </div> @@ -128,7 +128,7 @@ dependence of the measured value \(y\):" />  <div class="row">    <div class="col-md-9 contents">      <div class="page-header"> -    <h1>Two component error model</h1> +    <h1>Two-component error model</h1>      <div class="hidden name"><code>sigma_twocomp.Rd</code></div>      </div> diff --git a/docs/sitemap.xml b/docs/sitemap.xml index 3a56fe49..a8d6dfa4 100644 --- a/docs/sitemap.xml +++ b/docs/sitemap.xml @@ -55,6 +55,9 @@      <loc>https://pkgdown.jrwb.de/mkin/reference/add_err.html</loc>    </url>    <url> +    <loc>https://pkgdown.jrwb.de/mkin/reference/aw.html</loc> +  </url> +  <url>      <loc>https://pkgdown.jrwb.de/mkin/reference/confint.mkinfit.html</loc>    </url>    <url> @@ -67,6 +70,9 @@      <loc>https://pkgdown.jrwb.de/mkin/reference/ilr.html</loc>    </url>    <url> +    <loc>https://pkgdown.jrwb.de/mkin/reference/loftest.html</loc> +  </url> +  <url>      <loc>https://pkgdown.jrwb.de/mkin/reference/logLik.mkinfit.html</loc>    </url>    <url> diff --git a/man/aw.Rd b/man/aw.Rd new file mode 100644 index 00000000..40676716 --- /dev/null +++ b/man/aw.Rd @@ -0,0 +1,47 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/aw.R +\name{aw} +\alias{aw} +\alias{aw.mkinfit} +\alias{aw.mmkin} +\title{Calculate Akaike weights for model averaging} +\usage{ +aw(object, ...) + +\method{aw}{mkinfit}(object, ...) + +\method{aw}{mmkin}(object, ...) +} +\arguments{ +\item{object}{An \link{mmkin} column object, containing two or more +\link{mkinfit} models that have been fitted to the same data, +or an mkinfit object. In the latter case, further mkinfit +objects fitted to the same data should be specified +as dots arguments.} + +\item{\dots}{Not used in the method for \link{mmkin} column objects, +further \link{mkinfit} objects in the method for mkinfit objects.} +} +\description{ +Akaike weights are calculated based on the relative +expected Kullback-Leibler information as specified +by Burnham and Anderson (2004). +} +\examples{ +\dontrun{ +f_sfo <- mkinfit("SFO", FOCUS_2006_D, quiet = TRUE) +f_dfop <- mkinfit("DFOP", FOCUS_2006_D, quiet = TRUE) +aw_sfo_dfop <- aw(f_sfo, f_dfop) +sum(aw_sfo_dfop) +aw_sfo_dfop # SFO gets more weight as it has less parameters and a similar fit +f <- mmkin(c("SFO", "FOMC", "DFOP"), list("FOCUS D" = FOCUS_2006_D), cores = 1, quiet = TRUE) +aw(f) +sum(aw(f)) +aw(f[c("SFO", "DFOP")]) +} +} +\references{ +Burnham KP and Anderson DR (2004) Multimodel +Inference: Understanding AIC and BIC in Model Selection. +\emph{Sociological Methods & Research} \strong{33}(2) 261-304 +} diff --git a/man/loftest.Rd b/man/loftest.Rd new file mode 100644 index 00000000..397b5c08 --- /dev/null +++ b/man/loftest.Rd @@ -0,0 +1,81 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/loftest.R +\name{loftest} +\alias{loftest} +\alias{loftest.mkinfit} +\title{Lack-of-fit test for models fitted to data with replicates} +\usage{ +loftest(object, ...) + +\method{loftest}{mkinfit}(object, ...) +} +\arguments{ +\item{object}{A model object with a defined loftest method} + +\item{\dots}{Not used} +} +\description{ +This is a generic function with a method currently only defined for mkinfit +objects. It fits an anova model to the data contained in the object and +compares the likelihoods using the likelihood ratio test +\code{\link[lmtest]{lrtest.default}} from the lmtest package. +} +\details{ +The anova model is interpreted as the simplest form of an mkinfit model, +assuming only a constant variance about the means, but not enforcing any +structure of the means, so we have one model parameter for every mean +of replicate samples. +} +\examples{ +\dontrun{ +test_data <- subset(synthetic_data_for_UBA_2014[[12]]$data, name == "parent") +sfo_fit <- mkinfit("SFO", test_data, quiet = TRUE) +plot_res(sfo_fit) # We see a clear pattern in the residuals +loftest(sfo_fit)  # We have a clear lack of fit +# +# We try a different model (the one that was used to generate the data) +dfop_fit <- mkinfit("DFOP", test_data, quiet = TRUE) +plot_res(dfop_fit) # We don't see systematic deviations, but heteroscedastic residuals +# therefore we should consider adapting the error model, although we have +loftest(dfop_fit) # no lack of fit +# +# This is the anova model used internally for the comparison +test_data_anova <- test_data +test_data_anova$time <- as.factor(test_data_anova$time) +anova_fit <- lm(value ~ time, data = test_data_anova) +summary(anova_fit) +logLik(anova_fit) # We get the same likelihood and degrees of freedom +# +test_data_2 <- synthetic_data_for_UBA_2014[[12]]$data +m_synth_SFO_lin <- mkinmod(parent = list(type = "SFO", to = "M1"), +  M1 = list(type = "SFO", to = "M2"), +  M2 = list(type = "SFO"), use_of_ff = "max") +sfo_lin_fit <- mkinfit(m_synth_SFO_lin, test_data_2, quiet = TRUE) +plot_res(sfo_lin_fit) # not a good model, we try parallel formation +loftest(sfo_lin_fit) +# +m_synth_SFO_par <- mkinmod(parent = list(type = "SFO", to = c("M1", "M2")), +  M1 = list(type = "SFO"), +  M2 = list(type = "SFO"), use_of_ff = "max") +sfo_par_fit <- mkinfit(m_synth_SFO_par, test_data_2, quiet = TRUE) +plot_res(sfo_par_fit) # much better for metabolites +loftest(sfo_par_fit) +# +m_synth_DFOP_par <- mkinmod(parent = list(type = "DFOP", to = c("M1", "M2")), +  M1 = list(type = "SFO"), +  M2 = list(type = "SFO"), use_of_ff = "max") +dfop_par_fit <- mkinfit(m_synth_DFOP_par, test_data_2, quiet = TRUE) +plot_res(dfop_par_fit) # No visual lack of fit +loftest(dfop_par_fit)  # no lack of fit found by the test +# +# The anova model used for comparison in the case of transformation products +test_data_anova_2 <- dfop_par_fit$data +test_data_anova_2$variable <- as.factor(test_data_anova_2$variable) +test_data_anova_2$time <- as.factor(test_data_anova_2$time) +anova_fit_2 <- lm(observed ~ time:variable - 1, data = test_data_anova_2) +summary(anova_fit_2) +} +} +\seealso{ +lrtest +} diff --git a/man/lrtest.mkinfit.Rd b/man/lrtest.mkinfit.Rd index bc8ab4dc..84d7bc99 100644 --- a/man/lrtest.mkinfit.Rd +++ b/man/lrtest.mkinfit.Rd @@ -2,12 +2,16 @@  % Please edit documentation in R/lrtest.mkinfit.R  \name{lrtest.mkinfit}  \alias{lrtest.mkinfit} +\alias{lrtest.mmkin}  \title{Likelihood ratio test for mkinfit models}  \usage{  \method{lrtest}{mkinfit}(object, object_2 = NULL, ...) + +\method{lrtest}{mmkin}(object, ...)  }  \arguments{ -\item{object}{An \code{\link{mkinfit}} object} +\item{object}{An \code{\link{mkinfit}} object, or an \code{\link{mmkin}} column +object containing two fits to the same data.}  \item{object_2}{Optionally, another mkinfit object fitted to the same data.} diff --git a/man/plot.mmkin.Rd b/man/plot.mmkin.Rd index 333998da..605e458e 100644 --- a/man/plot.mmkin.Rd +++ b/man/plot.mmkin.Rd @@ -8,7 +8,7 @@ of an mmkin object}  \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, ...) +  rel.height.middle = 0.9, ymax = "auto", ...)  }  \arguments{  \item{x}{An object of class \code{\link{mmkin}}, with either one row or one @@ -36,6 +36,8 @@ chi2 error percentage.}  \item{rel.height.middle}{The relative height of the middle plot, if more  than two rows of plots are shown.} +\item{ymax}{Maximum y axis value for \code{\link{plot.mkinfit}}.} +  \item{\dots}{Further arguments passed to \code{\link{plot.mkinfit}} and  \code{\link{mkinresplot}}.}  } diff --git a/man/sigma_twocomp.Rd b/man/sigma_twocomp.Rd index 3e7854f1..0004144f 100644 --- a/man/sigma_twocomp.Rd +++ b/man/sigma_twocomp.Rd @@ -2,7 +2,7 @@  % Please edit documentation in R/sigma_twocomp.R  \name{sigma_twocomp}  \alias{sigma_twocomp} -\title{Two component error model} +\title{Two-component error model}  \usage{  sigma_twocomp(y, sigma_low, rsd_high)  } @@ -1,9 +1,10 @@  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.5 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] @@ -12,7 +13,7 @@ Testing mkin  ✔ |  12       | Special cases of mkinfit calls [2.4 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.0 s] +✔ |  16       | Evaluations according to 2015 NAFTA guidance [4.1 s]  ✔ |   4       | Calculation of maximum time weighted average concentrations (TWAs) [2.3 s]  ✔ |   3       | Summary  ✔ |  11       | Plotting [0.6 s] @@ -21,13 +22,17 @@ Testing mkin  ✔ |   2       | Complex test case from Schaefer et al. (2007) Piacenza paper [5.3 s]  ✔ |   4       | Fitting the SFORB model [1.7 s]  ✔ |   1       | Summaries of old mkinfit objects -✔ |   4       | Results for synthetic data established in expertise for UBA (Ranke 2014) [7.1 s] -✔ |   6       | Hypothesis tests [31.2 s] +✔ |   4       | Results for synthetic data established in expertise for UBA (Ranke 2014) [7.2 s] +✔ |   7     1 | Hypothesis tests [32.3 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: 108.3 s +Duration: 110.2 s -OK:       132 +OK:       138  Failed:   0  Warnings: 0 -Skipped:  0 +Skipped:  1 diff --git a/tests/testthat/FOCUS_2006_D.csf b/tests/testthat/FOCUS_2006_D.csf index 528e2b61..358b50e3 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-05 +Date: 2019-11-13  Optimiser: IRLS  [Data] diff --git a/tests/testthat/setup_script.R b/tests/testthat/setup_script.R index 9becdd2a..e33f4af7 100644 --- a/tests/testthat/setup_script.R +++ b/tests/testthat/setup_script.R @@ -32,9 +32,6 @@ f_1_mkin_trans <- mkinfit("SFO", FOCUS_2006_A, quiet = TRUE)  f_1_mkin_notrans <- mkinfit("SFO", FOCUS_2006_A, quiet = TRUE,    transform_rates = FALSE) -f_2_mkin <- mkinfit("DFOP", FOCUS_2006_C, quiet = TRUE) -f_2_nls <- nls(value ~ SSbiexp(time, A1, lrc1, A2, lrc2), data = FOCUS_2006_C) -  # mmkin object of parent fits for tests  models <- c("SFO", "FOMC", "DFOP", "HS")  fits <- mmkin(models, @@ -62,11 +59,14 @@ f_sfo_sfo.ff <- mkinfit(SFO_SFO.ff,    subset(FOCUS_2006_D, value != 0),    quiet = TRUE) -# Two metabolites  SFO_lin_a <- synthetic_data_for_UBA_2014[[1]]$data -  DFOP_par_c <- synthetic_data_for_UBA_2014[[12]]$data +f_2_mkin <- mkinfit("DFOP", DFOP_par_c, quiet = TRUE) +f_2_nls <- nls(value ~ SSbiexp(time, A1, lrc1, A2, lrc2), data = subset(DFOP_par_c, name == "parent")) +f_2_anova <- lm(value ~ as.factor(time), data = subset(DFOP_par_c, name == "parent")) + +# Two metabolites  m_synth_SFO_lin <- mkinmod(    parent = mkinsub("SFO", "M1"),    M1 = mkinsub("SFO", "M2"), diff --git a/tests/testthat/test_SFORB.R b/tests/testthat/test_SFORB.R index 49b3beed..bc9ab646 100644 --- a/tests/testthat/test_SFORB.R +++ b/tests/testthat/test_SFORB.R @@ -18,8 +18,6 @@  context("Fitting the SFORB model") -logistic <- mkinmod(parent = mkinsub("logistic")) -  test_that("Fitting the SFORB model is equivalent to fitting DFOP", {    f_sforb <- mkinfit("SFORB", FOCUS_2006_C, quiet = TRUE)    f_dfop <- mkinfit("DFOP", FOCUS_2006_C, quiet = TRUE) diff --git a/tests/testthat/test_aw.R b/tests/testthat/test_aw.R new file mode 100644 index 00000000..0a493893 --- /dev/null +++ b/tests/testthat/test_aw.R @@ -0,0 +1,12 @@ +context("Calculation of Akaike weights") + +test_that("Akaike weights sum to one", { +  skip_on_cran() +  aw_1 <- aw(fit_nw_1, fit_obs_1, fit_tc_1) +  expect_error(aw(fit_nw_1, f_2_mkin), "same data") +  expect_error(aw(fit_nw_1, 3), "mkinfit objects") +  expect_equal(sum(aw_1), 1) +  aw_2 <- aw(fits[c("SFO", "DFOP"), "FOCUS_D"]) +  expect_equal(sum(aw_2), 1) +  expect_error(aw(fits), "mmkin column object") +}) diff --git a/tests/testthat/test_confidence.R b/tests/testthat/test_confidence.R index a2bf1401..e85fdb7a 100644 --- a/tests/testthat/test_confidence.R +++ b/tests/testthat/test_confidence.R @@ -54,11 +54,12 @@ test_that("Quadratic confidence intervals for rate constants are comparable to v    # Another case:    se_mkin_2 <- summary(f_2_mkin)$par[1:4, "Std. Error"]    se_nls_2 <- summary(f_2_nls)$coefficients[, "Std. Error"] -  # Here we the ratio of standard errors can be explained by the same +  # Here the ratio of standard errors can be explained by the same    # principle up to about 3% +  nobs_DFOP_par_c_parent <- nrow(subset(DFOP_par_c, name == "parent"))    expect_equivalent(      se_nls_2[c("lrc1", "lrc2")] / se_mkin_2[c("log_k1", "log_k2")], -    rep(sqrt(nrow(FOCUS_2006_C) / (nrow(FOCUS_2006_C) - 4)), 2), +    rep(sqrt(nobs_DFOP_par_c_parent / (nobs_DFOP_par_c_parent - 4)), 2),      tolerance = 0.03)  }) @@ -73,7 +74,7 @@ test_that("Likelihood profile based confidence intervals work", {     }     f_mle <- stats4::mle(f_nll, start = as.list(parms(f)), nobs = nrow(FOCUS_2006_C)) -   ci_mkin_1_p_0.95 <- confint(f, method = "profile", level = 0.95,  +   ci_mkin_1_p_0.95 <- confint(f, method = "profile", level = 0.95,       cores = n_cores, quiet = TRUE)     # Magically, we get very similar boundaries as stats4::mle diff --git a/tests/testthat/test_tests.R b/tests/testthat/test_tests.R index 5a522f8e..ddf8e1a0 100644 --- a/tests/testthat/test_tests.R +++ b/tests/testthat/test_tests.R @@ -1,5 +1,21 @@  context("Hypothesis tests") +test_that("The lack-of-fit test works and can be reproduced using nls", { + +  expect_error(loftest(f_1_mkin_trans), "Not defined for fits to data without replicates") + +  loftest_mkin <- loftest(f_2_mkin) + +  # This code is a slightly modified version of that given in Ritz and Streibig +  # (2008) Nonlinear Regression using R, p. 64 +  Q <- as.numeric(- 2 * (logLik(f_2_nls) -  logLik(f_2_anova))) +  df.Q <- df.residual(f_2_nls) - df.residual(f_2_anova) +  p_nls <- 1 - pchisq(Q, df.Q) + +  expect_equal(loftest_mkin[["2", "Pr(>Chisq)"]], p_nls, tolerance = 1e-5) + +}) +  test_that("The likelihood ratio test works", {    expect_error(lrtest(f_1_mkin_trans, f_2_mkin), "not been fitted to the same data") @@ -25,7 +41,7 @@ test_that("Updating fitted models works", {      parent = mkinsub("DFOP", to = "A1"),      A1 = mkinsub("SFO", to = "A2"),      A2 = mkinsub("SFO"), -    use_of_ff = "max" +    use_of_ff = "max", quiet = TRUE    )    f_soil_1_tc <- mkinfit(dfop_sfo_sfo, @@ -41,6 +57,9 @@ test_that("Updating fitted models works", {  })  test_that("We can do a likelihood ratio test using an update specification", { +  skip("This errors out if called by testthat while it works in a normal R session")    test_2_mkin_k2 <- lrtest(f_2_mkin, fixed_parms = c(k2 = 0)) -  expect_equivalent(test_2_mkin_k2[["2", "Pr(>Chisq)"]], 1.139e-6, tolerance = 1e-8) +  expect_equivalent(test_2_mkin_k2[["2", "Pr(>Chisq)"]], 4.851e-8, tolerance = 1e-8) +  test_2_mkin_tc <- lrtest(f_2_mkin, error_model = "tc") +  expect_equivalent(test_2_mkin_tc[["2", "Pr(>Chisq)"]], 7.302e-5, tolerance = 1e-7)  }) | 
