extended_line_search Subroutine

private subroutine extended_line_search(me, r, ro, rp, f, fo, fp, po, pp, fmin, fmax, rmin, rmax, tols, kd, ld, nit, kit, nred, mred, maxst, iest, inits, iters, kters, mes, isys)

extended line search without directional derivatives.

Method

safeguarded extrapolation and interpolation with extended termination criteria.

Note

This routine was formerly called ps0l02.

Type Bound

psqp_class

Arguments

Type IntentOptional Attributes Name
class(psqp_class), intent(inout) :: me
real(kind=wp) :: r

value of the stepsize parameter.

real(kind=wp) :: ro

initial value of the stepsize parameter.

real(kind=wp) :: rp

previous value of the stepsize parameter.

real(kind=wp) :: f

value of the objective function.

real(kind=wp) :: fo

initial value of the objective function.

real(kind=wp) :: fp

previous value of the objective function.

real(kind=wp) :: po

initial value of the directional derivative.

real(kind=wp) :: pp

previous value of the directional derivative.

real(kind=wp) :: fmin

lower bound for value of the objective function.

real(kind=wp) :: fmax

upper bound for value of the objective function.

real(kind=wp) :: rmin

minimum value of the stepsize parameter

real(kind=wp) :: rmax

maximum value of the stepsize parameter

real(kind=wp) :: tols

termination tolerance for line search (in test on the change of the function value).

integer :: kd

degree of required dervatives.

integer :: ld

degree of previously computed derivatives.

integer :: nit

actual number of iterations.

integer :: kit

number of the iteration after last restart.

integer :: nred

actual number of extrapolations or interpolations.

integer :: mred

maximum number of extrapolations or interpolations.

integer :: maxst

maximum stepsize indicator. maxst=0 or maxst=1 if maximum stepsize was not or was reached.

integer :: iest

lower bound specification. iest=0 or iest=1 if lower bound is not or is given.

integer :: inits

choice of the initial stepsize.

  • inits=0 - initial stepsize is specified in the calling program.
  • inits=1 - unit initial stepsize.
  • inits=2 - combined unit and quadratically estimated initial stepsize.
  • inits=3 - quadratically estimated initial stepsize.
integer :: iters

termination indicator.

  • iters=0 - zero step.
  • iters=1 - perfect line search.
  • iters=2 goldstein stepsize.
  • iters=3 - curry stepsize.
  • iters=4 - extended curry stepsize.
  • iters=5 - armijo stepsize.
  • iters=6 - first stepsize.
  • iters=7 - maximum stepsize.
  • iters=8 - unbounded function.
  • iters=-1 - mred reached.
  • iters=-2 - positive directional derivative.
  • iters=-3 - error in interpolation.
integer :: kters

termination selection.

  • kters=1 - perfect line search.
  • kters=2 - goldstein stepsize.
  • kters=3 - curry stepsize.
  • kters=4 - extended curry stepsize.
  • kters=5 - armijo stepsize.
  • kters=6 - first stepsize.
integer :: mes

method selection.

  • mes=1 - bisection.
  • mes=2 - quadratic interpolation (with one directional derivative).
  • mes=3 - quadratic interpolation (with two directional derivatives).
  • mes=4 - cubic interpolation.
  • mes=5 - conic interpolation.
integer :: isys

control parameter.


Calls

proc~~extended_line_search~~CallsGraph proc~extended_line_search psqp_class%extended_line_search proc~line_search_interpolation line_search_interpolation proc~extended_line_search->proc~line_search_interpolation

Called by

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

