minpack_lmder Subroutine

public subroutine minpack_lmder(fcn, m, n, x, fvec, fjac, ldfjac, ftol, xtol, gtol, maxfev, diag, mode, factor, nprint, info, nfev, njev, ipvt, qtf, wa1, wa2, wa3, wa4, udata) bind(c)

Arguments

TypeIntentOptionalAttributesName
procedure(minpack_fcn_lmder) :: fcn
integer(kind=c_int), value:: m
integer(kind=c_int), value:: n
real(kind=c_double), intent(inout) :: x(n)
real(kind=c_double), intent(out) :: fvec(m)
real(kind=c_double), intent(out) :: fjac(ldfjac,n)
integer(kind=c_int), value:: ldfjac
real(kind=c_double), value:: ftol
real(kind=c_double), value:: xtol
real(kind=c_double), value:: gtol
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
integer(kind=c_int), intent(out) :: ipvt(n)
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(m)
type(c_ptr), value:: udata

Calls

proc~~minpack_lmder~~CallsGraph proc~minpack_lmder minpack_lmder proc~lmder lmder proc~minpack_lmder->proc~lmder proc~enorm enorm proc~lmder->proc~enorm proc~lmpar lmpar proc~lmder->proc~lmpar proc~qrfac qrfac proc~lmder->proc~qrfac proc~lmpar->proc~enorm proc~qrsolv qrsolv proc~lmpar->proc~qrsolv proc~qrfac->proc~enorm

Contents

Source Code


Source Code

    subroutine minpack_lmder(fcn, m, n, x, fvec, fjac, ldfjac, ftol, xtol, gtol, maxfev, &
            & diag, mode, factor, nprint, info, nfev, njev, ipvt, qtf, wa1, wa2, wa3, wa4, &
            & udata) &
            & bind(c)
        procedure(minpack_fcn_lmder) :: fcn
        integer(c_int), value :: m
        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), intent(out) :: ipvt(n)
        real(c_double), value :: ftol
        real(c_double), value :: xtol
        real(c_double), value :: gtol
        real(c_double), value :: factor
        real(c_double), intent(inout) :: x(n)
        real(c_double), intent(out) :: fvec(m)
        real(c_double), intent(out) :: fjac(ldfjac, n)
        real(c_double), intent(inout) :: diag(n)
        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(m)
        type(c_ptr), value :: udata

        call lmder(wrap_fcn, m, n, x, fvec, fjac, ldfjac, ftol, xtol, gtol, maxfev, &
            & diag, mode, factor, nprint, info, nfev, njev, ipvt, qtf, wa1, wa2, wa3, wa4)

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

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