[Rd] nls with algorithm = "port", starting values

Katharine Mullen kate at few.vu.nl
Mon Apr 16 09:35:43 CEST 2007


The documentation for nls says the following about the starting values:

 start: a named list or named numeric vector of starting estimates.
          Since R 2.4.0, when 'start' is missing, a very cheap guess
          for 'start' is tried (if 'algorithm != "plinear"').

It may be a good idea to document that when algorithm = "port", if start
is a named list, the elements of the list must be numeric vectors of
length 1.  Ie, start = list(a=1,b=2,c=3) is ok, but start = list(a=c(1,2),
b=3) is not.  This is not the case when algorithm is "plinear" or the
default GN, and is because of the way that the "port" code in nls.R
transforms the starting values (the other options do something else):

nls_port_fit <- function(m, start, lower, upper, control, trace)
{
    ## Establish the working vectors and check and set options
    p <- length(par <- as.double(start))


Example:

## exponentially decaying data
getExpmat <- function(theta, t)
{
        conc <- matrix(nrow = length(t), ncol = length(theta))
        for(i in 1:length(theta)) {
                conc[, i] <- exp(- theta[i] * t)
        }
        conc
}

expsum <- as.vector(getExpmat(c(.05,.005), 1:100) %*% c(1,1))
expsumNoisy <- expsum + max(expsum) *.001 * rnorm(100)
expsum.df <-data.frame(expsumNoisy)

## estimate decay rates, amplitudes with default Gauss-Newton
summary (nls(expsumNoisy ~ getExpmat(k, 1:100) %*% sp, expsum.df, start =
list(k = c(.6,.02), sp = c(1,2)), trace=TRUE, control =
nls.control(maxiter=20,
warnOnly =  TRUE)))

## won't work with port
summary (nls(expsumNoisy ~ getExpmat(k, 1:100) %*% sp, expsum.df, start =
list(k = c(.6,.02), sp = c(1,2)), algorithm = "port",
trace=TRUE, control = nls.control(maxiter=20,
warnOnly =  TRUE)))



More information about the R-devel mailing list