dvevtr Subroutine

public pure subroutine dvevtr(m, nq, indx, v, ldv, ld2v, e, lde, ve, ldve, ld2ve, vev, ldvev, wrk5)

Uses

  • proc~~dvevtr~~UsesGraph proc~dvevtr dvevtr module~odrpack_kinds odrpack_kinds proc~dvevtr->module~odrpack_kinds iso_fortran_env iso_fortran_env module~odrpack_kinds->iso_fortran_env

Compute v*e*trans(v) for the (indx)th m by nq array in v.

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: m

The number of columns of data in the independent variable.

integer, intent(in) :: nq

The number of responses per observation.

integer, intent(in) :: indx

The row in v in which the m by nq array is stored.

real(kind=wp), intent(in) :: v(ldv,ld2v,nq)

An array of nq by m matrices.

integer, intent(in) :: ldv

The leading dimension of array v.

integer, intent(in) :: ld2v

The second dimension of array v.

real(kind=wp), intent(in) :: e(lde,m)

The m by m matrix of the factors, so ete = (d**2 + alpha*t**2).

integer, intent(in) :: lde

The leading dimension of array e.

real(kind=wp), intent(out) :: ve(ldve,ld2ve,m)

The nq by m array ve = v * inv(e).

integer, intent(in) :: ldve

The leading dimension of array ve.

integer, intent(in) :: ld2ve

The second dimension of array ve.

real(kind=wp), intent(out) :: vev(ldvev,nq)

The nq by nq array vev = v * inv(ete) * trans(v).

integer, intent(in) :: ldvev

The leading dimension of array vev.

real(kind=wp), intent(out) :: wrk5(m)

An m work vector.


Calls

proc~~dvevtr~~CallsGraph proc~dvevtr dvevtr proc~dsolve dsolve proc~dvevtr->proc~dsolve interface~daxpy daxpy proc~dsolve->interface~daxpy interface~ddot ddot proc~dsolve->interface~ddot

Called by

proc~~dvevtr~~CalledByGraph proc~dvevtr dvevtr proc~dodstp dodstp proc~dodstp->proc~dvevtr proc~dodlm dodlm proc~dodlm->proc~dodstp proc~dodvcv dodvcv proc~dodvcv->proc~dodstp proc~dodmn dodmn proc~dodmn->proc~dodlm proc~dodmn->proc~dodvcv proc~doddrv doddrv proc~doddrv->proc~dodmn 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
integer, public :: j
integer, public :: l1
integer, public :: l2

Source Code

   pure subroutine dvevtr &
      (m, nq, indx, &
       v, ldv, ld2v, e, lde, ve, ldve, ld2ve, vev, ldvev, &
       wrk5)
   !! Compute `v*e*trans(v)` for the (`indx`)th `m` by `nq` array in `v`.
      ! Routines Called  DSOLVE
      ! Date Written   910613   (YYMMDD)
      ! Revision Date  920304   (YYMMDD)

      use odrpack_kinds, only: zero

      integer, intent(in) :: m
         !! The number of columns of data in the independent variable.
      integer, intent(in) :: nq
         !! The number of responses per observation.
      integer, intent(in) :: indx
         !! The row in `v` in which the `m` by `nq` array is stored.
      integer, intent(in) :: ldv
         !! The leading dimension of array `v`.
      integer, intent(in) :: ld2v
         !! The second dimension of array `v`.
      integer, intent(in) :: lde
         !! The leading dimension of array `e`.
      integer, intent(in) :: ldve
         !! The leading dimension of array `ve`.
      integer, intent(in) :: ldvev
         !! The leading dimension of array `vev`.
      integer, intent(in) :: ld2ve
         !! The second dimension of array `ve`.
      real(wp), intent(in) :: v(ldv, ld2v, nq)
         !! An array of `nq` by `m` matrices.
      real(wp), intent(in) :: e(lde, m)
         !! The `m` by `m` matrix of the factors, so `ete = (d**2 + alpha*t**2)`.
      real(wp), intent(out) :: ve(ldve, ld2ve, m)
         !! The `nq` by `m` array `ve = v * inv(e)`.
      real(wp), intent(out) :: vev(ldvev, nq)
         !! The `nq` by `nq` array `vev = v * inv(ete) * trans(v)`.
      real(wp), intent(out) :: wrk5(m)
         !! An `m` work vector.

      ! Local scalars
      integer :: j, l1, l2

      ! Variable Definitions (alphabetically)
      !  INDX:    The row in V in which the M by NQ array is stored.
      !  J:       An indexing variable.
      !  LDE:     The leading dimension of array E.
      !  LDV:     The leading dimension of array V.
      !  LDVE:    The leading dimension of array VE.
      !  LDVEV:   The leading dimension of array VEV.
      !  LD2V:    The second dimension of array V.
      !  L1:      An indexing variable.
      !  L2:      An indexing variable.
      !  M:       The number of columns of data in the independent variable.
      !  NQ:      The number of responses per observation.
      !  E:       The M by M matrix of the factors so ETE = (D**2 + ALPHA*T**2).
      !  V:       An array of NQ by M matrices.
      !  VE:      The NQ by M array VE = V * inv(E)
      !  VEV:     The NQ by NQ array VEV = V * inv(ETE) * trans(V).
      !  WRK5:    An M work vector.

      if (nq == 0 .or. m == 0) return

      do l1 = 1, nq
         do j = 1, m
            wrk5(j) = v(indx, j, l1)
         end do
         call dsolve(m, e, lde, wrk5, 4)
         do j = 1, m
            ve(indx, l1, j) = wrk5(j)
         end do
      end do

      do l1 = 1, nq
         do l2 = 1, l1
            vev(l1, l2) = zero
            do j = 1, m
               vev(l1, l2) = vev(l1, l2) + ve(indx, l1, j)*ve(indx, l2, j)
            end do
            vev(l2, l1) = vev(l1, l2)
         end do
      end do

   end subroutine dvevtr