fsolve_hybrj_sub Subroutine

subroutine fsolve_hybrj_sub(func, dfunc, x, tol, info, check)

Arguments

Type IntentOptional Attributes Name
subroutine func(x, f)
Arguments
Type IntentOptional Attributes Name
real(kind=8), intent(in), dimension(:) :: x
real(kind=8), dimension(size(x)) :: f
subroutine dfunc(x, df)
Arguments
Type IntentOptional Attributes Name
real(kind=8), intent(in), dimension(:) :: x
real(kind=8), dimension(size(x),size(x)) :: df
real(kind=8), dimension(:) :: x
real(kind=8), optional :: tol
integer, optional :: info
logical, optional :: check

Calls

proc~~fsolve_hybrj_sub~~CallsGraph proc~fsolve_hybrj_sub fsolve_hybrj_sub hybrj1 hybrj1 proc~fsolve_hybrj_sub->hybrj1

Source Code

subroutine fsolve_hybrj_sub(func,dfunc,x,tol,info,check)
  interface
     subroutine func(x,f)
       real(8),dimension(:),intent(in) :: x
       real(8),dimension(size(x))      :: f
     end subroutine func
     !
     subroutine dfunc(x,df)
       real(8),dimension(:),intent(in)    :: x
       real(8),dimension(size(x),size(x)) :: df
     end subroutine dfunc
  end interface
  real(8),dimension(:)               :: x      
  real(8),optional                   :: tol
  integer,optional                   :: info
  real(8)                            :: tol_
  integer                            :: info_
  logical,optional                   :: check
  logical                            :: check_
  integer                            :: n
  real(8),dimension(size(x))         :: fvec
  real(8),dimension(size(x),size(x)) :: fjac
  tol_ = 1.d-15;if(present(tol))tol_=tol
  check_=.true.;if(present(check))check_=check
  n=size(x)
  call hybrj1(fsolve_hybrj1_sub2sub,n,x,fvec,fjac,n,tol_,info_)
  if(present(info))info=info_
  if(check_)then
     include "fsolve_error.h90"
  endif
contains
  subroutine fsolve_hybrj1_sub2sub(n,x,fvec,fjac,ldfjac,iflag)
    integer ::  n
    real(8) ::  x(n)
    real(8) ::  fvec(n)
    integer ::  ldfjac
    real(8) ::  fjac(ldfjac,n)
    integer ::  iflag
    if(iflag==1)then
       call func(x,fvec)
    elseif(iflag==2)then
       call dfunc(x,fjac)
    endif
    if(iflag<0)stop "FSOLVE_HYBRJ1_sub2sub ERROR: iflag < 0 "
  end subroutine fsolve_hybrj1_sub2sub
end subroutine fsolve_hybrj_sub