compute_con_and_dcon Subroutine

private subroutine compute_con_and_dcon(me, nf, nc, x, fc, cf, cl, cu, ic, gc, cg, cmax, kd, ld)

computation of the value and the gradient of the constraint function.

Note

This routine was formerly called pc1f01.

Type Bound

psqp_class

Arguments

Type IntentOptional Attributes Name
class(psqp_class), intent(inout) :: me
integer :: nf

number of variables.

integer :: nc

number of constraints.

real(kind=wp) :: x(nf)

x(nf) vector of variables.

real(kind=wp) :: fc

value of the selected constraint function.

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

cf(nc) vector containing values of constraint functions.

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

cl(nc) vector containing lower bounds for constraint functions.

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

cu(nc) vector containing upper bounds for constraint functions.

integer :: ic(*)

ic(nc) vector containing types of constraints.

real(kind=wp) :: gc(nf)

gc(nf) gradient of the selected constraint function.

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

cg(nf*nc) matrix whose columns are gradients of constraint functions.

real(kind=wp) :: cmax

maximum constraint violation.

integer :: kd

degree of required derivatives.

integer :: ld

degree of previously computed derivatives.


Calls

proc~~compute_con_and_dcon~~CallsGraph proc~compute_con_and_dcon psqp_class%compute_con_and_dcon proc~mxvcop mxvcop proc~compute_con_and_dcon->proc~mxvcop

Called by

proc~~compute_con_and_dcon~~CalledByGraph proc~compute_con_and_dcon psqp_class%compute_con_and_dcon proc~psqp psqp_class%psqp proc~psqp->proc~compute_con_and_dcon proc~psqpn psqp_class%psqpn proc~psqpn->proc~psqp

Source Code

   subroutine compute_con_and_dcon(me, nf, nc, x, fc, cf, cl, cu, ic, gc, cg, cmax, kd, ld)

      class(psqp_class), intent(inout) :: me
      real(wp) :: fc      !! value of the selected constraint function.
      real(wp) :: cmax    !! maximum constraint violation.
      integer  :: kd      !! degree of required derivatives.
      integer  :: ld      !! degree of previously computed derivatives.
      integer  :: nc      !! number of constraints.
      integer  :: nf      !! number of variables.
      real(wp) :: cf(*)   !! cf(nc) vector containing values of constraint functions.
      real(wp) :: cl(*)   !! cl(nc) vector containing lower bounds for constraint functions.
      real(wp) :: cu(*)   !! cu(nc) vector containing upper bounds for constraint functions.
      integer  :: ic(*)   !! ic(nc) vector containing types of constraints.
      real(wp) :: gc(nf)  !! gc(nf) gradient of the selected constraint function.
      real(wp) :: cg(*)   !! cg(nf*nc) matrix whose columns are gradients of constraint functions.
      real(wp) :: x(nf)   !! x(nf) vector of variables.

      real(wp) :: pom, temp
      integer :: kc

      if (kd <= ld) return
      if (ld < 0) cmax = 0.0_wp
      do kc = 1, nc
         if (kd >= 0) then
            if (ld < 0) then
               call me%con(nf, kc, x, fc)
               cf(kc) = fc
               if (ic(kc) > 0) then
                  pom = 0.0_wp
                  temp = cf(kc)
                  if (ic(kc) == 1 .or. ic(kc) >= 3) pom = min(pom, temp - cl(kc))
                  if (ic(kc) == 2 .or. ic(kc) >= 3) pom = min(pom, cu(kc) - temp)
                  if (pom < 0.0_wp) cmax = max(cmax, -pom)
               end if
            else
               fc = cf(kc)
            end if
            if (kd >= 1) then
               if (ld >= 1) then
                  call mxvcop(nf, cg((kc - 1)*nf + 1), gc)
               else
                  call me%dcon(nf, kc, x, gc)
                  call mxvcop(nf, gc, cg((kc - 1)*nf + 1))
               end if
            end if
         end if
      end do
      ld = kd

   end subroutine compute_con_and_dcon