aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--R/mhmkin.R23
-rw-r--r--R/saem.R4
2 files changed, 25 insertions, 2 deletions
diff --git a/R/mhmkin.R b/R/mhmkin.R
index 2cf9ba06..2df01f0c 100644
--- a/R/mhmkin.R
+++ b/R/mhmkin.R
@@ -203,3 +203,26 @@ BIC.mhmkin <- function(object, ...) {
dimnames(res) <- dimnames(object)
return(res)
}
+
+#' @export
+update.mhmkin <- function(object, ..., evaluate = TRUE) {
+ call <- attr(object, "call")
+
+ update_arguments <- match.call(expand.dots = FALSE)$...
+
+ if (length(update_arguments) > 0) {
+ update_arguments_in_call <- !is.na(match(names(update_arguments), names(call)))
+ }
+
+ for (a in names(update_arguments)[update_arguments_in_call]) {
+ call[[a]] <- update_arguments[[a]]
+ }
+
+ update_arguments_not_in_call <- !update_arguments_in_call
+ if(any(update_arguments_not_in_call)) {
+ call <- c(as.list(call), update_arguments[update_arguments_not_in_call])
+ call <- as.call(call)
+ }
+ if(evaluate) eval(call, parent.frame())
+ else call
+}
diff --git a/R/saem.R b/R/saem.R
index 99712c92..5256f6b5 100644
--- a/R/saem.R
+++ b/R/saem.R
@@ -635,8 +635,8 @@ logLik.saem.mmkin <- function(object, ...) return(logLik(object$so))
update.saem.mmkin <- function(object, ..., evaluate = TRUE) {
call <- object$call
# For some reason we get saem.mmkin in the call when using mhmkin
- # so we need to fix this in order to avoid exporting saem.mmkin
- # in addition to the S3 method
+ # so we need to fix this so we do not have to export saem.mmkin in
+ # addition to the S3 method
call[[1]] <- saem
update_arguments <- match.call(expand.dots = FALSE)$...

Contact - Imprint