Source Code

   subroutine extended_line_search(me, r, ro, rp, f, fo, fp, po, pp, fmin, fmax, &
                                   rmin, rmax, tols, kd, ld, nit, kit, nred, mred, maxst, iest, &
                                   inits, iters, kters, mes, isys)

      class(psqp_class), intent(inout) :: me
      integer :: kd     !! degree of required dervatives.
      integer :: ld     !! degree of previously computed derivatives.
      integer :: nit    !! actual number of iterations.
      integer :: kit    !! number of the iteration after last restart.
      integer :: nred   !! actual number of extrapolations or interpolations.
      integer :: mred   !! maximum number of extrapolations or interpolations.
      integer :: maxst  !! maximum stepsize indicator. maxst=0 or maxst=1
                        !! if maximum stepsize was not or was reached.
      integer :: iest   !! lower bound specification. iest=0 or iest=1
                        !! if lower bound is not or is given.
      integer :: inits  !! choice of the initial stepsize.
                        !!
                        !! * inits=0 - initial stepsize is specified in the calling program.
                        !! * inits=1 - unit initial stepsize.
                        !! * inits=2 - combined unit and quadratically estimated initial stepsize.
                        !! * inits=3 - quadratically estimated initial stepsize.
      integer :: iters  !! termination indicator.
                        !!
                        !! * iters=0 - zero step.
                        !! * iters=1 - perfect line search.
                        !! * iters=2   goldstein stepsize.
                        !! * iters=3 - curry stepsize.
                        !! * iters=4 - extended curry stepsize.
                        !! * iters=5 - armijo stepsize.
                        !! * iters=6 - first stepsize.
                        !! * iters=7 - maximum stepsize.
                        !! * iters=8 - unbounded function.
                        !! * iters=-1 - mred reached.
                        !! * iters=-2 - positive directional derivative.
                        !! * iters=-3 - error in interpolation.
      integer :: kters  !! termination selection.
                        !!
                        !! * kters=1 - perfect line search.
                        !! * kters=2 - goldstein stepsize.
                        !! * kters=3 - curry stepsize.
                        !! * kters=4 - extended curry stepsize.
                        !! * kters=5 - armijo stepsize.
                        !! * kters=6 - first stepsize.
      integer :: mes    !! method selection.
                        !!
                        !! * mes=1 - bisection.
                        !! * mes=2 - quadratic interpolation (with one directional derivative).
                        !! * mes=3 - quadratic interpolation (with two directional derivatives).
                        !! * mes=4 - cubic interpolation.
                        !! * mes=5 - conic interpolation.
      integer :: isys   !! control parameter.
      real(wp) :: r     !! value of the stepsize parameter.
      real(wp) :: ro    !! initial value of the stepsize parameter.
      real(wp) :: rp    !! previous value of the stepsize parameter.
      real(wp) :: f     !! value of the objective function.
      real(wp) :: fo    !! initial value of the objective function.
      real(wp) :: fp    !! previous value of the objective function.
      real(wp) :: po    !! initial value of the directional derivative.
      real(wp) :: pp    !! previous value of the directional derivative.
      real(wp) :: fmin  !! lower bound for value of the objective function.
      real(wp) :: fmax  !! upper bound for value of the objective function.
      real(wp) :: rmin  !! minimum value of the stepsize parameter
      real(wp) :: rmax  !! maximum value of the stepsize parameter
      real(wp) :: tols  !! termination tolerance for line search
                        !! (in test on the change of the function value).

      real(wp) :: rtemp
      integer :: merr, init1
      logical :: l1, l2, l3, l4, l6, l7

      real(wp), parameter :: tol = 1.0d-4

      if (isys /= 1) then
         ! go to (1,3) isys+1
         me%mes1 = 2
         me%mes2 = 2
         iters = 0
         if (po >= 0.0_wp) then
            r = 0.0_wp
            iters = -2
            isys = 0
            return
         end if
         if (rmax <= 0.0_wp) then
            iters = 0
            isys = 0
            return
         end if
         ! initial stepsize selection
         if (inits > 0) then
            rtemp = fmin - f
         elseif (iest == 0) then
            rtemp = f - fp
         else
            rtemp = max(f - fp, 10.0_wp*(fmin - f))
         end if
         init1 = abs(inits)
         rp = 0.0_wp
         fp = fo
         pp = po
         if (init1 == 0) then
         elseif (init1 == 1 .or. inits >= 1 .and. iest == 0) then
            r = 1.0_wp
         elseif (init1 == 2) then
            r = min(1.0_wp, 4.0_wp*rtemp/po)
         elseif (init1 == 3) then
            r = min(1.0_wp, 2.0_wp*rtemp/po)
         elseif (init1 == 4) then
            r = 2.0_wp*rtemp/po
         end if
         rtemp = r
         r = max(r, rmin)
         r = min(r, rmax)
         me%mode = 0
         me%rl = 0.0_wp
         me%fl = fo
         me%ru = 0.0_wp
         me%fu = fo
         me%ri = 0.0_wp
         me%fi = fo
      elseif (iters /= 0) then
         isys = 0
         return
      else
         if (f <= fmin) then
            iters = 7
            isys = 0
            return
         else
            l1 = r <= rmin .and. nit /= kit
            l2 = r >= rmax
            l3 = f - fo <= tols*r*po .or. f - fmin <= (fo - fmin)/10.0_wp
            l4 = f - fo >= (1.0_wp - tols)*r*po .or. me%mes2 == 2 .and. me%mode == 2
            l6 = me%ru - me%rl <= tol*me%ru .and. me%mode == 2
            l7 = me%mes2 <= 2 .or. me%mode /= 0
            maxst = 0
            if (l2) maxst = 1
         end if
         ! test on termination
         if (l1 .and. .not. l3) then
            iters = 0
            isys = 0
            return
         elseif (l2 .and. .not. f >= me%fu) then
            iters = 7
            isys = 0
            return
         elseif (l6) then
            iters = 1
            isys = 0
            return
         elseif (l3 .and. l7 .and. kters == 5) then
            iters = 5
            isys = 0
            return
         elseif (l3 .and. l4 .and. l7 .and. &
                 (kters == 2 .or. kters == 3 .or. kters == 4)) then
            iters = 2
            isys = 0
            return
         elseif (kters < 0 .or. kters == 6 .and. l7) then
            iters = 6
            isys = 0
            return
         elseif (abs(nred) >= mred) then
            iters = -1
            isys = 0
            return
         else
            rp = r
            fp = f
            me%mode = max(me%mode, 1)
            me%mtyp = abs(mes)
            if (f >= fmax) me%mtyp = 1
         end if
         if (me%mode == 1) then
            ! interval change after extrapolation
            me%rl = me%ri
            me%fl = me%fi
            me%ri = me%ru
            me%fi = me%fu
            me%ru = r
            me%fu = f
            if (f >= me%fi) then
               nred = 0
               me%mode = 2
            elseif (me%mes1 == 1) then
               me%mtyp = 1
            end if
            ! interval change after interpolation
         elseif (r <= me%ri) then
            if (f <= me%fi) then
               me%ru = me%ri
               me%fu = me%fi
               me%ri = r
               me%fi = f
            else
               me%rl = r
               me%fl = f
            end if
         elseif (f <= me%fi) then
            me%rl = me%ri
            me%fl = me%fi
            me%ri = r
            me%fi = f
         else
            me%ru = r
            me%fu = f
         end if
      end if
      ! new stepsize selection (extrapolation or interpolation)
      call line_search_interpolation(ro, me%rl, me%ru, me%ri, fo, me%fl, me%fu, &
                                     me%fi, po, r, me%mode, me%mtyp, merr)
      if (merr > 0) then
         iters = -merr
         isys = 0
         return
      elseif (me%mode == 1) then
         nred = nred - 1
         r = min(r, rmax)
      elseif (me%mode == 2) then
         nred = nred + 1
      end if
      ! computation of the new function value
      kd = 0
      ld = -1
      isys = 1
   end subroutine extended_line_search