hybrd1 Subroutine

public subroutine hybrd1(fcn, n, x, fvec, tol, info, Wa, Lwa)

the purpose of hybrd1 is to find a zero of a system of n nonlinear functions in n variables by a modification of the powell hybrid method. this is done by using the more general nonlinear equation solver hybrd. the user must provide a subroutine which calculates the functions. the jacobian is then calculated by a forward-difference approximation.

Arguments

TypeIntentOptionalAttributesName
procedure(func) :: fcn

user-supplied subroutine which calculates the functions

integer, intent(in) :: n

a positive integer input variable set to the number of functions and variables.

real(kind=wp), intent(inout), dimension(n):: x

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), dimension(n):: fvec

an output array of length n 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 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:

  • info = 0 improper input parameters.
  • info = 1 algorithm estimates that the relative error between x and the solution is at most tol.
  • info = 2 number of calls to fcn has reached or exceeded 200*(n+1).
  • info = 3 tol is too small. no further improvement in the approximate solution x is possible.
  • info = 4 iteration is not making good progress.
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 (n(3n+13))/2.


Calls

proc~~hybrd1~~CallsGraph proc~hybrd1 hybrd1 proc~hybrd hybrd proc~hybrd1->proc~hybrd proc~dogleg dogleg proc~hybrd->proc~dogleg proc~r1updt r1updt proc~hybrd->proc~r1updt proc~qrfac qrfac proc~hybrd->proc~qrfac proc~qform qform proc~hybrd->proc~qform proc~enorm enorm proc~hybrd->proc~enorm proc~r1mpyq r1mpyq proc~hybrd->proc~r1mpyq proc~fdjac1 fdjac1 proc~hybrd->proc~fdjac1 proc~dogleg->proc~enorm proc~qrfac->proc~enorm

Called by

proc~~hybrd1~~CalledByGraph proc~hybrd1 hybrd1 proc~minpack_hybrd1 minpack_hybrd1 proc~minpack_hybrd1->proc~hybrd1

Contents

Source Code


Source Code

    subroutine hybrd1(fcn, n, x, Fvec, Tol, Info, Wa, Lwa)

        implicit none

        procedure(func)                     :: fcn      !! user-supplied subroutine which calculates the functions
        integer, intent(in)                  :: n        !! a positive integer input variable set to the number
                                                    !! of functions and variables.
        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
                                                    !!  between `x` and the solution is at most `tol`.
                                                    !!  * ***info = 2*** number of calls to `fcn` has reached or exceeded
                                                    !!  `200*(n+1)`.
                                                    !!  * ***info = 3*** `tol` is too small. no further improvement in
                                                    !!  the approximate solution `x` is possible.
                                                    !!  * ***info = 4*** iteration is not making good progress.
        real(wp), intent(in)                 :: tol      !! a nonnegative input variable. termination occurs
                                                    !! when the algorithm estimates that the relative error
                                                    !! between `x` and the solution is at most `tol`.
        real(wp), dimension(n), intent(inout) :: x        !! 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), dimension(n), intent(out)   :: fvec     !! an output array of length `n` which contains
                                                    !! the functions evaluated at the output `x`.
        integer, intent(in) :: Lwa !! a positive integer input variable not less than
                              !! (n*(3*n+13))/2.
        real(wp), intent(inout) :: Wa(Lwa) !! a work array of length lwa.

        integer :: index, j, lr, maxfev, ml, mode, mu, nfev, nprint
        real(wp) :: epsfcn, xtol

        reaL(wp), parameter :: factor = 100.0_wp

        Info = 0

        ! check the input parameters for errors.

        if (n > 0 .and. Tol >= zero .and. Lwa >= (n*(3*n + 13))/2) then
            ! call hybrd.
            maxfev = 200*(n + 1)
            xtol = Tol
            ml = n - 1
            mu = n - 1
            epsfcn = zero
            mode = 2
            do j = 1, n
                Wa(j) = one
            end do
            nprint = 0
            lr = (n*(n + 1))/2
            index = 6*n + lr
            call hybrd(fcn, n, x, Fvec, xtol, maxfev, ml, mu, epsfcn, Wa(1), mode, &
                       factor, nprint, Info, nfev, Wa(index + 1), n, Wa(6*n + 1), lr, &
                       Wa(n + 1), Wa(2*n + 1), Wa(3*n + 1), Wa(4*n + 1), Wa(5*n + 1))
            if (Info == 5) Info = 4
        end if

    end subroutine hybrd1