update_tri_decomp_general Subroutine

private subroutine update_tri_decomp_general(nf, n, ica, cg, cr, h, s, g, eps7, gmax, umax, idecf, inew, nadd, ier, job)

triangular decomposition of kernel of the general projection is updated after constraint addition.

Note

This routine was formerly called pladr1.

Arguments

Type IntentOptional Attributes Name
integer :: nf

declared number of variables.

integer :: n

actual number of variables.

integer :: ica(*)

ica(nf) vector containing indices of active constraints.

real(kind=wp) :: cg(*)

cg(nf*nc) matrix whose columns are normals of the linear constraints.

real(kind=wp) :: cr(*)

cr(nf*(nf+1)/2) triangular decomposition of kernel of the orthogonal projection.

real(kind=wp) :: h(*)

h(nf*(nf+1)/2) triangular decomposition or inversion of the hessian matrix approximation.

real(kind=wp) :: s(*)

s(nf) auxiliary vector.

real(kind=wp) :: g(*)

g(nf) vector used in the dual range space quadratic programming method.

real(kind=wp) :: eps7

tolerance for linear independence of constraints.

real(kind=wp) :: gmax

maximum absolute value of a partial derivative.

real(kind=wp) :: umax

maximum absolute value of a negative lagrange multiplier.

integer :: idecf

decomposition indicator.

  • idecf=0-no decomposition.
  • idecf=1-gill-murray decomposition.
  • idecf=9-inversion.
  • idecf=10-diagonal matrix.
integer :: inew

index of the new active constraint.

integer :: nadd

number of constraint additions.

integer :: ier

error indicator.

integer :: job

specification of computation. output vector g is not or is computed in case when n<=0 if job=0 or job=1 respectively.


Calls

proc~~update_tri_decomp_general~~CallsGraph proc~update_tri_decomp_general update_tri_decomp_general proc~mxdpgb mxdpgb proc~update_tri_decomp_general->proc~mxdpgb proc~mxdprb mxdprb proc~update_tri_decomp_general->proc~mxdprb proc~mxdsmm mxdsmm proc~update_tri_decomp_general->proc~mxdsmm proc~mxdsmv mxdsmv proc~update_tri_decomp_general->proc~mxdsmv proc~mxvcop mxvcop proc~update_tri_decomp_general->proc~mxvcop proc~mxvdot mxvdot proc~update_tri_decomp_general->proc~mxvdot proc~mxvset mxvset proc~update_tri_decomp_general->proc~mxvset

Called by

proc~~update_tri_decomp_general~~CalledByGraph proc~update_tri_decomp_general update_tri_decomp_general proc~dual_range_space_quad_prog psqp_class%dual_range_space_quad_prog proc~dual_range_space_quad_prog->proc~update_tri_decomp_general proc~psqp psqp_class%psqp proc~psqp->proc~dual_range_space_quad_prog proc~psqpn psqp_class%psqpn proc~psqpn->proc~psqp

Source Code

   subroutine update_tri_decomp_general(nf, n, ica, cg, cr, h, s, g, eps7, &
                                        gmax, umax, idecf, inew, nadd, ier, job)

      integer :: nf       !! declared number of variables.
      integer :: n        !! actual number of variables.
      integer :: ica(*)   !! ica(nf)  vector containing indices of active constraints.
      integer :: idecf    !! decomposition indicator.
                          !!
                          !! * idecf=0-no decomposition.
                          !! * idecf=1-gill-murray decomposition.
                          !! * idecf=9-inversion.
                          !! * idecf=10-diagonal matrix.
      integer :: inew     !! index of the new active constraint.
      integer :: nadd     !! number of constraint additions.
      integer :: ier      !! error indicator.
      integer :: job      !! specification of computation.
                          !! output vector g is not or is
                          !! computed in case when n<=0 if
                          !! job=0 or job=1 respectively.
      real(wp) :: cg(*)   !! cg(nf*nc)  matrix whose columns are normals of
                          !! the linear constraints.
      real(wp) :: cr(*)   !! cr(nf*(nf+1)/2)  triangular decomposition of
                          !! kernel of the orthogonal projection.
      real(wp) :: h(*)    !! h(nf*(nf+1)/2)  triangular decomposition or
                          !! inversion of the hessian matrix approximation.
      real(wp) :: s(*)    !! s(nf)  auxiliary vector.
      real(wp) :: g(*)    !! g(nf)  vector used in the dual range space
                          !! quadratic programming method.
      real(wp) :: eps7    !! tolerance for linear independence of constraints.
      real(wp) :: gmax    !! maximum absolute value of a partial derivative.
      real(wp) :: umax    !! maximum absolute value of a negative
                          !! lagrange multiplier.

      integer :: nca, ncr, jcg, j, k, l

      ier = 0
      if (job == 0 .and. n <= 0) ier = 2
      if (inew == 0) ier = 3
      if (idecf /= 1 .and. idecf /= 9) ier = -2
      if (ier /= 0) return
      nca = nf - n
      ncr = nca*(nca + 1)/2
      if (inew > 0) then
         jcg = (inew - 1)*nf + 1
         if (idecf == 1) then
            call mxvcop(nf, cg(jcg), s)
            call mxdpgb(nf, h, s, 0)
         else
            call mxdsmm(nf, h, cg(jcg), s)
         end if
         gmax = mxvdot(nf, cg(jcg), s)
      else
         k = -inew
         if (idecf == 1) then
            call mxvset(nf, 0.0_wp, s)
            s(k) = 1.0_wp
            call mxdpgb(nf, h, s, 0)
         else
            call mxdsmv(nf, h, s, k)
         end if
         gmax = s(k)
      end if
      do j = 1, nca
         l = ica(j)
         if (l > 0) then
            g(j) = mxvdot(nf, cg((l - 1)*nf + 1), s)
         else
            l = -l
            g(j) = s(l)
         end if
      end do
      if (n == 0) then
         call mxdprb(nca, cr, g, 1)
         umax = 0.0_wp
         ier = 2
         return
      elseif (nca == 0) then
         umax = gmax
      else
         call mxdprb(nca, cr, g, 1)
         umax = gmax - mxvdot(nca, g, g)
         call mxvcop(nca, g, cr(ncr + 1))
      end if
      if (umax <= eps7*gmax) then
         ier = 1
         return
      else
         nca = nca + 1
         ncr = ncr + nca
         ica(nca) = inew
         cr(ncr) = sqrt(umax)
         if (job == 0) then
            n = n - 1
            nadd = nadd + 1
         end if
      end if

   end subroutine update_tri_decomp_general