wnlsm.f 19 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638
  1. *DECK WNLSM
  2. SUBROUTINE WNLSM (W, MDW, MME, MA, N, L, PRGOPT, X, RNORM, MODE,
  3. + IPIVOT, ITYPE, WD, H, SCALE, Z, TEMP, D)
  4. C***BEGIN PROLOGUE WNLSM
  5. C***SUBSIDIARY
  6. C***PURPOSE Subsidiary to WNNLS
  7. C***LIBRARY SLATEC
  8. C***TYPE SINGLE PRECISION (WNLSM-S, DWNLSM-D)
  9. C***AUTHOR Hanson, R. J., (SNLA)
  10. C Haskell, K. H., (SNLA)
  11. C***DESCRIPTION
  12. C
  13. C This is a companion subprogram to WNNLS.
  14. C The documentation for WNNLS has complete usage instructions.
  15. C
  16. C In addition to the parameters discussed in the prologue to
  17. C subroutine WNNLS, the following work arrays are used in
  18. C subroutine WNLSM (they are passed through the calling
  19. C sequence from WNNLS for purposes of variable dimensioning).
  20. C Their contents will in general be of no interest to the user.
  21. C
  22. C IPIVOT(*)
  23. C An array of length N. Upon completion it contains the
  24. C pivoting information for the cols of W(*,*).
  25. C
  26. C ITYPE(*)
  27. C An array of length M which is used to keep track
  28. C of the classification of the equations. ITYPE(I)=0
  29. C denotes equation I as an equality constraint.
  30. C ITYPE(I)=1 denotes equation I as a least squares
  31. C equation.
  32. C
  33. C WD(*)
  34. C An array of length N. Upon completion it contains the
  35. C dual solution vector.
  36. C
  37. C H(*)
  38. C An array of length N. Upon completion it contains the
  39. C pivot scalars of the Householder transformations performed
  40. C in the case KRANK.LT.L.
  41. C
  42. C SCALE(*)
  43. C An array of length M which is used by the subroutine
  44. C to store the diagonal matrix of weights.
  45. C These are used to apply the modified Givens
  46. C transformations.
  47. C
  48. C Z(*),TEMP(*)
  49. C Working arrays of length N.
  50. C
  51. C D(*)
  52. C An array of length N that contains the
  53. C column scaling for the matrix (E).
  54. C (A)
  55. C
  56. C***SEE ALSO WNNLS
  57. C***ROUTINES CALLED H12, ISAMAX, R1MACH, SASUM, SAXPY, SCOPY, SNRM2,
  58. C SROTM, SROTMG, SSCAL, SSWAP, WNLIT, XERMSG
  59. C***REVISION HISTORY (YYMMDD)
  60. C 790701 DATE WRITTEN
  61. C 890531 Changed all specific intrinsics to generic. (WRB)
  62. C 890618 Completely restructured and revised. (WRB & RWC)
  63. C 891214 Prologue converted to Version 4.0 format. (BAB)
  64. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  65. C 900328 Added TYPE section. (WRB)
  66. C 900510 Fixed an error message. (RWC)
  67. C***END PROLOGUE WNLSM
  68. INTEGER IPIVOT(*), ITYPE(*), L, MA, MDW, MME, MODE, N
  69. REAL D(*), H(*), PRGOPT(*), RNORM, SCALE(*), TEMP(*),
  70. * W(MDW,*), WD(*), X(*), Z(*)
  71. C
  72. EXTERNAL H12, ISAMAX, R1MACH, SASUM, SAXPY, SCOPY, SNRM2, SROTM,
  73. * SROTMG, SSCAL, SSWAP, WNLIT, XERMSG
  74. REAL R1MACH, SASUM, SNRM2
  75. INTEGER ISAMAX
  76. C
  77. REAL ALAMDA, ALPHA, ALSQ, AMAX, BLOWUP, BNORM,
  78. * DOPE(3), EANORM, FAC, SM, SPARAM(5), SRELPR, T, TAU, WMAX, Z2,
  79. * ZZ
  80. INTEGER I, IDOPE(3), IMAX, ISOL, ITEMP, ITER, ITMAX, IWMAX, J,
  81. * JCON, JP, KEY, KRANK, L1, LAST, LINK, M, ME, NEXT, NIV, NLINK,
  82. * NOPT, NSOLN, NTIMES
  83. LOGICAL DONE, FEASBL, FIRST, HITCON, POS
  84. C
  85. SAVE SRELPR, FIRST
  86. DATA FIRST /.TRUE./
  87. C***FIRST EXECUTABLE STATEMENT WNLSM
  88. C
  89. C Initialize variables.
  90. C SRELPR is the precision for the particular machine
  91. C being used. This logic avoids resetting it every entry.
  92. C
  93. IF (FIRST) SRELPR = R1MACH(4)
  94. FIRST = .FALSE.
  95. C
  96. C Set the nominal tolerance used in the code.
  97. C
  98. TAU = SQRT(SRELPR)
  99. C
  100. M = MA + MME
  101. ME = MME
  102. MODE = 2
  103. C
  104. C To process option vector
  105. C
  106. FAC = 1.E-4
  107. C
  108. C Set the nominal blow up factor used in the code.
  109. C
  110. BLOWUP = TAU
  111. C
  112. C The nominal column scaling used in the code is
  113. C the identity scaling.
  114. C
  115. CALL SCOPY (N, 1.E0, 0, D, 1)
  116. C
  117. C Define bound for number of options to change.
  118. C
  119. NOPT = 1000
  120. C
  121. C Define bound for positive value of LINK.
  122. C
  123. NLINK = 100000
  124. NTIMES = 0
  125. LAST = 1
  126. LINK = PRGOPT(1)
  127. IF (LINK.LE.0 .OR. LINK.GT.NLINK) THEN
  128. CALL XERMSG ('SLATEC', 'WNLSM',
  129. + 'WNNLS, THE OPTION VECTOR IS UNDEFINED', 3, 1)
  130. RETURN
  131. ENDIF
  132. C
  133. 100 IF (LINK.GT.1) THEN
  134. NTIMES = NTIMES + 1
  135. IF (NTIMES.GT.NOPT) THEN
  136. CALL XERMSG ('SLATEC', 'WNLSM',
  137. + 'WNNLS, THE LINKS IN THE OPTION VECTOR ARE CYCLING.', 3, 1)
  138. RETURN
  139. ENDIF
  140. C
  141. KEY = PRGOPT(LAST+1)
  142. IF (KEY.EQ.6 .AND. PRGOPT(LAST+2).NE.0.E0) THEN
  143. DO 110 J = 1,N
  144. T = SNRM2(M,W(1,J),1)
  145. IF (T.NE.0.E0) T = 1.E0/T
  146. D(J) = T
  147. 110 CONTINUE
  148. ENDIF
  149. C
  150. IF (KEY.EQ.7) CALL SCOPY (N, PRGOPT(LAST+2), 1, D, 1)
  151. IF (KEY.EQ.8) TAU = MAX(SRELPR,PRGOPT(LAST+2))
  152. IF (KEY.EQ.9) BLOWUP = MAX(SRELPR,PRGOPT(LAST+2))
  153. C
  154. NEXT = PRGOPT(LINK)
  155. IF (NEXT.LE.0 .OR. NEXT.GT.NLINK) THEN
  156. CALL XERMSG ('SLATEC', 'WNLSM',
  157. + 'WNNLS, THE OPTION VECTOR IS UNDEFINED', 3, 1)
  158. RETURN
  159. ENDIF
  160. C
  161. LAST = LINK
  162. LINK = NEXT
  163. GO TO 100
  164. ENDIF
  165. C
  166. DO 120 J = 1,N
  167. CALL SSCAL (M, D(J), W(1,J), 1)
  168. 120 CONTINUE
  169. C
  170. C Process option vector
  171. C
  172. DONE = .FALSE.
  173. ITER = 0
  174. ITMAX = 3*(N-L)
  175. MODE = 0
  176. NSOLN = L
  177. L1 = MIN(M,L)
  178. C
  179. C Compute scale factor to apply to equality constraint equations.
  180. C
  181. DO 130 J = 1,N
  182. WD(J) = SASUM(M,W(1,J),1)
  183. 130 CONTINUE
  184. C
  185. IMAX = ISAMAX(N,WD,1)
  186. EANORM = WD(IMAX)
  187. BNORM = SASUM(M,W(1,N+1),1)
  188. ALAMDA = EANORM/(SRELPR*FAC)
  189. C
  190. C Define scaling diagonal matrix for modified Givens usage and
  191. C classify equation types.
  192. C
  193. ALSQ = ALAMDA**2
  194. DO 140 I = 1,M
  195. C
  196. C When equation I is heavily weighted ITYPE(I)=0,
  197. C else ITYPE(I)=1.
  198. C
  199. IF (I.LE.ME) THEN
  200. T = ALSQ
  201. ITEMP = 0
  202. ELSE
  203. T = 1.E0
  204. ITEMP = 1
  205. ENDIF
  206. SCALE(I) = T
  207. ITYPE(I) = ITEMP
  208. 140 CONTINUE
  209. C
  210. C Set the solution vector X(*) to zero and the column interchange
  211. C matrix to the identity.
  212. C
  213. CALL SCOPY (N, 0.E0, 0, X, 1)
  214. DO 150 I = 1,N
  215. IPIVOT(I) = I
  216. 150 CONTINUE
  217. C
  218. C Perform initial triangularization in the submatrix
  219. C corresponding to the unconstrained variables.
  220. C Set first L components of dual vector to zero because
  221. C these correspond to the unconstrained variables.
  222. C
  223. CALL SCOPY (L, 0.E0, 0, WD, 1)
  224. C
  225. C The arrays IDOPE(*) and DOPE(*) are used to pass
  226. C information to WNLIT(). This was done to avoid
  227. C a long calling sequence or the use of COMMON.
  228. C
  229. IDOPE(1) = ME
  230. IDOPE(2) = NSOLN
  231. IDOPE(3) = L1
  232. C
  233. DOPE(1) = ALSQ
  234. DOPE(2) = EANORM
  235. DOPE(3) = TAU
  236. CALL WNLIT (W, MDW, M, N, L, IPIVOT, ITYPE, H, SCALE, RNORM,
  237. + IDOPE, DOPE, DONE)
  238. ME = IDOPE(1)
  239. KRANK = IDOPE(2)
  240. NIV = IDOPE(3)
  241. C
  242. C Perform WNNLS algorithm using the following steps.
  243. C
  244. C Until(DONE)
  245. C compute search direction and feasible point
  246. C when (HITCON) add constraints
  247. C else perform multiplier test and drop a constraint
  248. C fin
  249. C Compute-Final-Solution
  250. C
  251. C To compute search direction and feasible point,
  252. C solve the triangular system of currently non-active
  253. C variables and store the solution in Z(*).
  254. C
  255. C To solve system
  256. C Copy right hand side into TEMP vector to use overwriting method.
  257. C
  258. 160 IF (DONE) GO TO 330
  259. ISOL = L + 1
  260. IF (NSOLN.GE.ISOL) THEN
  261. CALL SCOPY (NIV, W(1,N+1), 1, TEMP, 1)
  262. DO 170 J = NSOLN,ISOL,-1
  263. IF (J.GT.KRANK) THEN
  264. I = NIV - NSOLN + J
  265. ELSE
  266. I = J
  267. ENDIF
  268. C
  269. IF (J.GT.KRANK .AND. J.LE.L) THEN
  270. Z(J) = 0.E0
  271. ELSE
  272. Z(J) = TEMP(I)/W(I,J)
  273. CALL SAXPY (I-1, -Z(J), W(1,J), 1, TEMP, 1)
  274. ENDIF
  275. 170 CONTINUE
  276. ENDIF
  277. C
  278. C Increment iteration counter and check against maximum number
  279. C of iterations.
  280. C
  281. ITER = ITER + 1
  282. IF (ITER.GT.ITMAX) THEN
  283. MODE = 1
  284. DONE = .TRUE.
  285. ENDIF
  286. C
  287. C Check to see if any constraints have become active.
  288. C If so, calculate an interpolation factor so that all
  289. C active constraints are removed from the basis.
  290. C
  291. ALPHA = 2.E0
  292. HITCON = .FALSE.
  293. DO 180 J = L+1,NSOLN
  294. ZZ = Z(J)
  295. IF (ZZ.LE.0.E0) THEN
  296. T = X(J)/(X(J)-ZZ)
  297. IF (T.LT.ALPHA) THEN
  298. ALPHA = T
  299. JCON = J
  300. ENDIF
  301. HITCON = .TRUE.
  302. ENDIF
  303. 180 CONTINUE
  304. C
  305. C Compute search direction and feasible point
  306. C
  307. IF (HITCON) THEN
  308. C
  309. C To add constraints, use computed ALPHA to interpolate between
  310. C last feasible solution X(*) and current unconstrained (and
  311. C infeasible) solution Z(*).
  312. C
  313. DO 190 J = L+1,NSOLN
  314. X(J) = X(J) + ALPHA*(Z(J)-X(J))
  315. 190 CONTINUE
  316. FEASBL = .FALSE.
  317. C
  318. C Remove column JCON and shift columns JCON+1 through N to the
  319. C left. Swap column JCON into the N th position. This achieves
  320. C upper Hessenberg form for the nonactive constraints and
  321. C leaves an upper Hessenberg matrix to retriangularize.
  322. C
  323. 200 DO 210 I = 1,M
  324. T = W(I,JCON)
  325. CALL SCOPY (N-JCON, W(I, JCON+1), MDW, W(I, JCON), MDW)
  326. W(I,N) = T
  327. 210 CONTINUE
  328. C
  329. C Update permuted index vector to reflect this shift and swap.
  330. C
  331. ITEMP = IPIVOT(JCON)
  332. DO 220 I = JCON,N - 1
  333. IPIVOT(I) = IPIVOT(I+1)
  334. 220 CONTINUE
  335. IPIVOT(N) = ITEMP
  336. C
  337. C Similarly permute X(*) vector.
  338. C
  339. CALL SCOPY (N-JCON, X(JCON+1), 1, X(JCON), 1)
  340. X(N) = 0.E0
  341. NSOLN = NSOLN - 1
  342. NIV = NIV - 1
  343. C
  344. C Retriangularize upper Hessenberg matrix after adding
  345. C constraints.
  346. C
  347. I = KRANK + JCON - L
  348. DO 230 J = JCON,NSOLN
  349. IF (ITYPE(I).EQ.0 .AND. ITYPE(I+1).EQ.0) THEN
  350. C
  351. C Zero IP1 to I in column J
  352. C
  353. IF (W(I+1,J).NE.0.E0) THEN
  354. CALL SROTMG (SCALE(I), SCALE(I+1), W(I,J), W(I+1,J),
  355. + SPARAM)
  356. W(I+1,J) = 0.E0
  357. CALL SROTM (N+1-J, W(I,J+1), MDW, W(I+1,J+1), MDW,
  358. + SPARAM)
  359. ENDIF
  360. ELSEIF (ITYPE(I).EQ.1 .AND. ITYPE(I+1).EQ.1) THEN
  361. C
  362. C Zero IP1 to I in column J
  363. C
  364. IF (W(I+1,J).NE.0.E0) THEN
  365. CALL SROTMG (SCALE(I), SCALE(I+1), W(I,J), W(I+1,J),
  366. + SPARAM)
  367. W(I+1,J) = 0.E0
  368. CALL SROTM (N+1-J, W(I,J+1), MDW, W(I+1,J+1), MDW,
  369. + SPARAM)
  370. ENDIF
  371. ELSEIF (ITYPE(I).EQ.1 .AND. ITYPE(I+1).EQ.0) THEN
  372. CALL SSWAP (N+1, W(I,1), MDW, W(I+1,1), MDW)
  373. CALL SSWAP (1, SCALE(I), 1, SCALE(I+1), 1)
  374. ITEMP = ITYPE(I+1)
  375. ITYPE(I+1) = ITYPE(I)
  376. ITYPE(I) = ITEMP
  377. C
  378. C Swapped row was formerly a pivot element, so it will
  379. C be large enough to perform elimination.
  380. C Zero IP1 to I in column J.
  381. C
  382. IF (W(I+1,J).NE.0.E0) THEN
  383. CALL SROTMG (SCALE(I), SCALE(I+1), W(I,J), W(I+1,J),
  384. + SPARAM)
  385. W(I+1,J) = 0.E0
  386. CALL SROTM (N+1-J, W(I,J+1), MDW, W(I+1,J+1), MDW,
  387. + SPARAM)
  388. ENDIF
  389. ELSEIF (ITYPE(I).EQ.0 .AND. ITYPE(I+1).EQ.1) THEN
  390. IF (SCALE(I)*W(I,J)**2/ALSQ.GT.(TAU*EANORM)**2) THEN
  391. C
  392. C Zero IP1 to I in column J
  393. C
  394. IF (W(I+1,J).NE.0.E0) THEN
  395. CALL SROTMG (SCALE(I), SCALE(I+1), W(I,J),
  396. + W(I+1,J), SPARAM)
  397. W(I+1,J) = 0.E0
  398. CALL SROTM (N+1-J, W(I,J+1), MDW, W(I+1,J+1), MDW,
  399. + SPARAM)
  400. ENDIF
  401. ELSE
  402. CALL SSWAP (N+1, W(I,1), MDW, W(I+1,1), MDW)
  403. CALL SSWAP (1, SCALE(I), 1, SCALE(I+1), 1)
  404. ITEMP = ITYPE(I+1)
  405. ITYPE(I+1) = ITYPE(I)
  406. ITYPE(I) = ITEMP
  407. W(I+1,J) = 0.E0
  408. ENDIF
  409. ENDIF
  410. I = I + 1
  411. 230 CONTINUE
  412. C
  413. C See if the remaining coefficients in the solution set are
  414. C feasible. They should be because of the way ALPHA was
  415. C determined. If any are infeasible, it is due to roundoff
  416. C error. Any that are non-positive will be set to zero and
  417. C removed from the solution set.
  418. C
  419. DO 240 JCON = L+1,NSOLN
  420. IF (X(JCON).LE.0.E0) GO TO 250
  421. 240 CONTINUE
  422. FEASBL = .TRUE.
  423. 250 IF (.NOT.FEASBL) GO TO 200
  424. ELSE
  425. C
  426. C To perform multiplier test and drop a constraint.
  427. C
  428. CALL SCOPY (NSOLN, Z, 1, X, 1)
  429. IF (NSOLN.LT.N) CALL SCOPY (N-NSOLN, 0.E0, 0, X(NSOLN+1), 1)
  430. C
  431. C Reclassify least squares equations as equalities as necessary.
  432. C
  433. I = NIV + 1
  434. 260 IF (I.LE.ME) THEN
  435. IF (ITYPE(I).EQ.0) THEN
  436. I = I + 1
  437. ELSE
  438. CALL SSWAP (N+1, W(I,1), MDW, W(ME,1), MDW)
  439. CALL SSWAP (1, SCALE(I), 1, SCALE(ME), 1)
  440. ITEMP = ITYPE(I)
  441. ITYPE(I) = ITYPE(ME)
  442. ITYPE(ME) = ITEMP
  443. ME = ME - 1
  444. ENDIF
  445. GO TO 260
  446. ENDIF
  447. C
  448. C Form inner product vector WD(*) of dual coefficients.
  449. C
  450. DO 280 J = NSOLN+1,N
  451. SM = 0.E0
  452. DO 270 I = NSOLN+1,M
  453. SM = SM + SCALE(I)*W(I,J)*W(I,N+1)
  454. 270 CONTINUE
  455. WD(J) = SM
  456. 280 CONTINUE
  457. C
  458. C Find J such that WD(J)=WMAX is maximum. This determines
  459. C that the incoming column J will reduce the residual vector
  460. C and be positive.
  461. C
  462. 290 WMAX = 0.E0
  463. IWMAX = NSOLN + 1
  464. DO 300 J = NSOLN+1,N
  465. IF (WD(J).GT.WMAX) THEN
  466. WMAX = WD(J)
  467. IWMAX = J
  468. ENDIF
  469. 300 CONTINUE
  470. IF (WMAX.LE.0.E0) GO TO 330
  471. C
  472. C Set dual coefficients to zero for incoming column.
  473. C
  474. WD(IWMAX) = 0.E0
  475. C
  476. C WMAX .GT. 0.E0, so okay to move column IWMAX to solution set.
  477. C Perform transformation to retriangularize, and test for near
  478. C linear dependence.
  479. C
  480. C Swap column IWMAX into NSOLN-th position to maintain upper
  481. C Hessenberg form of adjacent columns, and add new column to
  482. C triangular decomposition.
  483. C
  484. NSOLN = NSOLN + 1
  485. NIV = NIV + 1
  486. IF (NSOLN.NE.IWMAX) THEN
  487. CALL SSWAP (M, W(1,NSOLN), 1, W(1,IWMAX), 1)
  488. WD(IWMAX) = WD(NSOLN)
  489. WD(NSOLN) = 0.E0
  490. ITEMP = IPIVOT(NSOLN)
  491. IPIVOT(NSOLN) = IPIVOT(IWMAX)
  492. IPIVOT(IWMAX) = ITEMP
  493. ENDIF
  494. C
  495. C Reduce column NSOLN so that the matrix of nonactive constraints
  496. C variables is triangular.
  497. C
  498. DO 320 J = M,NIV+1,-1
  499. JP = J - 1
  500. C
  501. C When operating near the ME line, test to see if the pivot
  502. C element is near zero. If so, use the largest element above
  503. C it as the pivot. This is to maintain the sharp interface
  504. C between weighted and non-weighted rows in all cases.
  505. C
  506. IF (J.EQ.ME+1) THEN
  507. IMAX = ME
  508. AMAX = SCALE(ME)*W(ME,NSOLN)**2
  509. DO 310 JP = J - 1,NIV,-1
  510. T = SCALE(JP)*W(JP,NSOLN)**2
  511. IF (T.GT.AMAX) THEN
  512. IMAX = JP
  513. AMAX = T
  514. ENDIF
  515. 310 CONTINUE
  516. JP = IMAX
  517. ENDIF
  518. C
  519. IF (W(J,NSOLN).NE.0.E0) THEN
  520. CALL SROTMG (SCALE(JP), SCALE(J), W(JP,NSOLN),
  521. + W(J,NSOLN), SPARAM)
  522. W(J,NSOLN) = 0.E0
  523. CALL SROTM (N+1-NSOLN, W(JP,NSOLN+1), MDW, W(J,NSOLN+1),
  524. + MDW, SPARAM)
  525. ENDIF
  526. 320 CONTINUE
  527. C
  528. C Solve for Z(NSOLN)=proposed new value for X(NSOLN). Test if
  529. C this is nonpositive or too large. If this was true or if the
  530. C pivot term was zero, reject the column as dependent.
  531. C
  532. IF (W(NIV,NSOLN).NE.0.E0) THEN
  533. ISOL = NIV
  534. Z2 = W(ISOL,N+1)/W(ISOL,NSOLN)
  535. Z(NSOLN) = Z2
  536. POS = Z2 .GT. 0.E0
  537. IF (Z2*EANORM.GE.BNORM .AND. POS) THEN
  538. POS = .NOT. (BLOWUP*Z2*EANORM.GE.BNORM)
  539. ENDIF
  540. C
  541. C Try to add row ME+1 as an additional equality constraint.
  542. C Check size of proposed new solution component.
  543. C Reject it if it is too large.
  544. C
  545. ELSEIF (NIV.LE.ME .AND. W(ME+1,NSOLN).NE.0.E0) THEN
  546. ISOL = ME + 1
  547. IF (POS) THEN
  548. C
  549. C Swap rows ME+1 and NIV, and scale factors for these rows.
  550. C
  551. CALL SSWAP (N+1, W(ME+1,1), MDW, W(NIV,1), MDW)
  552. CALL SSWAP (1, SCALE(ME+1), 1, SCALE(NIV), 1)
  553. ITEMP = ITYPE(ME+1)
  554. ITYPE(ME+1) = ITYPE(NIV)
  555. ITYPE(NIV) = ITEMP
  556. ME = ME + 1
  557. ENDIF
  558. ELSE
  559. POS = .FALSE.
  560. ENDIF
  561. C
  562. IF (.NOT.POS) THEN
  563. NSOLN = NSOLN - 1
  564. NIV = NIV - 1
  565. ENDIF
  566. IF (.NOT.(POS.OR.DONE)) GO TO 290
  567. ENDIF
  568. GO TO 160
  569. C
  570. C Else perform multiplier test and drop a constraint. To compute
  571. C final solution. Solve system, store results in X(*).
  572. C
  573. C Copy right hand side into TEMP vector to use overwriting method.
  574. C
  575. 330 ISOL = 1
  576. IF (NSOLN.GE.ISOL) THEN
  577. CALL SCOPY (NIV, W(1,N+1), 1, TEMP, 1)
  578. DO 340 J = NSOLN,ISOL,-1
  579. IF (J.GT.KRANK) THEN
  580. I = NIV - NSOLN + J
  581. ELSE
  582. I = J
  583. ENDIF
  584. C
  585. IF (J.GT.KRANK .AND. J.LE.L) THEN
  586. Z(J) = 0.E0
  587. ELSE
  588. Z(J) = TEMP(I)/W(I,J)
  589. CALL SAXPY (I-1, -Z(J), W(1,J), 1, TEMP, 1)
  590. ENDIF
  591. 340 CONTINUE
  592. ENDIF
  593. C
  594. C Solve system.
  595. C
  596. CALL SCOPY (NSOLN, Z, 1, X, 1)
  597. C
  598. C Apply Householder transformations to X(*) if KRANK.LT.L
  599. C
  600. IF (KRANK.LT.L) THEN
  601. DO 350 I = 1,KRANK
  602. CALL H12 (2, I, KRANK+1, L, W(I,1), MDW, H(I), X, 1, 1, 1)
  603. 350 CONTINUE
  604. ENDIF
  605. C
  606. C Fill in trailing zeroes for constrained variables not in solution.
  607. C
  608. IF (NSOLN.LT.N) CALL SCOPY (N-NSOLN, 0.E0, 0, X(NSOLN+1), 1)
  609. C
  610. C Permute solution vector to natural order.
  611. C
  612. DO 380 I = 1,N
  613. J = I
  614. 360 IF (IPIVOT(J).EQ.I) GO TO 370
  615. J = J + 1
  616. GO TO 360
  617. C
  618. 370 IPIVOT(J) = IPIVOT(I)
  619. IPIVOT(I) = J
  620. CALL SSWAP (1, X(J), 1, X(I), 1)
  621. 380 CONTINUE
  622. C
  623. C Rescale the solution using the column scaling.
  624. C
  625. DO 390 J = 1,N
  626. X(J) = X(J)*D(J)
  627. 390 CONTINUE
  628. C
  629. DO 400 I = NSOLN+1,M
  630. T = W(I,N+1)
  631. IF (I.LE.ME) T = T/ALAMDA
  632. T = (SCALE(I)*T)*T
  633. RNORM = RNORM + T
  634. 400 CONTINUE
  635. C
  636. RNORM = SQRT(RNORM)
  637. RETURN
  638. END