[Rd] suggested minor patch for optim.R

Ben Bolker bolker at zoo.ufl.edu
Sat Apr 5 01:08:16 CEST 2008


    optim ignores misspelled control parameters, so that trying
to set (e.g.) "maxint=1000" in  the control argument silently
does nothing.  The patch below (watch out for line breaks! also
posted at http://www.zoo.ufl.edu/bolker/optim_patch.R , and
http://www.zoo.ufl.edu/bolker/optim_new.R) adds
three lines to optim.R that issue a warning if any names of
elements of "control" fail to match the internal object that
contains the defaults.

   Here is code that shows the behavior:

set.seed(1001)
x <- rnorm(10)
y <- rnorm(10,mean=1+2*x,sd=0.2)
ssqfun <- function(p) { sum((y-(p[1]+p[2]*x))^2) }
## use bogus control variable
O1 <- optim(fn=ssqfun,par=c(1,2),control=list(maxint=100))
## get new version
source(url("http://www.zoo.ufl.edu/bolker/optim_new.R"))
O2 <- optim(fn=ssqfun,par=c(1,2),control=list(maxint=100))
O3 <- optim(fn=ssqfun,par=c(1,2),control=list(maxint=100,bogus=123))

   I realize this is probably too late for feature freeze for 2.7.0 (?),
but I'd appreciate any comments ...


*** optim_orig.R        2008-04-04 18:55:42.000000000 -0400
--- optim_new.R 2008-04-04 18:58:56.000000000 -0400
***************
*** 37,46 ****
--- 37,50 ----
                   type = 1,
                   lmm = 5, factr = 1e7, pgtol = 0,
                   tmax = 10, temp = 10.0)
+     orig.names <- names(con)
       if (method == "Nelder-Mead") con$maxit <- 500
       if (method == "SANN") con$maxit <- 10000

       con[(namc <- names(control))] <- control
+     newnames <- names(control)[!names(control) %in% orig.names]
+     if (length(newnames)>0)
+       warning(paste("unknown names in 
control:",paste(newnames,collapse=", ")))
       if(con$trace < 0)
           warning("read the documentation for 'trace' more carefully")
       if (method == "L-BFGS-B" &&



More information about the R-devel mailing list