SECTION 1.9 OPTIMIZATION OVER A SUBSET OF VARIABLES

It is sometimes desirable to optimize with respect to a subset of the variables over which a function is defined. If this were desired, the function subroutine would have to be rewritten for each separate suboptimization. Since this is very inconvenient, the procedure described below allows the user to carry out suboptimization with respect to any subset of variables using a given, previously defined function subroutine.

1. In the MAIN program, the user should include the following statements:

      EXTERNAL PERM
      COMMON/BPRM/IPRM(np)
C where np should be replaced by the the number of variables
C in the complete set of variables
      COMMON/BPRM2/XPRM(np) . . . .
      NP = number of variables in full set.
      NPE = number of effective variables of optimization.
      IF (NP-NPE.LE.0) STOP
      IPRM(1) =
C see 3 below for how to set values of IPRM . .
      IPRM(NP) =
      X(1) =
C see 4a below for how to set values of X
      . . .
      X(NP) =
      . . .
      CALL LABEL(ALABEL,NP) or other labeling
      CALL PRMCHK(NP,X,ALABEL,iflag,*nn)
C nn -- error return iflag -- see 4a below
      CALL OPT(X, NPE, ..., PERM, ALABEL)

2. In addition the user must include the following routine:

      SUBROUTINE PERM (A,NPE,FU0,*)
      IMPLICIT REAL*8 (A-H,O-Z)
      EXTERNAL func
C func = actual function name
      DIMENSION A(np)
C np = number of variables in full set
      CALL PERM1(A,np,NPE,FU0,*10,func)
      RETURN
10    RETURN 1
      END 

3. The array IPRM represents a permutation of the variables. The variable indices in the first NPE positions of IPRM will be the ones with respect to which optimization is performed. Thus, if NP=5, NPE=3 and IPRM is filled with the permutation 1,5,4,2,3, optimization will be performed with respect to X(1), X(5), and X(4). NPE may be in the range 1 to NP-1. The call to PRMCHK checks that a valid permutation has been placed in IPRM and copies the unpermuted starting point into XPRM. It should immediately precede the call to OPT. The call to OPT should use NPE as the number of variables and PERM as the function. The real function name is placed in subroutine PERM. Clearly, the user can not name his own function "PERM".

4. Notes on arrays which may or may not be permuted:

(a) The variables and labels must be permuted before calling OPT. If IFLAG = 0, PRMCHK assumes the arrays are already permuted. One way to permute an array is as follows:

      DO I = 1,NP
      Y(I) = X(IPRM(I))
      END DO
      DO I = 1,NP
      X(I) = Y(I)
      END DO

This demonstrates what it means for an array to be permuted. If IFLAG = 1, permutation will be done automatically. For example, if IFLAG = 1, IPRM = 1,5,4,2,3, and NPE = 3, X(2) and X(3) should contain the values at which they are to be held constant. X(1), X(4), and X(5) should contain starting values. Upon leaving PRMCHK, the array will be permuted. Most users will want to use the IFLAG = 1 option. In this case, they can set up X and ALABEL in the normal way and PRMCHK will do all the necessary manipulations. The IFLAG = 0 option is provided primarily for users who wish to use one optimization method followed immediately by another optimization method. Since all arrays are permuted upon leaving OPT, the PRMCHK for the second optimization can be done with IFLAG = 0. This is probably the only case in which IFLAG = 0 would be useful. PRMCHK must always be called immediately before a call to OPT. If an error is found in the permutation, PRMCHK does not change any array and returns to an error return statement.

(b) In OPT, all arrays are permuted, included those which the user can obtain with OPTOUT or OPTMOV, or those intermediate variable values printed during optimization. Function calls to PERM and numerical derivatives will be correct, because they use the real values. Any analytic derivatives must take account of the permutation. Note that in a permuted array, the value of real element i is found in element j, where IPRM(j) = i. Extreme care must be used when analytic derivatives are used. First, to get the value of any real variable i (which is not being held constant), one must look in element j of the variable array, where IPRM(j) = i. The values of any variables which are being held constant are only available from array XPRM, the unpermuted copy of the starting point made by PRMCHK. Also, the partials which are returned must be permuted. The following is probably the best way of computing analytic first partial derivatives:

      SUBROUTINE FP(X,NPE,F,FPD,FUNC)
      IMPLICIT REAL*8 (A-H,O-Z)
      DIMENSION X(NPE),FPD(NPE)
      DIMENSION FPD0(np)
C np = real number of variables
      COMMON/BPRM/IPRM(np)
      COMMON/BPRM2/XPRM(np)
C Unpermute variables not being held constant, and put them in XPRM (only those
C variables in XPRM which are held constant may not be changed by the user)
      DO I = 1, NPE
      XPRM(IPRM(I)) = X(I)
      END DO
C
C Do calculation of first partials. Values of the real variables may be found
C in XPRM.
C Place the first partials in array FPD0.
C
C Permute first partials.
      DO I = 1, NPE
      FPD(I) = FPD0(IPRM(I))
      END DO
      RETURN
      END 

For second partials, we would have:

      DO I = 1,NPE
      DO J = 1,NPE
      SPD(I,J)=SPD0(IPRM(I),IPRM(J))
      END DO
      END DO

Note again the meaning of the word "permute". All arrays used by OPT, or available from OPTMOV or OPTOUT, are permuted.

(c) X will remain in permuted order upon exit from OPT. Since the labels are also permuted, the labelled optimal point (produced by OPT) will be correct.

Return to
|Sect. 1.1|Sect. 1.11|Sect. 1.12|Sect. 14.1|Beginning|