diff options
| -rw-r--r-- | NAMESPACE | 4 | ||||
| -rw-r--r-- | NEWS.md | 2 | ||||
| -rw-r--r-- | R/memkin.R | 170 | ||||
| -rw-r--r-- | R/mkinsub.R | 11 | ||||
| -rw-r--r-- | R/nlme.R | 213 | ||||
| -rw-r--r-- | check.log | 71 | ||||
| -rw-r--r-- | man/memkin.Rd | 84 | ||||
| -rw-r--r-- | man/mkinsub.Rd | 11 | ||||
| -rw-r--r-- | man/nlme.Rd | 134 | ||||
| -rw-r--r-- | vignettes/web_only/FOCUS_Z.R | 115 | ||||
| -rw-r--r-- | vignettes/web_only/compiled_models.R | 61 | 
11 files changed, 368 insertions, 508 deletions
| @@ -45,7 +45,7 @@ export(max_twa_fomc)  export(max_twa_hs)  export(max_twa_parent)  export(max_twa_sfo) -export(memkin) +export(mean_degparms)  export(mkin_long_to_wide)  export(mkin_wide_to_long)  export(mkinds) @@ -60,6 +60,8 @@ export(mkinresplot)  export(mkinsub)  export(mmkin)  export(nafta) +export(nlme_data) +export(nlme_function)  export(parms)  export(plot_err)  export(plot_res) @@ -1,5 +1,7 @@  # mkin 0.9.49.10 (unreleased) +- 'mean_degparms, nlme_data, nlme_function': Three new functions to facilitate building nlme models from mmkin row objects +  - 'endpoints': Don't return the SFORB list component if it's empty. This reduces distraction and complies with the documentation  - Article in compiled models: Add some platform specific code and suppress warnings about zero values being removed from the FOCUS D dataset diff --git a/R/memkin.R b/R/memkin.R deleted file mode 100644 index 8a71484e..00000000 --- a/R/memkin.R +++ /dev/null @@ -1,170 +0,0 @@ -#' Estimation of parameter distributions from mmkin row objects -#' -#' This function sets up and attempts to fit a mixed effects model to -#' an mmkin row object which is essentially a list of mkinfit objects -#' that have been obtained by fitting the same model to a list of -#' datasets. -#' -#' @param object An mmkin row object containing several fits of the same model to different datasets -#' @param random_spec Either "auto" or a specification of random effects for \code{\link{nlme}} -#'   given as a character vector -#' @param ... Additional arguments passed to \code{\link{nlme}} -#' @import nlme -#' @importFrom purrr map_dfr -#' @return An nlme object -#' @examples -#' sampling_times = c(0, 1, 3, 7, 14, 28, 60, 90, 120) -#' m_SFO <- mkinmod(parent = mkinsub("SFO")) -#' d_SFO_1 <- mkinpredict(m_SFO, -#'   c(k_parent_sink = 0.1), -#'   c(parent = 98), sampling_times) -#' d_SFO_1_long <- mkin_wide_to_long(d_SFO_1, time = "time") -#' d_SFO_2 <- mkinpredict(m_SFO, -#'   c(k_parent_sink = 0.05), -#'   c(parent = 102), sampling_times) -#' d_SFO_2_long <- mkin_wide_to_long(d_SFO_2, time = "time") -#' d_SFO_3 <- mkinpredict(m_SFO, -#'   c(k_parent_sink = 0.02), -#'   c(parent = 103), sampling_times) -#' d_SFO_3_long <- mkin_wide_to_long(d_SFO_3, time = "time") -#' -#' d1 <- add_err(d_SFO_1, function(value) 3, n = 1) -#' d2 <- add_err(d_SFO_2, function(value) 2, n = 1) -#' d3 <- add_err(d_SFO_3, function(value) 4, n = 1) -#' ds <- c(d1 = d1, d2 = d2, d3 = d3) -#' -#' f <- mmkin("SFO", ds) -#' x <- memkin(f) -#' summary(x) -#' -#' ds_2 <- lapply(experimental_data_for_UBA_2019[6:10], -#'  function(x) x$data[c("name", "time", "value")]) -#' m_sfo_sfo <- mkinmod(parent = mkinsub("SFO", "A1"), -#'   A1 = mkinsub("SFO"), use_of_ff = "min") -#' m_sfo_sfo_ff <- mkinmod(parent = mkinsub("SFO", "A1"), -#'   A1 = mkinsub("SFO"), use_of_ff = "max") -#' m_fomc_sfo <- mkinmod(parent = mkinsub("FOMC", "A1"), -#'   A1 = mkinsub("SFO")) -#' m_dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "A1"), -#'   A1 = mkinsub("SFO")) -#' m_sforb_sfo <- mkinmod(parent = mkinsub("SFORB", "A1"), -#'   A1 = mkinsub("SFO")) -#' -#' f_2 <- mmkin(list("SFO-SFO" = m_sfo_sfo, -#'  "SFO-SFO-ff" = m_sfo_sfo_ff, -#'  "FOMC-SFO" = m_fomc_sfo, -#'  "DFOP-SFO" = m_dfop_sfo, -#'  "SFORB-SFO" = m_sforb_sfo), -#'   ds_2) -#' -#' f_nlme_sfo_sfo <- memkin(f_2[1, ]) -#' f_nlme_sfo_sfo_2 <- memkin(f_2[1, ], "pdDiag(parent_0 + log_k_parent_sink + log_k_parent_A1 + log_k_A1_sink ~ 1)") # explicit -#' f_nlme_sfo_sfo_3 <- memkin(f_2[1, ], "pdDiag(parent_0 + log_k_parent_sink + log_k_parent_A1 ~ 1)") # reduced -#' f_nlme_sfo_sfo_4 <- memkin(f_2[1, ], "pdDiag(parent_0 + log_k_parent_sink ~ 1)") # further reduced -#' \dontrun{ -#'   f_nlme_sfo_sfo_ff <- memkin(f_2[2, ]) # does not converge with maxIter = 50 -#' } -#' f_nlme_fomc_sfo <- memkin(f_2[3, ]) -#' \dontrun{ -#'   f_nlme_dfop_sfo <- memkin(f_2[4, ])  # apparently underdetermined -#'   f_nlme_sforb_sfo <- memkin(f_2[5, ]) # also does not converge -#' } -#' anova(f_nlme_fomc_sfo, f_nlme_sfo_sfo, f_nlme_sfo_sfo_4) -#' @export -memkin <- function(object, random_spec = "auto", ...) { -  if (nrow(object) > 1) stop("Only row objects allowed") -  ds_names <- colnames(object) - -  p_mat_start_trans <- sapply(object, parms, transformed = TRUE) -  colnames(p_mat_start_trans) <- ds_names - -  p_names_mean_function <- setdiff(rownames(p_mat_start_trans), names(object[[1]]$errparms)) -  p_start_mean_function <- apply(p_mat_start_trans[p_names_mean_function, ], 1, mean) - -  ds_list <- lapply(object, function(x) x$data[c("time", "variable", "observed")]) -  names(ds_list) <- ds_names -  ds_nlme <- purrr::map_dfr(ds_list, function(x) x, .id = "ds") -  ds_nlme$variable <- as.character(ds_nlme$variable) -  ds_nlme_grouped <- groupedData(observed ~ time | ds, ds_nlme) - -  mkin_model <- object[[1]]$mkinmod - -  # Inspired by https://stackoverflow.com/a/12983961/3805440 -  # and https://stackoverflow.com/a/26280789/3805440 -  model_function_alist <- replicate(length(p_names_mean_function) + 2, substitute()) -  names(model_function_alist) <- c("name", "time", p_names_mean_function) - -  model_function_body <- quote({ -    arg_frame <- as.data.frame(as.list((environment())), stringsAsFactors = FALSE) -    res_frame <- arg_frame[1:2] -    parm_frame <- arg_frame[-(1:2)] -    parms_unique <- unique(parm_frame) - -    n_unique <- nrow(parms_unique) - -    times_ds <- list() -    names_ds <- list() -    for (i in 1:n_unique) { -      times_ds[[i]] <- -        arg_frame[which(arg_frame[[3]] == parms_unique[i, 1]), "time"] -      names_ds[[i]] <- -        arg_frame[which(arg_frame[[3]] == parms_unique[i, 1]), "name"] -    } - -    res_list <- lapply(1:n_unique, function(x) { -      transparms_optim <- unlist(parms_unique[x, , drop = TRUE]) -      parms_fixed <- object[[1]]$bparms.fixed - -      odeini_optim_parm_names <- grep('_0$', names(transparms_optim), value = TRUE) -      odeini_optim <- transparms_optim[odeini_optim_parm_names] -      names(odeini_optim) <- gsub('_0$', '', odeini_optim_parm_names) -      odeini_fixed_parm_names <- grep('_0$', names(parms_fixed), value = TRUE) -      odeini_fixed <- parms_fixed[odeini_fixed_parm_names] -      names(odeini_fixed) <- gsub('_0$', '', odeini_fixed_parm_names) -      odeini <- c(odeini_optim, odeini_fixed)[names(mkin_model$diffs)] - -      ode_transparms_optim_names <- setdiff(names(transparms_optim), odeini_optim_parm_names) -      odeparms_optim <- backtransform_odeparms(transparms_optim[ode_transparms_optim_names], mkin_model, -        transform_rates = object[[1]]$transform_rates, -        transform_fractions = object[[1]]$transform_fractions) -      odeparms_fixed_names <- setdiff(names(parms_fixed), odeini_fixed_parm_names) -      odeparms_fixed <- parms_fixed[odeparms_fixed_names] -      odeparms <- c(odeparms_optim, odeparms_fixed) - -      out_wide <- mkinpredict(mkin_model, -        odeparms = odeparms, odeini = odeini, -        solution_type = object[[1]]$solution_type, -        outtimes = sort(unique(times_ds[[x]]))) -      out_array <- out_wide[, -1, drop = FALSE] -      rownames(out_array) <- as.character(unique(times_ds[[x]])) -      out_times <- as.character(times_ds[[x]]) -      out_names <- as.character(names_ds[[x]]) -      out_values <- mapply(function(times, names) out_array[times, names], -        out_times, out_names) -      return(as.numeric(out_values)) -    }) -    res <- unlist(res_list) -    return(res) -  }) -  model_function <- as.function(c(model_function_alist, model_function_body)) -  # For some reason, using envir = parent.frame() here is not enough, -  # we need to use assign -  assign("model_function", model_function, envir = parent.frame()) - -  random_spec <- if (random_spec[1] == "auto") { -      paste0("pdDiag(", paste(p_names_mean_function, collapse = " + "), " ~ 1),\n") -  } else { -      paste0(random_spec, ",\n") -  } -  nlme_call_text <- paste0( -    "nlme(observed ~ model_function(variable, time, ", -      paste(p_names_mean_function, collapse = ", "), "),\n", -    "  data = ds_nlme_grouped,\n", -    "  fixed = ", paste(p_names_mean_function, collapse = " + "), " ~ 1,\n", -    "  random = ", random_spec, "\n", -    "  start = p_start_mean_function)\n") - -  f_nlme <- eval(parse(text = nlme_call_text)) - -  return(f_nlme) -} diff --git a/R/mkinsub.R b/R/mkinsub.R index db91ca00..f87c230a 100644 --- a/R/mkinsub.R +++ b/R/mkinsub.R @@ -27,11 +27,12 @@  #'   parent = mkinsub("SFO", "m1"),  #'   m1 = mkinsub("SFO"))  #'  -#' # Now supplying full names -#' SFO_SFO.2 <- mkinmod( -#'   parent = mkinsub("SFO", "m1", full_name = "Test compound"), -#'   m1 = mkinsub("SFO", full_name = "Metabolite M1")) -#'  +#' \dontrun{ +#'   # Now supplying full names +#'   SFO_SFO.2 <- mkinmod( +#'     parent = mkinsub("SFO", "m1", full_name = "Test compound"), +#'     m1 = mkinsub("SFO", full_name = "Metabolite M1")) +#'  }  #' @export  mkinsub <- function(submodel, to = NULL, sink = TRUE, full_name = NA)  { diff --git a/R/nlme.R b/R/nlme.R new file mode 100644 index 00000000..b17fe15a --- /dev/null +++ b/R/nlme.R @@ -0,0 +1,213 @@ +#' Estimation of parameter distributions from mmkin row objects +#' +#' This function sets up and attempts to fit a mixed effects model to +#' an mmkin row object. An mmkin row object is essentially a list of mkinfit +#' objects that have been obtained by fitting the same model to a list of +#' datasets. +#' +#' @param object An mmkin row object containing several fits of the same model to different datasets +#' @import nlme +#' @importFrom purrr map_dfr +#' @return A named vector containing mean values of the fitted degradation model parameters +#' @rdname nlme +#' @examples +#' sampling_times = c(0, 1, 3, 7, 14, 28, 60, 90, 120) +#' m_SFO <- mkinmod(parent = mkinsub("SFO")) +#' d_SFO_1 <- mkinpredict(m_SFO, +#'   c(k_parent_sink = 0.1), +#'   c(parent = 98), sampling_times) +#' d_SFO_1_long <- mkin_wide_to_long(d_SFO_1, time = "time") +#' d_SFO_2 <- mkinpredict(m_SFO, +#'   c(k_parent_sink = 0.05), +#'   c(parent = 102), sampling_times) +#' d_SFO_2_long <- mkin_wide_to_long(d_SFO_2, time = "time") +#' d_SFO_3 <- mkinpredict(m_SFO, +#'   c(k_parent_sink = 0.02), +#'   c(parent = 103), sampling_times) +#' d_SFO_3_long <- mkin_wide_to_long(d_SFO_3, time = "time") +#' +#' d1 <- add_err(d_SFO_1, function(value) 3, n = 1) +#' d2 <- add_err(d_SFO_2, function(value) 2, n = 1) +#' d3 <- add_err(d_SFO_3, function(value) 4, n = 1) +#' ds <- c(d1 = d1, d2 = d2, d3 = d3) +#' +#' f <- mmkin("SFO", ds, cores = 1, quiet = TRUE) +#' mean_dp <- mean_degparms(f) +#' grouped_data <- nlme_data(f) +#' nlme_f <- nlme_function(f) +#' +#' library(nlme) +#' m_nlme <- nlme(value ~ nlme_f(name, time, parent_0, log_k_parent_sink), +#'   data = grouped_data, +#'   fixed = parent_0 + log_k_parent_sink ~ 1, +#'   random = pdDiag(parent_0 + log_k_parent_sink ~ 1), +#'   start = mean_dp) +#' summary(m_nlme) +#' +#' \dontrun{ +#'   Test on some real data +#'   ds_2 <- lapply(experimental_data_for_UBA_2019[6:10], +#'    function(x) x$data[c("name", "time", "value")]) +#'   m_sfo_sfo <- mkinmod(parent = mkinsub("SFO", "A1"), +#'     A1 = mkinsub("SFO"), use_of_ff = "min") +#'   m_sfo_sfo_ff <- mkinmod(parent = mkinsub("SFO", "A1"), +#'     A1 = mkinsub("SFO"), use_of_ff = "max") +#'   m_fomc_sfo <- mkinmod(parent = mkinsub("FOMC", "A1"), +#'     A1 = mkinsub("SFO")) +#'   m_dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "A1"), +#'     A1 = mkinsub("SFO")) +#'   m_sforb_sfo <- mkinmod(parent = mkinsub("SFORB", "A1"), +#'     A1 = mkinsub("SFO")) +#' +#'   f_2 <- mmkin(list("SFO-SFO" = m_sfo_sfo, +#'    "SFO-SFO-ff" = m_sfo_sfo_ff, +#'    "FOMC-SFO" = m_fomc_sfo, +#'    "DFOP-SFO" = m_dfop_sfo, +#'    "SFORB-SFO" = m_sforb_sfo), +#'     ds_2) +#' +#'   grouped_data_2 <- nlme_data(f_2["SFO-SFO", ]) +#' +#'   mean_dp_sfo_sfo <- mean_degparms(f_2["SFO-SFO", ]) +#'   mean_dp_sfo_sfo_ff <- mean_degparms(f_2["SFO-SFO-ff", ]) +#'   mean_dp_fomc_sfo <- mean_degparms(f_2["FOMC-SFO", ]) +#'   mean_dp_dfop_sfo <- mean_degparms(f_2["DFOP-SFO", ]) +#'   mean_dp_sforb_sfo <- mean_degparms(f_2["SFORB-SFO", ]) +#' +#'   nlme_f_sfo_sfo <- nlme_function(f_2["SFO-SFO", ]) +#'   nlme_f_sfo_sfo_ff <- nlme_function(f_2["SFO-SFO-ff", ]) +#'   nlme_f_fomc_sfo <- nlme_function(f_2["FOMC-SFO", ]) +#' +#'   # Allowing for correlations between random effects leads to non-convergence +#'   f_nlme_sfo_sfo <- nlme(value ~ nlme_f_sfo_sfo(name, time, +#'        parent_0, log_k_parent_sink, log_k_parent_A1, log_k_A1_sink), +#'      data = grouped_data_2, +#'      fixed = parent_0 + log_k_parent_sink + log_k_parent_A1 + log_k_A1_sink ~ 1, +#'      random = pdDiag(parent_0 + log_k_parent_sink + log_k_parent_A1 + log_k_A1_sink ~ 1), +#'      start = mean_dp_sfo_sfo) +#' +#'   # The same model fitted with transformed formation fractions does not converge +#'   f_nlme_sfo_sfo_ff <- nlme(value ~ nlme_f_sfo_sfo_ff(name, time, +#'        parent_0, log_k_parent, log_k_A1, f_parent_ilr_1), +#'      data = grouped_data_2, +#'      fixed = parent_0 + log_k_parent + log_k_A1 + f_parent_ilr_1 ~ 1, +#'      random = pdDiag(parent_0 + log_k_parent + log_k_A1 + f_parent_ilr_1 ~ 1), +#'      start = mean_dp_sfo_sfo_ff) +#' +#'   # It does converge with this version of reduced random effects +#'   f_nlme_sfo_sfo_ff <- nlme(value ~ nlme_f_sfo_sfo_ff(name, time, +#'        parent_0, log_k_parent, log_k_A1, f_parent_ilr_1), +#'      data = grouped_data_2, +#'      fixed = parent_0 + log_k_parent + log_k_A1 + f_parent_ilr_1 ~ 1, +#'      random = pdDiag(parent_0 + log_k_parent ~ 1), +#'      start = mean_dp_sfo_sfo_ff) +#' +#'   f_nlme_fomc_sfo <- nlme(value ~ nlme_f_fomc_sfo(name, time, +#'        parent_0, log_alpha, log_beta, log_k_A1, f_parent_ilr_1), +#'      data = grouped_data_2, +#'      fixed = parent_0 + log_alpha + log_beta + log_k_A1 + f_parent_ilr_1 ~ 1, +#'      random = pdDiag(parent_0 + log_alpha + log_beta + log_k_A1 + f_parent_ilr_1 ~ 1), +#'      start = mean_dp_fomc_sfo) +#' +#'   # DFOP-SFO and SFORB-SFO did not converge with full random effects +#' +#'   anova(f_nlme_fomc_sfo, f_nlme_sfo_sfo) +#' } +#' @export +mean_degparms <- function(object) { +  if (nrow(object) > 1) stop("Only row objects allowed") +  p_mat_start_trans <- sapply(object, parms, transformed = TRUE) +  mean_degparm_names <- setdiff(rownames(p_mat_start_trans), names(object[[1]]$errparms)) +  res <- apply(p_mat_start_trans[mean_degparm_names, ], 1, mean) +  return(res) +} + +#' @rdname nlme +#' @importFrom purrr map_dfr +#' @return A groupedData data object +#' @export +nlme_data <- function(object) { +  if (nrow(object) > 1) stop("Only row objects allowed") +  ds_names <- colnames(object) + +  ds_list <- lapply(object, function(x) x$data[c("time", "variable", "observed")]) +  names(ds_list) <- ds_names +  ds_nlme <- purrr::map_dfr(ds_list, function(x) x, .id = "ds") +  ds_nlme$variable <- as.character(ds_nlme$variable) +  ds_nlme_renamed <- data.frame(ds = ds_nlme$ds, name = ds_nlme$variable, +    time = ds_nlme$time, value = ds_nlme$observed, +    stringsAsFactors = FALSE) +  ds_nlme_grouped <- groupedData(value ~ time | ds, ds_nlme_renamed) +  return(ds_nlme_grouped) +} + +#' @rdname nlme +#' @return A function that can be used with nlme +#' @export +nlme_function <- function(object) { +  if (nrow(object) > 1) stop("Only row objects allowed") + +  mkin_model <- object[[1]]$mkinmod + +  degparm_names <- names(mean_degparms(object)) + +  # Inspired by https://stackoverflow.com/a/12983961/3805440 +  # and https://stackoverflow.com/a/26280789/3805440 +  model_function_alist <- replicate(length(degparm_names) + 2, substitute()) +  names(model_function_alist) <- c("name", "time", degparm_names) + +  model_function_body <- quote({ +    arg_frame <- as.data.frame(as.list((environment())), stringsAsFactors = FALSE) +    res_frame <- arg_frame[1:2] +    parm_frame <- arg_frame[-(1:2)] +    parms_unique <- unique(parm_frame) + +    n_unique <- nrow(parms_unique) + +    times_ds <- list() +    names_ds <- list() +    for (i in 1:n_unique) { +      times_ds[[i]] <- +        arg_frame[which(arg_frame[[3]] == parms_unique[i, 1]), "time"] +      names_ds[[i]] <- +        arg_frame[which(arg_frame[[3]] == parms_unique[i, 1]), "name"] +    } + +    res_list <- lapply(1:n_unique, function(x) { +      transparms_optim <- unlist(parms_unique[x, , drop = TRUE]) +      parms_fixed <- object[[1]]$bparms.fixed + +      odeini_optim_parm_names <- grep('_0$', names(transparms_optim), value = TRUE) +      odeini_optim <- transparms_optim[odeini_optim_parm_names] +      names(odeini_optim) <- gsub('_0$', '', odeini_optim_parm_names) +      odeini_fixed_parm_names <- grep('_0$', names(parms_fixed), value = TRUE) +      odeini_fixed <- parms_fixed[odeini_fixed_parm_names] +      names(odeini_fixed) <- gsub('_0$', '', odeini_fixed_parm_names) +      odeini <- c(odeini_optim, odeini_fixed)[names(mkin_model$diffs)] + +      ode_transparms_optim_names <- setdiff(names(transparms_optim), odeini_optim_parm_names) +      odeparms_optim <- backtransform_odeparms(transparms_optim[ode_transparms_optim_names], mkin_model, +        transform_rates = object[[1]]$transform_rates, +        transform_fractions = object[[1]]$transform_fractions) +      odeparms_fixed_names <- setdiff(names(parms_fixed), odeini_fixed_parm_names) +      odeparms_fixed <- parms_fixed[odeparms_fixed_names] +      odeparms <- c(odeparms_optim, odeparms_fixed) + +      out_wide <- mkinpredict(mkin_model, +        odeparms = odeparms, odeini = odeini, +        solution_type = object[[1]]$solution_type, +        outtimes = sort(unique(times_ds[[x]]))) +      out_array <- out_wide[, -1, drop = FALSE] +      rownames(out_array) <- as.character(unique(times_ds[[x]])) +      out_times <- as.character(times_ds[[x]]) +      out_names <- as.character(names_ds[[x]]) +      out_values <- mapply(function(times, names) out_array[times, names], +        out_times, out_names) +      return(as.numeric(out_values)) +    }) +    res <- unlist(res_list) +    return(res) +  }) +  model_function <- as.function(c(model_function_alist, model_function_body)) +  return(model_function) +} @@ -24,27 +24,7 @@ Maintainer: ‘Johannes Ranke <jranke@uni-bremen.de>’  * checking for future file timestamps ... OK  * checking ‘build’ directory ... OK  * checking DESCRIPTION meta-information ... OK -* checking top-level files ... WARNING -Conversion of ‘README.md’ failed: -[WARNING] This document format requires a nonempty <title> element. -  Please specify either ‘title’ or ‘pagetitle’ in the metadata. -  Falling back to ‘README’ -Could not fetch https://codecov.io/github/jranke/mkin/branch/master/graphs/badge.svg -HttpExceptionRequest Request { -  host                 = "codecov.io" -  port                 = 443 -  secure               = True -  requestHeaders       = [] -  path                 = "/github/jranke/mkin/branch/master/graphs/badge.svg" -  queryString          = "" -  method               = "GET" -  proxy                = Nothing -  rawBody              = False -  redirectCount        = 10 -  responseTimeout      = ResponseTimeoutDefault -  requestVersion       = HTTP/1.1 -} - ConnectionTimeout +* checking top-level files ... OK  * checking for left-over files ... OK  * checking index information ... OK  * checking package subdirectories ... OK @@ -64,13 +44,7 @@ HttpExceptionRequest Request {  * checking R code for possible problems ... OK  * checking Rd files ... OK  * checking Rd metadata ... OK -* checking Rd line widths ... NOTE -Rd file 'memkin.Rd': -  \examples lines wider than 100 characters: -     f_nlme_sfo_sfo_2 <- memkin(f_2[1, ], "pdDiag(parent_0 + log_k_parent_sink + log_k_parent_A1 + log_k_A1_sink ~ 1)") # explicit -     f_nlme_sfo_sfo_3 <- memkin(f_2[1, ], "pdDiag(parent_0 + log_k_parent_sink + log_k_parent_A1 ~ 1)") # reduced - -These lines will be truncated in the PDF manual. +* checking Rd line widths ... OK  * checking Rd cross-references ... OK  * checking for missing documentation entries ... OK  * checking for code/documentation mismatches ... OK @@ -82,41 +56,7 @@ These lines will be truncated in the PDF manual.  * checking data for ASCII and uncompressed saves ... OK  * checking installed files from ‘inst/doc’ ... OK  * checking files in ‘vignettes’ ... OK -* checking examples ... ERROR -Running examples in ‘mkin-Ex.R’ failed -The error most likely occurred in: - -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") -> ### Name: memkin -> ### Title: Estimation of parameter distributions from mmkin row objects -> ### Aliases: memkin ->  -> ### ** Examples ->  -> sampling_times = c(0, 1, 3, 7, 14, 28, 60, 90, 120) -> m_SFO <- mkinmod(parent = mkinsub("SFO")) -> d_SFO_1 <- mkinpredict(m_SFO, -+   c(k_parent_sink = 0.1), -+   c(parent = 98), sampling_times) -> d_SFO_1_long <- mkin_wide_to_long(d_SFO_1, time = "time") -> d_SFO_2 <- mkinpredict(m_SFO, -+   c(k_parent_sink = 0.05), -+   c(parent = 102), sampling_times) -> d_SFO_2_long <- mkin_wide_to_long(d_SFO_2, time = "time") -> d_SFO_3 <- mkinpredict(m_SFO, -+   c(k_parent_sink = 0.02), -+   c(parent = 103), sampling_times) -> d_SFO_3_long <- mkin_wide_to_long(d_SFO_3, time = "time") ->  -> d1 <- add_err(d_SFO_1, function(value) 3, n = 1) -> d2 <- add_err(d_SFO_2, function(value) 2, n = 1) -> d3 <- add_err(d_SFO_3, function(value) 4, n = 1) -> ds <- c(d1 = d1, d2 = d2, d3 = d3) ->  -> f <- mmkin("SFO", ds) -Error in .check_ncores(cores) : 8 simultaneous processes spawned -Calls: mmkin -> mclapply -> .check_ncores -Execution halted +* checking examples ... OK  * checking for unstated dependencies in ‘tests’ ... OK  * checking tests ... SKIPPED  * checking for unstated dependencies in vignettes ... OK @@ -126,8 +66,5 @@ Execution halted  * checking for detritus in the temp directory ... OK  * DONE -Status: 1 ERROR, 1 WARNING, 1 NOTE -See -  ‘/home/jranke/git/mkin/mkin.Rcheck/00check.log’ -for details. +Status: OK diff --git a/man/memkin.Rd b/man/memkin.Rd deleted file mode 100644 index 8ae6100a..00000000 --- a/man/memkin.Rd +++ /dev/null @@ -1,84 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/memkin.R -\name{memkin} -\alias{memkin} -\title{Estimation of parameter distributions from mmkin row objects} -\usage{ -memkin(object, random_spec = "auto", ...) -} -\arguments{ -\item{object}{An mmkin row object containing several fits of the same model to different datasets} - -\item{random_spec}{Either "auto" or a specification of random effects for \code{\link{nlme}} -given as a character vector} - -\item{...}{Additional arguments passed to \code{\link{nlme}}} -} -\value{ -An nlme object -} -\description{ -This function sets up and attempts to fit a mixed effects model to -an mmkin row object which is essentially a list of mkinfit objects -that have been obtained by fitting the same model to a list of -datasets. -} -\examples{ -sampling_times = c(0, 1, 3, 7, 14, 28, 60, 90, 120) -m_SFO <- mkinmod(parent = mkinsub("SFO")) -d_SFO_1 <- mkinpredict(m_SFO, -  c(k_parent_sink = 0.1), -  c(parent = 98), sampling_times) -d_SFO_1_long <- mkin_wide_to_long(d_SFO_1, time = "time") -d_SFO_2 <- mkinpredict(m_SFO, -  c(k_parent_sink = 0.05), -  c(parent = 102), sampling_times) -d_SFO_2_long <- mkin_wide_to_long(d_SFO_2, time = "time") -d_SFO_3 <- mkinpredict(m_SFO, -  c(k_parent_sink = 0.02), -  c(parent = 103), sampling_times) -d_SFO_3_long <- mkin_wide_to_long(d_SFO_3, time = "time") - -d1 <- add_err(d_SFO_1, function(value) 3, n = 1) -d2 <- add_err(d_SFO_2, function(value) 2, n = 1) -d3 <- add_err(d_SFO_3, function(value) 4, n = 1) -ds <- c(d1 = d1, d2 = d2, d3 = d3) - -f <- mmkin("SFO", ds) -x <- memkin(f) -summary(x) - -ds_2 <- lapply(experimental_data_for_UBA_2019[6:10], - function(x) x$data[c("name", "time", "value")]) -m_sfo_sfo <- mkinmod(parent = mkinsub("SFO", "A1"), -  A1 = mkinsub("SFO"), use_of_ff = "min") -m_sfo_sfo_ff <- mkinmod(parent = mkinsub("SFO", "A1"), -  A1 = mkinsub("SFO"), use_of_ff = "max") -m_fomc_sfo <- mkinmod(parent = mkinsub("FOMC", "A1"), -  A1 = mkinsub("SFO")) -m_dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "A1"), -  A1 = mkinsub("SFO")) -m_sforb_sfo <- mkinmod(parent = mkinsub("SFORB", "A1"), -  A1 = mkinsub("SFO")) - -f_2 <- mmkin(list("SFO-SFO" = m_sfo_sfo, - "SFO-SFO-ff" = m_sfo_sfo_ff, - "FOMC-SFO" = m_fomc_sfo, - "DFOP-SFO" = m_dfop_sfo, - "SFORB-SFO" = m_sforb_sfo), -  ds_2) - -f_nlme_sfo_sfo <- memkin(f_2[1, ]) -f_nlme_sfo_sfo_2 <- memkin(f_2[1, ], "pdDiag(parent_0 + log_k_parent_sink + log_k_parent_A1 + log_k_A1_sink ~ 1)") # explicit -f_nlme_sfo_sfo_3 <- memkin(f_2[1, ], "pdDiag(parent_0 + log_k_parent_sink + log_k_parent_A1 ~ 1)") # reduced -f_nlme_sfo_sfo_4 <- memkin(f_2[1, ], "pdDiag(parent_0 + log_k_parent_sink ~ 1)") # further reduced -\dontrun{ -  f_nlme_sfo_sfo_ff <- memkin(f_2[2, ]) # does not converge with maxIter = 50 -} -f_nlme_fomc_sfo <- memkin(f_2[3, ]) -\dontrun{ -  f_nlme_dfop_sfo <- memkin(f_2[4, ])  # apparently underdetermined -  f_nlme_sforb_sfo <- memkin(f_2[5, ]) # also does not converge -} -anova(f_nlme_fomc_sfo, f_nlme_sfo_sfo, f_nlme_sfo_sfo_4) -} diff --git a/man/mkinsub.Rd b/man/mkinsub.Rd index 6522a37e..81615a00 100644 --- a/man/mkinsub.Rd +++ b/man/mkinsub.Rd @@ -40,11 +40,12 @@ SFO_SFO.2 <- mkinmod(    parent = mkinsub("SFO", "m1"),    m1 = mkinsub("SFO")) -# Now supplying full names -SFO_SFO.2 <- mkinmod( -  parent = mkinsub("SFO", "m1", full_name = "Test compound"), -  m1 = mkinsub("SFO", full_name = "Metabolite M1")) - +\dontrun{ +  # Now supplying full names +  SFO_SFO.2 <- mkinmod( +    parent = mkinsub("SFO", "m1", full_name = "Test compound"), +    m1 = mkinsub("SFO", full_name = "Metabolite M1")) + }  }  \author{  Johannes Ranke diff --git a/man/nlme.Rd b/man/nlme.Rd new file mode 100644 index 00000000..e74ba16d --- /dev/null +++ b/man/nlme.Rd @@ -0,0 +1,134 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/nlme.R +\name{mean_degparms} +\alias{mean_degparms} +\alias{nlme_data} +\alias{nlme_function} +\title{Estimation of parameter distributions from mmkin row objects} +\usage{ +mean_degparms(object) + +nlme_data(object) + +nlme_function(object) +} +\arguments{ +\item{object}{An mmkin row object containing several fits of the same model to different datasets} +} +\value{ +A named vector containing mean values of the fitted degradation model parameters + +A groupedData data object + +A function that can be used with nlme +} +\description{ +This function sets up and attempts to fit a mixed effects model to +an mmkin row object. An mmkin row object is essentially a list of mkinfit +objects that have been obtained by fitting the same model to a list of +datasets. +} +\examples{ +sampling_times = c(0, 1, 3, 7, 14, 28, 60, 90, 120) +m_SFO <- mkinmod(parent = mkinsub("SFO")) +d_SFO_1 <- mkinpredict(m_SFO, +  c(k_parent_sink = 0.1), +  c(parent = 98), sampling_times) +d_SFO_1_long <- mkin_wide_to_long(d_SFO_1, time = "time") +d_SFO_2 <- mkinpredict(m_SFO, +  c(k_parent_sink = 0.05), +  c(parent = 102), sampling_times) +d_SFO_2_long <- mkin_wide_to_long(d_SFO_2, time = "time") +d_SFO_3 <- mkinpredict(m_SFO, +  c(k_parent_sink = 0.02), +  c(parent = 103), sampling_times) +d_SFO_3_long <- mkin_wide_to_long(d_SFO_3, time = "time") + +d1 <- add_err(d_SFO_1, function(value) 3, n = 1) +d2 <- add_err(d_SFO_2, function(value) 2, n = 1) +d3 <- add_err(d_SFO_3, function(value) 4, n = 1) +ds <- c(d1 = d1, d2 = d2, d3 = d3) + +f <- mmkin("SFO", ds, cores = 1, quiet = TRUE) +mean_dp <- mean_degparms(f) +grouped_data <- nlme_data(f) +nlme_f <- nlme_function(f) + +library(nlme) +m_nlme <- nlme(value ~ nlme_f(name, time, parent_0, log_k_parent_sink), +  data = grouped_data, +  fixed = parent_0 + log_k_parent_sink ~ 1, +  random = pdDiag(parent_0 + log_k_parent_sink ~ 1), +  start = mean_dp) +summary(m_nlme) + +\dontrun{ +  Test on some real data +  ds_2 <- lapply(experimental_data_for_UBA_2019[6:10], +   function(x) x$data[c("name", "time", "value")]) +  m_sfo_sfo <- mkinmod(parent = mkinsub("SFO", "A1"), +    A1 = mkinsub("SFO"), use_of_ff = "min") +  m_sfo_sfo_ff <- mkinmod(parent = mkinsub("SFO", "A1"), +    A1 = mkinsub("SFO"), use_of_ff = "max") +  m_fomc_sfo <- mkinmod(parent = mkinsub("FOMC", "A1"), +    A1 = mkinsub("SFO")) +  m_dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "A1"), +    A1 = mkinsub("SFO")) +  m_sforb_sfo <- mkinmod(parent = mkinsub("SFORB", "A1"), +    A1 = mkinsub("SFO")) + +  f_2 <- mmkin(list("SFO-SFO" = m_sfo_sfo, +   "SFO-SFO-ff" = m_sfo_sfo_ff, +   "FOMC-SFO" = m_fomc_sfo, +   "DFOP-SFO" = m_dfop_sfo, +   "SFORB-SFO" = m_sforb_sfo), +    ds_2) + +  grouped_data_2 <- nlme_data(f_2["SFO-SFO", ]) + +  mean_dp_sfo_sfo <- mean_degparms(f_2["SFO-SFO", ]) +  mean_dp_sfo_sfo_ff <- mean_degparms(f_2["SFO-SFO-ff", ]) +  mean_dp_fomc_sfo <- mean_degparms(f_2["FOMC-SFO", ]) +  mean_dp_dfop_sfo <- mean_degparms(f_2["DFOP-SFO", ]) +  mean_dp_sforb_sfo <- mean_degparms(f_2["SFORB-SFO", ]) + +  nlme_f_sfo_sfo <- nlme_function(f_2["SFO-SFO", ]) +  nlme_f_sfo_sfo_ff <- nlme_function(f_2["SFO-SFO-ff", ]) +  nlme_f_fomc_sfo <- nlme_function(f_2["FOMC-SFO", ]) + +  # Allowing for correlations between random effects leads to non-convergence +  f_nlme_sfo_sfo <- nlme(value ~ nlme_f_sfo_sfo(name, time, +       parent_0, log_k_parent_sink, log_k_parent_A1, log_k_A1_sink), +     data = grouped_data_2, +     fixed = parent_0 + log_k_parent_sink + log_k_parent_A1 + log_k_A1_sink ~ 1, +     random = pdDiag(parent_0 + log_k_parent_sink + log_k_parent_A1 + log_k_A1_sink ~ 1), +     start = mean_dp_sfo_sfo) + +  # The same model fitted with transformed formation fractions does not converge +  f_nlme_sfo_sfo_ff <- nlme(value ~ nlme_f_sfo_sfo_ff(name, time, +       parent_0, log_k_parent, log_k_A1, f_parent_ilr_1), +     data = grouped_data_2, +     fixed = parent_0 + log_k_parent + log_k_A1 + f_parent_ilr_1 ~ 1, +     random = pdDiag(parent_0 + log_k_parent + log_k_A1 + f_parent_ilr_1 ~ 1), +     start = mean_dp_sfo_sfo_ff) + +  # It does converge with this version of reduced random effects +  f_nlme_sfo_sfo_ff <- nlme(value ~ nlme_f_sfo_sfo_ff(name, time, +       parent_0, log_k_parent, log_k_A1, f_parent_ilr_1), +     data = grouped_data_2, +     fixed = parent_0 + log_k_parent + log_k_A1 + f_parent_ilr_1 ~ 1, +     random = pdDiag(parent_0 + log_k_parent ~ 1), +     start = mean_dp_sfo_sfo_ff) + +  f_nlme_fomc_sfo <- nlme(value ~ nlme_f_fomc_sfo(name, time, +       parent_0, log_alpha, log_beta, log_k_A1, f_parent_ilr_1), +     data = grouped_data_2, +     fixed = parent_0 + log_alpha + log_beta + log_k_A1 + f_parent_ilr_1 ~ 1, +     random = pdDiag(parent_0 + log_alpha + log_beta + log_k_A1 + f_parent_ilr_1 ~ 1), +     start = mean_dp_fomc_sfo) + +  # DFOP-SFO and SFORB-SFO did not converge with full random effects + +  anova(f_nlme_fomc_sfo, f_nlme_sfo_sfo) +} +} diff --git a/vignettes/web_only/FOCUS_Z.R b/vignettes/web_only/FOCUS_Z.R deleted file mode 100644 index 0c19794e..00000000 --- a/vignettes/web_only/FOCUS_Z.R +++ /dev/null @@ -1,115 +0,0 @@ -## ---- include = FALSE--------------------------------------------------------- -require(knitr) -options(digits = 5) -opts_chunk$set(engine='R', tidy = FALSE) - -## ---- echo = TRUE, fig = TRUE, fig.width = 8, fig.height = 7------------------ -library(mkin, quietly = TRUE) -LOD = 0.5 -FOCUS_2006_Z = data.frame( -  t = c(0, 0.04, 0.125, 0.29, 0.54, 1, 2, 3, 4, 7, 10, 14, 21, -        42, 61, 96, 124), -  Z0 = c(100, 81.7, 70.4, 51.1, 41.2, 6.6, 4.6, 3.9, 4.6, 4.3, 6.8, -         2.9, 3.5, 5.3, 4.4, 1.2, 0.7), -  Z1 = c(0, 18.3, 29.6, 46.3, 55.1, 65.7, 39.1, 36, 15.3, 5.6, 1.1, -         1.6, 0.6, 0.5 * LOD, NA, NA, NA), -  Z2 = c(0, NA, 0.5 * LOD, 2.6, 3.8, 15.3, 37.2, 31.7, 35.6, 14.5, -         0.8, 2.1, 1.9, 0.5 * LOD, NA, NA, NA), -  Z3 = c(0, NA, NA, NA, NA, 0.5 * LOD, 9.2, 13.1, 22.3, 28.4, 32.5, -         25.2, 17.2, 4.8, 4.5, 2.8, 4.4)) - -FOCUS_2006_Z_mkin <- mkin_wide_to_long(FOCUS_2006_Z) - -## ----FOCUS_2006_Z_fits_1, echo=TRUE, fig.height=6----------------------------- -Z.2a <- mkinmod(Z0 = mkinsub("SFO", "Z1"), -                Z1 = mkinsub("SFO")) -m.Z.2a <- mkinfit(Z.2a, FOCUS_2006_Z_mkin, quiet = TRUE) -plot_sep(m.Z.2a) -summary(m.Z.2a, data = FALSE)$bpar - -## ----FOCUS_2006_Z_fits_2, echo=TRUE, fig.height=6----------------------------- -Z.2a.ff <- mkinmod(Z0 = mkinsub("SFO", "Z1"), -                   Z1 = mkinsub("SFO"), -                   use_of_ff = "max") - -m.Z.2a.ff <- mkinfit(Z.2a.ff, FOCUS_2006_Z_mkin, quiet = TRUE) -plot_sep(m.Z.2a.ff) -summary(m.Z.2a.ff, data = FALSE)$bpar - -## ----FOCUS_2006_Z_fits_3, echo=TRUE, fig.height=6----------------------------- -Z.3 <- mkinmod(Z0 = mkinsub("SFO", "Z1", sink = FALSE), -               Z1 = mkinsub("SFO"), use_of_ff = "max") -m.Z.3 <- mkinfit(Z.3, FOCUS_2006_Z_mkin, quiet = TRUE) -plot_sep(m.Z.3) -summary(m.Z.3, data = FALSE)$bpar - -## ----FOCUS_2006_Z_fits_5, echo=TRUE, fig.height=7----------------------------- -Z.5 <- mkinmod(Z0 = mkinsub("SFO", "Z1", sink = FALSE), -               Z1 = mkinsub("SFO", "Z2", sink = FALSE), -               Z2 = mkinsub("SFO"), use_of_ff = "max") -m.Z.5 <- mkinfit(Z.5, FOCUS_2006_Z_mkin, quiet = TRUE) -plot_sep(m.Z.5) - -## ----FOCUS_2006_Z_fits_6, echo=TRUE, fig.height=8----------------------------- -Z.FOCUS <- mkinmod(Z0 = mkinsub("SFO", "Z1", sink = FALSE), -                   Z1 = mkinsub("SFO", "Z2", sink = FALSE), -                   Z2 = mkinsub("SFO", "Z3"), -                   Z3 = mkinsub("SFO"), -                   use_of_ff = "max") -m.Z.FOCUS <- mkinfit(Z.FOCUS, FOCUS_2006_Z_mkin, -                     parms.ini = m.Z.5$bparms.ode, -                     quiet = TRUE) -plot_sep(m.Z.FOCUS) -summary(m.Z.FOCUS, data = FALSE)$bpar -endpoints(m.Z.FOCUS) - -## ----FOCUS_2006_Z_fits_7, echo=TRUE, fig.height=8----------------------------- -Z.mkin.1 <- mkinmod(Z0 = mkinsub("SFO", "Z1", sink = FALSE), -                    Z1 = mkinsub("SFO", "Z2", sink = FALSE), -                    Z2 = mkinsub("SFO", "Z3"), -                    Z3 = mkinsub("SFORB")) -m.Z.mkin.1 <- mkinfit(Z.mkin.1, FOCUS_2006_Z_mkin, quiet = TRUE) -plot_sep(m.Z.mkin.1) -summary(m.Z.mkin.1, data = FALSE)$cov.unscaled - -## ----FOCUS_2006_Z_fits_9, echo=TRUE, fig.height=8----------------------------- -Z.mkin.3 <- mkinmod(Z0 = mkinsub("SFORB", "Z1", sink = FALSE), -                    Z1 = mkinsub("SFO", "Z2", sink = FALSE), -                    Z2 = mkinsub("SFO")) -m.Z.mkin.3 <- mkinfit(Z.mkin.3, FOCUS_2006_Z_mkin, quiet = TRUE) -plot_sep(m.Z.mkin.3) - -## ----FOCUS_2006_Z_fits_10, echo=TRUE, fig.height=8---------------------------- -Z.mkin.4 <- mkinmod(Z0 = mkinsub("SFORB", "Z1", sink = FALSE), -                    Z1 = mkinsub("SFO", "Z2", sink = FALSE), -                    Z2 = mkinsub("SFO", "Z3"), -                    Z3 = mkinsub("SFO")) -m.Z.mkin.4 <- mkinfit(Z.mkin.4, FOCUS_2006_Z_mkin, -                      parms.ini = m.Z.mkin.3$bparms.ode, -                      quiet = TRUE) -plot_sep(m.Z.mkin.4) - -## ----FOCUS_2006_Z_fits_11, echo=TRUE, fig.height=8---------------------------- -Z.mkin.5 <- mkinmod(Z0 = mkinsub("SFORB", "Z1", sink = FALSE), -                    Z1 = mkinsub("SFO", "Z2", sink = FALSE), -                    Z2 = mkinsub("SFO", "Z3"), -                    Z3 = mkinsub("SFORB")) -m.Z.mkin.5 <- mkinfit(Z.mkin.5, FOCUS_2006_Z_mkin, -                      parms.ini = m.Z.mkin.4$bparms.ode[1:4], -                      quiet = TRUE) -plot_sep(m.Z.mkin.5) - -## ----FOCUS_2006_Z_fits_11a, echo=TRUE----------------------------------------- -m.Z.mkin.5a <- mkinfit(Z.mkin.5, FOCUS_2006_Z_mkin, -                       parms.ini = c(m.Z.mkin.5$bparms.ode[1:7], -                                     k_Z3_bound_free = 0), -                       fixed_parms = "k_Z3_bound_free", -                       quiet = TRUE) -plot_sep(m.Z.mkin.5a) - -## ----FOCUS_2006_Z_fits_11b, echo=TRUE----------------------------------------- -mkinparplot(m.Z.mkin.5a) - -## ----FOCUS_2006_Z_fits_11b_endpoints, echo=TRUE------------------------------- -endpoints(m.Z.mkin.5a) - diff --git a/vignettes/web_only/compiled_models.R b/vignettes/web_only/compiled_models.R deleted file mode 100644 index 691037ec..00000000 --- a/vignettes/web_only/compiled_models.R +++ /dev/null @@ -1,61 +0,0 @@ -## ---- include = FALSE--------------------------------------------------------- -library(knitr) -opts_chunk$set(tidy = FALSE, cache = FALSE) - -## ----check_gcc, eval = FALSE-------------------------------------------------- -#  pkgbuild::has_compiler() - -## ----Rprofile, eval = FALSE--------------------------------------------------- -#  Sys.setenv(PATH = paste("C:/Rtools/bin", Sys.getenv("PATH"), sep=";")) - -## ----HOME, eval = FALSE------------------------------------------------------- -#  Sys.getenv("HOME") - -## ----create_SFO_SFO----------------------------------------------------------- -library("mkin", quietly = TRUE) -SFO_SFO <- mkinmod( -  parent = mkinsub("SFO", "m1"), -  m1 = mkinsub("SFO")) - -## ----benchmark_SFO_SFO, fig.height = 3, message = FALSE, warning = FALSE------ -if (require(rbenchmark)) { -  b.1 <- benchmark( -    "deSolve, not compiled" = mkinfit(SFO_SFO, FOCUS_2006_D, -                                      solution_type = "deSolve", -                                      use_compiled = FALSE, quiet = TRUE), -    "Eigenvalue based" = mkinfit(SFO_SFO, FOCUS_2006_D, -                                 solution_type = "eigen", quiet = TRUE), -    "deSolve, compiled" = mkinfit(SFO_SFO, FOCUS_2006_D, -                                  solution_type = "deSolve", quiet = TRUE), -    replications = 3) -  print(b.1) -  factor_SFO_SFO <- round(b.1["1", "relative"]) -} else { -  factor_SFO_SFO <- NA -  print("R package rbenchmark is not available") -} - -## ----benchmark_FOMC_SFO, fig.height = 3, warning = FALSE---------------------- -if (require(rbenchmark)) { -  FOMC_SFO <- mkinmod( -    parent = mkinsub("FOMC", "m1"), -    m1 = mkinsub( "SFO")) - -  b.2 <- benchmark( -    "deSolve, not compiled" = mkinfit(FOMC_SFO, FOCUS_2006_D, -                                      use_compiled = FALSE, quiet = TRUE), -    "deSolve, compiled" = mkinfit(FOMC_SFO, FOCUS_2006_D, quiet = TRUE), -    replications = 3) -  print(b.2) -  factor_FOMC_SFO <- round(b.2["1", "relative"]) -} else { -  factor_FOMC_SFO <- NA -  print("R package benchmark is not available") -} - -## ----sessionInfo, echo = FALSE------------------------------------------------ -cat(utils::capture.output(utils::sessionInfo())[1:3], sep = "\n") -if(!inherits(try(cpuinfo <- readLines("/proc/cpuinfo")), "try-error")) { -  cat(gsub("model name\t: ", "CPU model: ", cpuinfo[grep("model name", cpuinfo)[1]])) -} - | 
