the purpose of lmdif1 is to minimize the sum of the squares of m nonlinear functions in n variables by a modification of the levenberg-marquardt algorithm. this is done by using the more general least-squares solver lmdif. the user must provide a subroutine which calculates the functions. the jacobian is then calculated by a forward-difference approximation.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
procedure(func2) | :: | fcn | the user-supplied subroutine which calculates the functions. |
|||
integer, | intent(in) | :: | m | a positive integer input variable set to the number of functions. |
||
integer, | intent(in) | :: | n | a positive integer input variable set to the number of variables. n must not exceed m. |
||
real(kind=wp), | intent(inout) | :: | x(n) | an array of length n. on input x must contain an initial estimate of the solution vector. on output x contains the final estimate of the solution vector. |
||
real(kind=wp), | intent(out) | :: | Fvec(m) | an output array of length m which contains the functions evaluated at the output x. |
||
real(kind=wp), | intent(in) | :: | Tol | a nonnegative input variable. termination occurs when the algorithm estimates either that the relative error in the sum of squares is at most tol or that the relative error between x and the solution is at most tol. |
||
integer, | intent(out) | :: | Info | an integer output variable. if the user has terminated execution, info is set to the (negative) value of iflag. see description of fcn. otherwise, info is set as follows:
|
||
integer, | intent(inout) | :: | Iwa(n) | an integer work array of length n. |
||
real(kind=wp), | intent(inout) | :: | Wa(Lwa) | a work array of length lwa. |
||
integer, | intent(in) | :: | Lwa | a positive integer input variable not less than mn+5n+m. |
subroutine lmdif1(fcn, m, n, x, Fvec, Tol, Info, Iwa, Wa, Lwa)
implicit none
procedure(func2) :: fcn !! the user-supplied subroutine which
!! calculates the functions.
integer, intent(in) :: m !! a positive integer input variable set to the number
!! of functions.
integer, intent(in) :: n !! a positive integer input variable set to the number
!! of variables. n must not exceed m.
integer, intent(out) :: Info !! an integer output variable. if the user has
!! terminated execution, info is set to the (negative)
!! value of iflag. see description of fcn. otherwise,
!! info is set as follows:
!!
!! * ***info = 0*** improper input parameters.
!! * ***info = 1*** algorithm estimates that the relative error
!! in the sum of squares is at most tol.
!! * ***info = 2*** algorithm estimates that the relative error
!! between x and the solution is at most tol.
!! * ***info = 3*** conditions for info = 1 and info = 2 both hold.
!! * ***info = 4*** fvec is orthogonal to the columns of the
!! jacobian to machine precision.
!! * ***info = 5*** number of calls to fcn has reached or
!! exceeded 200*(n+1).
!! * ***info = 6*** tol is too small. no further reduction in
!! the sum of squares is possible.
!! * ***info = 7*** tol is too small. no further improvement in
!! the approximate solution x is possible.
integer, intent(in) :: Lwa !! a positive integer input variable not less than
!! m*n+5*n+m.
integer, intent(inout) :: Iwa(n) !! an integer work array of length n.
real(wp), intent(in) :: Tol !! a nonnegative input variable. termination occurs
!! when the algorithm estimates either that the relative
!! error in the sum of squares is at most tol or that
!! the relative error between x and the solution is at
!! most tol.
real(wp), intent(inout) :: x(n) !! an array of length n. on input x must contain
!! an initial estimate of the solution vector. on output x
!! contains the final estimate of the solution vector.
real(wp), intent(out) :: Fvec(m) !! an output array of length m which contains
!! the functions evaluated at the output x.
real(wp), intent(inout) :: Wa(Lwa) !! a work array of length lwa.
integer :: maxfev, mode, mp5n, nfev, nprint
real(wp) :: epsfcn, ftol, gtol, xtol
real(wp), parameter :: factor = 1.0e2_wp
Info = 0
! check the input parameters for errors.
if (n > 0 .and. m >= n .and. Tol >= zero .and. Lwa >= m*n + 5*n + m) then
! call lmdif.
maxfev = 200*(n + 1)
ftol = Tol
xtol = Tol
gtol = zero
epsfcn = zero
mode = 1
nprint = 0
mp5n = m + 5*n
call lmdif(fcn, m, n, x, Fvec, ftol, xtol, gtol, maxfev, epsfcn, Wa(1), &
mode, factor, nprint, Info, nfev, Wa(mp5n + 1), m, Iwa, &
Wa(n + 1), Wa(2*n + 1), Wa(3*n + 1), Wa(4*n + 1), Wa(5*n + 1))
if (Info == 8) Info = 4
end if
end subroutine lmdif1