minpack_capi Module


Uses

  • module~~minpack_capi~~UsesGraph module~minpack_capi minpack_capi iso_c_binding iso_c_binding module~minpack_capi->iso_c_binding module~minpack_module minpack_module module~minpack_capi->module~minpack_module iso_fortran_env iso_fortran_env module~minpack_module->iso_fortran_env

Contents


Abstract Interfaces

abstract interface

  • public subroutine minpack_func(n, x, fvec, iflag, udata) bind(c)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=c_int), value:: n
    real(kind=c_double), intent(in) :: x(n)
    real(kind=c_double), intent(out) :: fvec(n)
    integer(kind=c_int), intent(inout) :: iflag
    type(c_ptr), value:: udata

abstract interface

  • public subroutine minpack_func2(m, n, x, fvec, iflag, udata) bind(c)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=c_int), value:: m
    integer(kind=c_int), value:: n
    real(kind=c_double), intent(in) :: x(n)
    real(kind=c_double), intent(out) :: fvec(m)
    integer(kind=c_int), intent(inout) :: iflag
    type(c_ptr), value:: udata

abstract interface

  • public subroutine minpack_fcn_hybrj(n, x, fvec, fjac, ldfjac, iflag, udata) bind(c)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=c_int), value:: n
    real(kind=c_double), intent(in) :: 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
    integer(kind=c_int), intent(inout) :: iflag
    type(c_ptr), value:: udata

abstract interface

  • public subroutine minpack_fcn_lmder(m, n, x, fvec, fjac, ldfjac, iflag, udata) bind(c)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=c_int), value:: m
    integer(kind=c_int), value:: n
    real(kind=c_double), intent(in) :: x(n)
    real(kind=c_double), intent(inout) :: fvec(m)
    real(kind=c_double), intent(inout) :: fjac(ldfjac,n)
    integer(kind=c_int), value:: ldfjac
    integer(kind=c_int), intent(inout) :: iflag
    type(c_ptr), value:: udata

abstract interface

  • public subroutine minpack_fcn_lmstr(m, n, x, fvec, fjrow, iflag, udata) bind(c)

    Arguments

    TypeIntentOptionalAttributesName
    integer(kind=c_int), value:: m
    integer(kind=c_int), value:: n
    real(kind=c_double), intent(in) :: x(n)
    real(kind=c_double), intent(inout) :: fvec(m)
    real(kind=c_double), intent(inout) :: fjrow(n)
    integer(kind=c_int), intent(inout) :: iflag
    type(c_ptr), value:: udata

Functions

public function minpack_dpmpar(i) result(par) bind(c)

Arguments

TypeIntentOptionalAttributesName
integer(kind=c_int), value:: i

Return Value real(kind=c_double)


Subroutines

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

Arguments

TypeIntentOptionalAttributesName
procedure(minpack_func) :: 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), value:: xtol
integer(kind=c_int), value:: maxfev
integer(kind=c_int), value:: ml
integer(kind=c_int), value:: mu
real(kind=c_double), value:: epsfcn
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
real(kind=c_double), intent(out) :: fjac(ldfjac,n)
integer(kind=c_int), value:: ldfjac
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

public subroutine minpack_hybrd1(fcn, n, x, fvec, tol, info, Wa, Lwa, udata) bind(c)

Arguments

TypeIntentOptionalAttributesName
procedure(minpack_func) :: 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), value:: tol
integer(kind=c_int), intent(out) :: info
real(kind=c_double), intent(inout) :: Wa(Lwa)
integer(kind=c_int), value:: Lwa
type(c_ptr), value:: udata

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

public subroutine minpack_hybrj1(fcn, n, x, fvec, fjac, ldfjac, tol, info, wa, lwa, 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:: tol
integer(kind=c_int), intent(out) :: info
real(kind=c_double), intent(inout) :: wa(lwa)
integer(kind=c_int), value:: lwa
type(c_ptr), value:: udata

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

Arguments

TypeIntentOptionalAttributesName
procedure(minpack_func2) :: 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), value:: ftol
real(kind=c_double), value:: xtol
real(kind=c_double), value:: gtol
integer(kind=c_int), value:: maxfev
real(kind=c_double), value:: epsfcn
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
real(kind=c_double), intent(out) :: fjac(ldfjac,n)
integer(kind=c_int), value:: ldfjac
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

public subroutine minpack_lmdif1(fcn, m, n, x, fvec, tol, info, iwa, wa, lwa, udata) bind(c)

Arguments

TypeIntentOptionalAttributesName
procedure(minpack_func2) :: 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(inout) :: fvec(m)
real(kind=c_double), value:: tol
integer(kind=c_int), intent(out) :: info
integer(kind=c_int), intent(inout) :: iwa(n)
real(kind=c_double), intent(inout) :: wa(lwa)
integer(kind=c_int), value:: lwa
type(c_ptr), value:: udata

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

public subroutine minpack_lmder1(fcn, m, n, x, fvec, fjac, ldfjac, tol, info, ipvt, wa, lwa, 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:: tol
integer(kind=c_int), intent(out) :: info
integer(kind=c_int), intent(out) :: ipvt(n)
real(kind=c_double), intent(inout) :: wa(lwa)
integer(kind=c_int), value:: lwa
type(c_ptr), value:: udata

private subroutine minpack_lmstr(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_lmstr) :: 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

private subroutine minpack_lmstr1(fcn, m, n, x, fvec, fjac, ldfjac, tol, info, ipvt, wa, lwa, udata) bind(c)

Arguments

TypeIntentOptionalAttributesName
procedure(minpack_fcn_lmstr) :: 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:: tol
integer(kind=c_int), intent(out) :: info
integer(kind=c_int), intent(out) :: ipvt(n)
real(kind=c_double), intent(inout) :: wa(lwa)
integer(kind=c_int), value:: lwa
type(c_ptr), value:: udata

public subroutine minpack_chkder(m, n, x, fvec, fjac, ldfjac, xp, fvecp, mode, err) bind(c)

Arguments

TypeIntentOptionalAttributesName
integer(kind=c_int), value:: m
integer(kind=c_int), value:: n
real(kind=c_double), intent(in) :: x(n)
real(kind=c_double), intent(in) :: fvec(m)
real(kind=c_double), intent(in) :: fjac(ldfjac,n)
integer(kind=c_int), value:: ldfjac
real(kind=c_double), intent(out) :: xp(n)
real(kind=c_double), intent(in) :: fvecp(m)
integer(kind=c_int), value:: mode
real(kind=c_double), intent(out) :: err(m)