dpvd Subroutine

public subroutine dpvd(fcn, n, m, np, nq, beta, xplusd, ifixb, ifixx, ldifx, nrow, j, lq, stp, istop, nfev, pvd, wrk1, wrk2, wrk6)

Compute nrow-th function value using x(nrow, j) + delta(nrow, j) + stp.

Arguments

Type IntentOptional Attributes Name
procedure(fcn_t) :: fcn

The user-supplied subroutine for evaluating the model.

integer, intent(in) :: n

The number of observations.

integer, intent(in) :: m

The number of columns of data in the independent variable.

integer, intent(in) :: np

The number of function parameters.

integer, intent(in) :: nq

The number of responses per observation.

real(kind=wp), intent(in) :: beta(np)

The function parameters.

real(kind=wp), intent(inout) :: xplusd(n,m)

The values of x + delta.

integer, intent(in) :: ifixb(np)

The values designating whether the elements of beta are fixed at their input values or not.

integer, intent(in) :: ifixx(ldifx,m)

The values designating whether the elements of x are fixed at their input values or not.

integer, intent(in) :: ldifx

The leading dimension of array ifixx.

integer, intent(in) :: nrow

The row number of the independent variable array at which the derivative is to be checked.

integer, intent(in) :: j

The index of the partial derivative being examined.

integer, intent(in) :: lq

The response currently being examined.

real(kind=wp), intent(in) :: stp

The step size for the finite difference derivative.

integer, intent(out) :: istop

The variable designating whether there are problems computing the function at the current beta and delta.

integer, intent(inout) :: nfev

The number of function evaluations.

real(kind=wp), intent(out) :: pvd

The function value for the selected observation & response.

real(kind=wp), intent(out) :: wrk1(n,m,nq)

Work array.

real(kind=wp), intent(out) :: wrk2(n,nq)

Work array.

real(kind=wp), intent(out) :: wrk6(n,np,nq)

Work array.


Called by

proc~~dpvd~~CalledByGraph proc~dpvd dpvd proc~djckc djckc proc~djckc->proc~dpvd proc~djckf djckf proc~djckc->proc~djckf proc~djckf->proc~dpvd proc~djckm djckm proc~djckm->proc~dpvd proc~djckm->proc~djckc proc~djckz djckz proc~djckm->proc~djckz proc~djckz->proc~dpvd proc~djck djck proc~djck->proc~djckm proc~doddrv doddrv proc~doddrv->proc~djck proc~dodcnt dodcnt proc~dodcnt->proc~doddrv proc~odr odr proc~odr->proc~dodcnt proc~odr_long_c odr_long_c proc~odr_long_c->proc~odr proc~odr_medium_c odr_medium_c proc~odr_medium_c->proc~odr proc~odr_short_c odr_short_c proc~odr_short_c->proc~odr program~example1 example1 program~example1->proc~odr program~example2 example2 program~example2->proc~odr program~example3 example3 program~example3->proc~odr program~example4 example4 program~example4->proc~odr program~example5 example5 program~example5->proc~odr

Variables

Type Visibility Attributes Name Initial
real(kind=wp), public :: xpdj

Source Code

   subroutine dpvd &
      (fcn, &
       n, m, np, nq, &
       beta, xplusd, ifixb, ifixx, ldifx, &
       nrow, j, lq, stp, &
       istop, nfev, pvd, &
       wrk1, wrk2, wrk6)
   !! Compute `nrow`-th function value using `x(nrow, j) + delta(nrow, j) + stp`.
      ! Routines Called FCN
      ! Date Written   860529   (YYMMDD)
      ! Revision Date  920304   (YYMMDD)

      procedure(fcn_t) :: fcn
         !! The user-supplied subroutine for evaluating the model.
      integer, intent(in) :: n
         !! The number of observations.
      integer, intent(in) :: m
         !! The number of columns of data in the independent variable.
      integer, intent(in) :: np
         !! The number of function parameters.
      integer, intent(in) :: nq
         !! The number of responses per observation.
      real(wp), intent(in) :: beta(np)
         !! The function parameters.
      real(wp), intent(inout) :: xplusd(n, m)
         !! The values of `x + delta`.
      integer, intent(in) :: ifixb(np)
         !! The values designating whether the elements of `beta` are fixed at their input values or not.
      integer, intent(in) :: ifixx(ldifx, m)
         !! The values designating whether the elements of `x` are fixed at their input values or not.
      integer, intent(in) :: ldifx
         !! The leading dimension of array `ifixx`.
      integer, intent(in) :: nrow
         !! The row number of the independent variable array at which the derivative is to be checked.
      integer, intent(in) :: j
         !! The index of the partial derivative being examined.
      integer, intent(in) :: lq
         !! The response currently being examined.
      real(wp), intent(in) :: stp
         !! The step size for the finite difference derivative.
      integer, intent(out) :: istop
         !! The variable designating whether there are problems computing the function at the
         !! current `beta` and `delta`.
      integer, intent(inout) :: nfev
         !! The number of function evaluations.
      real(wp), intent(out) :: pvd
         !! The function value for the selected observation & response.
      real(wp), intent(out) :: wrk1(n, m, nq)
         !! Work array.
      real(wp), intent(out) :: wrk2(n, nq)
         !! Work array.
      real(wp), intent(out) :: wrk6(n, np, nq)
         !! Work array.

      ! Local scalars
      real(wp) :: xpdj

      ! Variable Definitions (alphabetically)
      !  BETA:    The function parameters.
      !  FCN:     The user-supplied subroutine for evaluating the model.
      !  IFIXB:   The values designating whether the elements of BETA are
      !           fixed at their input values or not.
      !  IFIXX:   The values designating whether the elements of X are fixed at their input values or not.
      !  ISTOP:   The variable designating whether there are problems
      !           computing the function at the current BETA and DELTA.
      !  J:       The index of the partial derivative being examined.
      !  LDIFX:   The leading dimension of array IFIXX.
      !  LQ:      The response currently being examined.
      !  M:       The number of columns of data in the independent variable.
      !  N:       The number of observations.
      !  NFEV:    The number of function evaluations.
      !  NP:      The number of function parameters.
      !  NQ:      The number of responses per observation.
      !  NROW:    The row number of the independent variable array at which the derivative is to be checked.
      !  PVD:     The function value for the selected observation & response.
      !  STP:     The step size for the finite difference derivative.
      !  XPDJ:    The (NROW,J)th element of XPLUSD.
      !  XPLUSD:  The values of X + DELTA.

      xpdj = xplusd(nrow, j)
      xplusd(nrow, j) = xplusd(nrow, j) + stp
      istop = 0
      call fcn(n, m, np, nq, &
               n, m, np, &
               beta, xplusd, &
               ifixb, ifixx, ldifx, &
               003, wrk2, wrk6, wrk1, &
               istop)
      if (istop == 0) then
         nfev = nfev + 1
      else
         return
      end if
      xplusd(nrow, j) = xpdj

      pvd = wrk2(nrow, lq)

   end subroutine dpvd