dmpar.f 8.4 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271
  1. *DECK DMPAR
  2. SUBROUTINE DMPAR (N, R, LDR, IPVT, DIAG, QTB, DELTA, PAR, X,
  3. + SIGMA, WA1, WA2)
  4. C***BEGIN PROLOGUE DMPAR
  5. C***SUBSIDIARY
  6. C***PURPOSE Subsidiary to DNLS1 and DNLS1E
  7. C***LIBRARY SLATEC
  8. C***TYPE DOUBLE PRECISION (LMPAR-S, DMPAR-D)
  9. C***AUTHOR (UNKNOWN)
  10. C***DESCRIPTION
  11. C
  12. C **** Double Precision version of LMPAR ****
  13. C
  14. C Given an M by N matrix A, an N by N nonsingular DIAGONAL
  15. C matrix D, an M-vector B, and a positive number DELTA,
  16. C the problem is to determine a value for the parameter
  17. C PAR such that if X solves the system
  18. C
  19. C A*X = B , SQRT(PAR)*D*X = 0 ,
  20. C
  21. C in the least squares sense, and DXNORM is the Euclidean
  22. C norm of D*X, then either PAR is zero and
  23. C
  24. C (DXNORM-DELTA) .LE. 0.1*DELTA ,
  25. C
  26. C or PAR is positive and
  27. C
  28. C ABS(DXNORM-DELTA) .LE. 0.1*DELTA .
  29. C
  30. C This subroutine completes the solution of the problem
  31. C if it is provided with the necessary information from the
  32. C QR factorization, with column pivoting, of A. That is, if
  33. C A*P = Q*R, where P is a permutation matrix, Q has orthogonal
  34. C columns, and R is an upper triangular matrix with diagonal
  35. C elements of nonincreasing magnitude, then DMPAR expects
  36. C the full upper triangle of R, the permutation matrix P,
  37. C and the first N components of (Q TRANSPOSE)*B. On output
  38. C DMPAR also provides an upper triangular matrix S such that
  39. C
  40. C T T T
  41. C P *(A *A + PAR*D*D)*P = S *S .
  42. C
  43. C S is employed within DMPAR and may be of separate interest.
  44. C
  45. C Only a few iterations are generally needed for convergence
  46. C of the algorithm. If, however, the limit of 10 iterations
  47. C is reached, then the output PAR will contain the best
  48. C value obtained so far.
  49. C
  50. C The subroutine statement is
  51. C
  52. C SUBROUTINE DMPAR(N,R,LDR,IPVT,DIAG,QTB,DELTA,PAR,X,SIGMA,
  53. C WA1,WA2)
  54. C
  55. C where
  56. C
  57. C N is a positive integer input variable set to the order of R.
  58. C
  59. C R is an N by N array. On input the full upper triangle
  60. C must contain the full upper triangle of the matrix R.
  61. C On output the full upper triangle is unaltered, and the
  62. C strict lower triangle contains the strict upper triangle
  63. C (transposed) of the upper triangular matrix S.
  64. C
  65. C LDR is a positive integer input variable not less than N
  66. C which specifies the leading dimension of the array R.
  67. C
  68. C IPVT is an integer input array of length N which defines the
  69. C permutation matrix P such that A*P = Q*R. Column J of P
  70. C is column IPVT(J) of the identity matrix.
  71. C
  72. C DIAG is an input array of length N which must contain the
  73. C diagonal elements of the matrix D.
  74. C
  75. C QTB is an input array of length N which must contain the first
  76. C N elements of the vector (Q TRANSPOSE)*B.
  77. C
  78. C DELTA is a positive input variable which specifies an upper
  79. C bound on the Euclidean norm of D*X.
  80. C
  81. C PAR is a nonnegative variable. On input PAR contains an
  82. C initial estimate of the Levenberg-Marquardt parameter.
  83. C On output PAR contains the final estimate.
  84. C
  85. C X is an output array of length N which contains the least
  86. C squares solution of the system A*X = B, SQRT(PAR)*D*X = 0,
  87. C for the output PAR.
  88. C
  89. C SIGMA is an output array of length N which contains the
  90. C diagonal elements of the upper triangular matrix S.
  91. C
  92. C WA1 and WA2 are work arrays of length N.
  93. C
  94. C***SEE ALSO DNLS1, DNLS1E
  95. C***ROUTINES CALLED D1MACH, DENORM, DQRSLV
  96. C***REVISION HISTORY (YYMMDD)
  97. C 800301 DATE WRITTEN
  98. C 890531 Changed all specific intrinsics to generic. (WRB)
  99. C 890831 Modified array declarations. (WRB)
  100. C 891214 Prologue converted to Version 4.0 format. (BAB)
  101. C 900326 Removed duplicate information from DESCRIPTION section.
  102. C (WRB)
  103. C 900328 Added TYPE section. (WRB)
  104. C***END PROLOGUE DMPAR
  105. INTEGER N,LDR
  106. INTEGER IPVT(*)
  107. DOUBLE PRECISION DELTA,PAR
  108. DOUBLE PRECISION R(LDR,*),DIAG(*),QTB(*),X(*),SIGMA(*),WA1(*),
  109. 1 WA2(*)
  110. INTEGER I,ITER,J,JM1,JP1,K,L,NSING
  111. DOUBLE PRECISION DXNORM,DWARF,FP,GNORM,PARC,PARL,PARU,P1,P001,
  112. 1 SUM,TEMP,ZERO
  113. DOUBLE PRECISION D1MACH,DENORM
  114. SAVE P1, P001, ZERO
  115. DATA P1,P001,ZERO /1.0D-1,1.0D-3,0.0D0/
  116. C***FIRST EXECUTABLE STATEMENT DMPAR
  117. DWARF = D1MACH(1)
  118. C
  119. C COMPUTE AND STORE IN X THE GAUSS-NEWTON DIRECTION. IF THE
  120. C JACOBIAN IS RANK-DEFICIENT, OBTAIN A LEAST SQUARES SOLUTION.
  121. C
  122. NSING = N
  123. DO 10 J = 1, N
  124. WA1(J) = QTB(J)
  125. IF (R(J,J) .EQ. ZERO .AND. NSING .EQ. N) NSING = J - 1
  126. IF (NSING .LT. N) WA1(J) = ZERO
  127. 10 CONTINUE
  128. IF (NSING .LT. 1) GO TO 50
  129. DO 40 K = 1, NSING
  130. J = NSING - K + 1
  131. WA1(J) = WA1(J)/R(J,J)
  132. TEMP = WA1(J)
  133. JM1 = J - 1
  134. IF (JM1 .LT. 1) GO TO 30
  135. DO 20 I = 1, JM1
  136. WA1(I) = WA1(I) - R(I,J)*TEMP
  137. 20 CONTINUE
  138. 30 CONTINUE
  139. 40 CONTINUE
  140. 50 CONTINUE
  141. DO 60 J = 1, N
  142. L = IPVT(J)
  143. X(L) = WA1(J)
  144. 60 CONTINUE
  145. C
  146. C INITIALIZE THE ITERATION COUNTER.
  147. C EVALUATE THE FUNCTION AT THE ORIGIN, AND TEST
  148. C FOR ACCEPTANCE OF THE GAUSS-NEWTON DIRECTION.
  149. C
  150. ITER = 0
  151. DO 70 J = 1, N
  152. WA2(J) = DIAG(J)*X(J)
  153. 70 CONTINUE
  154. DXNORM = DENORM(N,WA2)
  155. FP = DXNORM - DELTA
  156. IF (FP .LE. P1*DELTA) GO TO 220
  157. C
  158. C IF THE JACOBIAN IS NOT RANK DEFICIENT, THE NEWTON
  159. C STEP PROVIDES A LOWER BOUND, PARL, FOR THE ZERO OF
  160. C THE FUNCTION. OTHERWISE SET THIS BOUND TO ZERO.
  161. C
  162. PARL = ZERO
  163. IF (NSING .LT. N) GO TO 120
  164. DO 80 J = 1, N
  165. L = IPVT(J)
  166. WA1(J) = DIAG(L)*(WA2(L)/DXNORM)
  167. 80 CONTINUE
  168. DO 110 J = 1, N
  169. SUM = ZERO
  170. JM1 = J - 1
  171. IF (JM1 .LT. 1) GO TO 100
  172. DO 90 I = 1, JM1
  173. SUM = SUM + R(I,J)*WA1(I)
  174. 90 CONTINUE
  175. 100 CONTINUE
  176. WA1(J) = (WA1(J) - SUM)/R(J,J)
  177. 110 CONTINUE
  178. TEMP = DENORM(N,WA1)
  179. PARL = ((FP/DELTA)/TEMP)/TEMP
  180. 120 CONTINUE
  181. C
  182. C CALCULATE AN UPPER BOUND, PARU, FOR THE ZERO OF THE FUNCTION.
  183. C
  184. DO 140 J = 1, N
  185. SUM = ZERO
  186. DO 130 I = 1, J
  187. SUM = SUM + R(I,J)*QTB(I)
  188. 130 CONTINUE
  189. L = IPVT(J)
  190. WA1(J) = SUM/DIAG(L)
  191. 140 CONTINUE
  192. GNORM = DENORM(N,WA1)
  193. PARU = GNORM/DELTA
  194. IF (PARU .EQ. ZERO) PARU = DWARF/MIN(DELTA,P1)
  195. C
  196. C IF THE INPUT PAR LIES OUTSIDE OF THE INTERVAL (PARL,PARU),
  197. C SET PAR TO THE CLOSER ENDPOINT.
  198. C
  199. PAR = MAX(PAR,PARL)
  200. PAR = MIN(PAR,PARU)
  201. IF (PAR .EQ. ZERO) PAR = GNORM/DXNORM
  202. C
  203. C BEGINNING OF AN ITERATION.
  204. C
  205. 150 CONTINUE
  206. ITER = ITER + 1
  207. C
  208. C EVALUATE THE FUNCTION AT THE CURRENT VALUE OF PAR.
  209. C
  210. IF (PAR .EQ. ZERO) PAR = MAX(DWARF,P001*PARU)
  211. TEMP = SQRT(PAR)
  212. DO 160 J = 1, N
  213. WA1(J) = TEMP*DIAG(J)
  214. 160 CONTINUE
  215. CALL DQRSLV(N,R,LDR,IPVT,WA1,QTB,X,SIGMA,WA2)
  216. DO 170 J = 1, N
  217. WA2(J) = DIAG(J)*X(J)
  218. 170 CONTINUE
  219. DXNORM = DENORM(N,WA2)
  220. TEMP = FP
  221. FP = DXNORM - DELTA
  222. C
  223. C IF THE FUNCTION IS SMALL ENOUGH, ACCEPT THE CURRENT VALUE
  224. C OF PAR. ALSO TEST FOR THE EXCEPTIONAL CASES WHERE PARL
  225. C IS ZERO OR THE NUMBER OF ITERATIONS HAS REACHED 10.
  226. C
  227. IF (ABS(FP) .LE. P1*DELTA
  228. 1 .OR. PARL .EQ. ZERO .AND. FP .LE. TEMP
  229. 2 .AND. TEMP .LT. ZERO .OR. ITER .EQ. 10) GO TO 220
  230. C
  231. C COMPUTE THE NEWTON CORRECTION.
  232. C
  233. DO 180 J = 1, N
  234. L = IPVT(J)
  235. WA1(J) = DIAG(L)*(WA2(L)/DXNORM)
  236. 180 CONTINUE
  237. DO 210 J = 1, N
  238. WA1(J) = WA1(J)/SIGMA(J)
  239. TEMP = WA1(J)
  240. JP1 = J + 1
  241. IF (N .LT. JP1) GO TO 200
  242. DO 190 I = JP1, N
  243. WA1(I) = WA1(I) - R(I,J)*TEMP
  244. 190 CONTINUE
  245. 200 CONTINUE
  246. 210 CONTINUE
  247. TEMP = DENORM(N,WA1)
  248. PARC = ((FP/DELTA)/TEMP)/TEMP
  249. C
  250. C DEPENDING ON THE SIGN OF THE FUNCTION, UPDATE PARL OR PARU.
  251. C
  252. IF (FP .GT. ZERO) PARL = MAX(PARL,PAR)
  253. IF (FP .LT. ZERO) PARU = MIN(PARU,PAR)
  254. C
  255. C COMPUTE AN IMPROVED ESTIMATE FOR PAR.
  256. C
  257. PAR = MAX(PARL,PAR+PARC)
  258. C
  259. C END OF AN ITERATION.
  260. C
  261. GO TO 150
  262. 220 CONTINUE
  263. C
  264. C TERMINATION.
  265. C
  266. IF (ITER .EQ. 0) PAR = ZERO
  267. RETURN
  268. C
  269. C LAST CARD OF SUBROUTINE DMPAR.
  270. C
  271. END