minpack_hybrj Subroutine

public subroutine minpack_hybrj(fcn, n, x, fvec, fjac, ldfjac, xtol, maxfev, diag, mode, factor, nprint, info, nfev, njev, r, lr, qtf, wa1, wa2, wa3, wa4, udata) bind(c)

Arguments

TypeIntentOptionalAttributesName
procedure(minpack_fcn_hybrj) :: fcn
integer(kind=c_int), value:: n
real(kind=c_double), intent(inout) :: x(n)
real(kind=c_double), intent(out) :: fvec(n)
real(kind=c_double), intent(out) :: fjac(ldfjac,n)
integer(kind=c_int), value:: ldfjac
real(kind=c_double), value:: xtol
integer(kind=c_int), value:: maxfev
real(kind=c_double), intent(inout) :: diag(n)
integer(kind=c_int), value:: mode
real(kind=c_double), value:: factor
integer(kind=c_int), value:: nprint
integer(kind=c_int), intent(out) :: info
integer(kind=c_int), intent(out) :: nfev
integer(kind=c_int), intent(out) :: njev
real(kind=c_double), intent(out) :: r(lr)
integer(kind=c_int), value:: lr
real(kind=c_double), intent(out) :: qtf(n)
real(kind=c_double), intent(inout) :: wa1(n)
real(kind=c_double), intent(inout) :: wa2(n)
real(kind=c_double), intent(inout) :: wa3(n)
real(kind=c_double), intent(inout) :: wa4(n)
type(c_ptr), value:: udata

Calls

proc~~minpack_hybrj~~CallsGraph proc~minpack_hybrj minpack_hybrj proc~hybrj hybrj proc~minpack_hybrj->proc~hybrj proc~dogleg dogleg proc~hybrj->proc~dogleg proc~r1updt r1updt proc~hybrj->proc~r1updt proc~qrfac qrfac proc~hybrj->proc~qrfac proc~qform qform proc~hybrj->proc~qform proc~enorm enorm proc~hybrj->proc~enorm proc~r1mpyq r1mpyq proc~hybrj->proc~r1mpyq proc~dogleg->proc~enorm proc~qrfac->proc~enorm

Contents

Source Code


Source Code

    subroutine minpack_hybrj(fcn, n, x, fvec, fjac, ldfjac, xtol, maxfev, diag, mode, &
            & factor, nprint, info, nfev, njev, r, lr, qtf, wa1, wa2, wa3, wa4, udata) &
            & bind(c)
        procedure(minpack_fcn_hybrj) :: fcn
        integer(c_int), value :: n
        integer(c_int), value :: ldfjac
        integer(c_int), value :: maxfev
        integer(c_int), value :: mode
        integer(c_int), value :: nprint
        integer(c_int), intent(out) :: info
        integer(c_int), intent(out) :: nfev
        integer(c_int), intent(out) :: njev
        integer(c_int), value :: lr
        real(c_double), value :: xtol
        real(c_double), value :: factor
        real(c_double), intent(inout) :: x(n)
        real(c_double), intent(out) :: fvec(n)
        real(c_double), intent(out) :: fjac(ldfjac, n)
        real(c_double), intent(inout) :: diag(n)
        real(c_double), intent(out) :: r(lr)
        real(c_double), intent(out) :: qtf(n)
        real(c_double), intent(inout) :: wa1(n)
        real(c_double), intent(inout) :: wa2(n)
        real(c_double), intent(inout) :: wa3(n)
        real(c_double), intent(inout) :: wa4(n)
        type(c_ptr), value :: udata

        call hybrj(wrap_fcn, n, x, fvec, fjac, ldfjac, xtol, maxfev, diag, mode, &
            & factor, nprint, info, nfev, njev, r, lr, qtf, wa1, wa2, wa3, wa4)

    contains
        subroutine wrap_fcn(n, x, fvec, fjac, ldfjac, iflag)
            integer, intent(in) :: n
            real(wp), intent(in) :: x(n)
            integer, intent(in) :: ldfjac
            real(wp), intent(inout) :: fvec(n)
            real(wp), intent(inout) :: fjac(ldfjac, n)
            integer, intent(inout) :: iflag

            call fcn(n, x, fvec, fjac, ldfjac, iflag, udata)
        end subroutine wrap_fcn
    end subroutine minpack_hybrj