bobyqa.f 5.4 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129
  1. SUBROUTINE BOBYQA (N,NPT,X,XL,XU,RHOBEG,RHOEND,IPRINT,
  2. 1 MAXFUN,W)
  3. IMPLICIT REAL*8 (A-H,O-Z)
  4. DIMENSION X(*),XL(*),XU(*),W(*)
  5. C
  6. C This subroutine seeks the least value of a function of many variables,
  7. C by applying a trust region method that forms quadratic models by
  8. C interpolation. There is usually some freedom in the interpolation
  9. C conditions, which is taken up by minimizing the Frobenius norm of
  10. C the change to the second derivative of the model, beginning with the
  11. C zero matrix. The values of the variables are constrained by upper and
  12. C lower bounds. The arguments of the subroutine are as follows.
  13. C
  14. C N must be set to the number of variables and must be at least two.
  15. C NPT is the number of interpolation conditions. Its value must be in
  16. C the interval [N+2,(N+1)(N+2)/2]. Choices that exceed 2*N+1 are not
  17. C recommended.
  18. C Initial values of the variables must be set in X(1),X(2),...,X(N). They
  19. C will be changed to the values that give the least calculated F.
  20. C For I=1,2,...,N, XL(I) and XU(I) must provide the lower and upper
  21. C bounds, respectively, on X(I). The construction of quadratic models
  22. C requires XL(I) to be strictly less than XU(I) for each I. Further,
  23. C the contribution to a model from changes to the I-th variable is
  24. C damaged severely by rounding errors if XU(I)-XL(I) is too small.
  25. C RHOBEG and RHOEND must be set to the initial and final values of a trust
  26. C region radius, so both must be positive with RHOEND no greater than
  27. C RHOBEG. Typically, RHOBEG should be about one tenth of the greatest
  28. C expected change to a variable, while RHOEND should indicate the
  29. C accuracy that is required in the final values of the variables. An
  30. C error return occurs if any of the differences XU(I)-XL(I), I=1,...,N,
  31. C is less than 2*RHOBEG.
  32. C The value of IPRINT should be set to 0, 1, 2 or 3, which controls the
  33. C amount of printing. Specifically, there is no output if IPRINT=0 and
  34. C there is output only at the return if IPRINT=1. Otherwise, each new
  35. C value of RHO is printed, with the best vector of variables so far and
  36. C the corresponding value of the objective function. Further, each new
  37. C value of F with its variables are output if IPRINT=3.
  38. C MAXFUN must be set to an upper bound on the number of calls of CALFUN.
  39. C The array W will be used for working space. Its length must be at least
  40. C (NPT+5)*(NPT+N)+3*N*(N+5)/2.
  41. C
  42. C SUBROUTINE CALFUN (N,X,F) has to be provided by the user. It must set
  43. C F to the value of the objective function for the current values of the
  44. C variables X(1),X(2),...,X(N), which are generated automatically in a
  45. C way that satisfies the bounds given in XL and XU.
  46. C
  47. C Return if the value of NPT is unacceptable.
  48. C
  49. NP=N+1
  50. IF (NPT .LT. N+2 .OR. NPT .GT. ((N+2)*NP)/2) THEN
  51. PRINT 10
  52. 10 FORMAT (/4X,'Return from BOBYQA because NPT is not in',
  53. 1 ' the required interval')
  54. GO TO 40
  55. END IF
  56. C
  57. C Partition the working space array, so that different parts of it can
  58. C be treated separately during the calculation of BOBYQB. The partition
  59. C requires the first (NPT+2)*(NPT+N)+3*N*(N+5)/2 elements of W plus the
  60. C space that is taken by the last array in the argument list of BOBYQB.
  61. C
  62. NDIM=NPT+N
  63. IXB=1
  64. IXP=IXB+N
  65. IFV=IXP+N*NPT
  66. IXO=IFV+NPT
  67. IGO=IXO+N
  68. IHQ=IGO+N
  69. IPQ=IHQ+(N*NP)/2
  70. IBMAT=IPQ+NPT
  71. IZMAT=IBMAT+NDIM*N
  72. ISL=IZMAT+NPT*(NPT-NP)
  73. ISU=ISL+N
  74. IXN=ISU+N
  75. IXA=IXN+N
  76. ID=IXA+N
  77. IVL=ID+N
  78. IW=IVL+NDIM
  79. C
  80. C Return if there is insufficient space between the bounds. Modify the
  81. C initial X if necessary in order to avoid conflicts between the bounds
  82. C and the construction of the first quadratic model. The lower and upper
  83. C bounds on moves from the updated X are set now, in the ISL and ISU
  84. C partitions of W, in order to provide useful and exact information about
  85. C components of X that become within distance RHOBEG from their bounds.
  86. C
  87. ZERO=0.0D0
  88. DO 30 J=1,N
  89. TEMP=XU(J)-XL(J)
  90. IF (TEMP .LT. RHOBEG+RHOBEG) THEN
  91. PRINT 20
  92. 20 FORMAT (/4X,'Return from BOBYQA because one of the',
  93. 1 ' differences XU(I)-XL(I)'/6X,' is less than 2*RHOBEG.')
  94. GO TO 40
  95. END IF
  96. JSL=ISL+J-1
  97. JSU=JSL+N
  98. W(JSL)=XL(J)-X(J)
  99. W(JSU)=XU(J)-X(J)
  100. IF (W(JSL) .GE. -RHOBEG) THEN
  101. IF (W(JSL) .GE. ZERO) THEN
  102. X(J)=XL(J)
  103. W(JSL)=ZERO
  104. W(JSU)=TEMP
  105. ELSE
  106. X(J)=XL(J)+RHOBEG
  107. W(JSL)=-RHOBEG
  108. W(JSU)=DMAX1(XU(J)-X(J),RHOBEG)
  109. END IF
  110. ELSE IF (W(JSU) .LE. RHOBEG) THEN
  111. IF (W(JSU) .LE. ZERO) THEN
  112. X(J)=XU(J)
  113. W(JSL)=-TEMP
  114. W(JSU)=ZERO
  115. ELSE
  116. X(J)=XU(J)-RHOBEG
  117. W(JSL)=DMIN1(XL(J)-X(J),-RHOBEG)
  118. W(JSU)=RHOBEG
  119. END IF
  120. END IF
  121. 30 CONTINUE
  122. C
  123. C Make the call of BOBYQB.
  124. C
  125. CALL BOBYQB (N,NPT,X,XL,XU,RHOBEG,RHOEND,IPRINT,MAXFUN,W(IXB),
  126. 1 W(IXP),W(IFV),W(IXO),W(IGO),W(IHQ),W(IPQ),W(IBMAT),W(IZMAT),
  127. 2 NDIM,W(ISL),W(ISU),W(IXN),W(IXA),W(ID),W(IVL),W(IW))
  128. 40 RETURN
  129. END