wnnls.f 13 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325
  1. *DECK WNNLS
  2. SUBROUTINE WNNLS (W, MDW, ME, MA, N, L, PRGOPT, X, RNORM, MODE,
  3. + IWORK, WORK)
  4. C***BEGIN PROLOGUE WNNLS
  5. C***PURPOSE Solve a linearly constrained least squares problem with
  6. C equality constraints and nonnegativity constraints on
  7. C selected variables.
  8. C***LIBRARY SLATEC
  9. C***CATEGORY K1A2A
  10. C***TYPE SINGLE PRECISION (WNNLS-S, DWNNLS-D)
  11. C***KEYWORDS CONSTRAINED LEAST SQUARES, CURVE FITTING, DATA FITTING,
  12. C EQUALITY CONSTRAINTS, INEQUALITY CONSTRAINTS,
  13. C NONNEGATIVITY CONSTRAINTS, QUADRATIC PROGRAMMING
  14. C***AUTHOR Hanson, R. J., (SNLA)
  15. C Haskell, K. H., (SNLA)
  16. C***DESCRIPTION
  17. C
  18. C Abstract
  19. C
  20. C This subprogram solves a linearly constrained least squares
  21. C problem. Suppose there are given matrices E and A of
  22. C respective dimensions ME by N and MA by N, and vectors F
  23. C and B of respective lengths ME and MA. This subroutine
  24. C solves the problem
  25. C
  26. C EX = F, (equations to be exactly satisfied)
  27. C
  28. C AX = B, (equations to be approximately satisfied,
  29. C in the least squares sense)
  30. C
  31. C subject to components L+1,...,N nonnegative
  32. C
  33. C Any values ME.GE.0, MA.GE.0 and 0.LE. L .LE.N are permitted.
  34. C
  35. C The problem is reposed as problem WNNLS
  36. C
  37. C (WT*E)X = (WT*F)
  38. C ( A) ( B), (least squares)
  39. C subject to components L+1,...,N nonnegative.
  40. C
  41. C The subprogram chooses the heavy weight (or penalty parameter) WT.
  42. C
  43. C The parameters for WNNLS are
  44. C
  45. C INPUT..
  46. C
  47. C W(*,*),MDW, The array W(*,*) is double subscripted with first
  48. C ME,MA,N,L dimensioning parameter equal to MDW. For this
  49. C discussion let us call M = ME + MA. Then MDW
  50. C must satisfy MDW.GE.M. The condition MDW.LT.M
  51. C is an error.
  52. C
  53. C The array W(*,*) contains the matrices and vectors
  54. C
  55. C (E F)
  56. C (A B)
  57. C
  58. C in rows and columns 1,...,M and 1,...,N+1
  59. C respectively. Columns 1,...,L correspond to
  60. C unconstrained variables X(1),...,X(L). The
  61. C remaining variables are constrained to be
  62. C nonnegative. The condition L.LT.0 or L.GT.N is
  63. C an error.
  64. C
  65. C PRGOPT(*) This real-valued array is the option vector.
  66. C If the user is satisfied with the nominal
  67. C subprogram features set
  68. C
  69. C PRGOPT(1)=1 (or PRGOPT(1)=1.0)
  70. C
  71. C Otherwise PRGOPT(*) is a linked list consisting of
  72. C groups of data of the following form
  73. C
  74. C LINK
  75. C KEY
  76. C DATA SET
  77. C
  78. C The parameters LINK and KEY are each one word.
  79. C The DATA SET can be comprised of several words.
  80. C The number of items depends on the value of KEY.
  81. C The value of LINK points to the first
  82. C entry of the next group of data within
  83. C PRGOPT(*). The exception is when there are
  84. C no more options to change. In that
  85. C case LINK=1 and the values KEY and DATA SET
  86. C are not referenced. The general layout of
  87. C PRGOPT(*) is as follows.
  88. C
  89. C ...PRGOPT(1)=LINK1 (link to first entry of next group)
  90. C . PRGOPT(2)=KEY1 (key to the option change)
  91. C . PRGOPT(3)=DATA VALUE (data value for this change)
  92. C . .
  93. C . .
  94. C . .
  95. C ...PRGOPT(LINK1)=LINK2 (link to the first entry of
  96. C . next group)
  97. C . PRGOPT(LINK1+1)=KEY2 (key to the option change)
  98. C . PRGOPT(LINK1+2)=DATA VALUE
  99. C ... .
  100. C . .
  101. C . .
  102. C ...PRGOPT(LINK)=1 (no more options to change)
  103. C
  104. C Values of LINK that are nonpositive are errors.
  105. C A value of LINK.GT.NLINK=100000 is also an error.
  106. C This helps prevent using invalid but positive
  107. C values of LINK that will probably extend
  108. C beyond the program limits of PRGOPT(*).
  109. C Unrecognized values of KEY are ignored. The
  110. C order of the options is arbitrary and any number
  111. C of options can be changed with the following
  112. C restriction. To prevent cycling in the
  113. C processing of the option array a count of the
  114. C number of options changed is maintained.
  115. C Whenever this count exceeds NOPT=1000 an error
  116. C message is printed and the subprogram returns.
  117. C
  118. C OPTIONS..
  119. C
  120. C KEY=6
  121. C Scale the nonzero columns of the
  122. C entire data matrix
  123. C (E)
  124. C (A)
  125. C to have length one. The DATA SET for
  126. C this option is a single value. It must
  127. C be nonzero if unit length column scaling is
  128. C desired.
  129. C
  130. C KEY=7
  131. C Scale columns of the entire data matrix
  132. C (E)
  133. C (A)
  134. C with a user-provided diagonal matrix.
  135. C The DATA SET for this option consists
  136. C of the N diagonal scaling factors, one for
  137. C each matrix column.
  138. C
  139. C KEY=8
  140. C Change the rank determination tolerance from
  141. C the nominal value of SQRT(SRELPR). This quantity
  142. C can be no smaller than SRELPR, The arithmetic-
  143. C storage precision. The quantity used
  144. C here is internally restricted to be at
  145. C least SRELPR. The DATA SET for this option
  146. C is the new tolerance.
  147. C
  148. C KEY=9
  149. C Change the blow-up parameter from the
  150. C nominal value of SQRT(SRELPR). The reciprocal of
  151. C this parameter is used in rejecting solution
  152. C components as too large when a variable is
  153. C first brought into the active set. Too large
  154. C means that the proposed component times the
  155. C reciprocal of the parameter is not less than
  156. C the ratio of the norms of the right-side
  157. C vector and the data matrix.
  158. C This parameter can be no smaller than SRELPR,
  159. C the arithmetic-storage precision.
  160. C
  161. C For example, suppose we want to provide
  162. C a diagonal matrix to scale the problem
  163. C matrix and change the tolerance used for
  164. C determining linear dependence of dropped col
  165. C vectors. For these options the dimensions of
  166. C PRGOPT(*) must be at least N+6. The FORTRAN
  167. C statements defining these options would
  168. C be as follows.
  169. C
  170. C PRGOPT(1)=N+3 (link to entry N+3 in PRGOPT(*))
  171. C PRGOPT(2)=7 (user-provided scaling key)
  172. C
  173. C CALL SCOPY(N,D,1,PRGOPT(3),1) (copy the N
  174. C scaling factors from a user array called D(*)
  175. C into PRGOPT(3)-PRGOPT(N+2))
  176. C
  177. C PRGOPT(N+3)=N+6 (link to entry N+6 of PRGOPT(*))
  178. C PRGOPT(N+4)=8 (linear dependence tolerance key)
  179. C PRGOPT(N+5)=... (new value of the tolerance)
  180. C
  181. C PRGOPT(N+6)=1 (no more options to change)
  182. C
  183. C
  184. C IWORK(1), The amounts of working storage actually allocated
  185. C IWORK(2) for the working arrays WORK(*) and IWORK(*),
  186. C respectively. These quantities are compared with
  187. C the actual amounts of storage needed for WNNLS( ).
  188. C Insufficient storage allocated for either WORK(*)
  189. C or IWORK(*) is considered an error. This feature
  190. C was included in WNNLS( ) because miscalculating
  191. C the storage formulas for WORK(*) and IWORK(*)
  192. C might very well lead to subtle and hard-to-find
  193. C execution errors.
  194. C
  195. C The length of WORK(*) must be at least
  196. C
  197. C LW = ME+MA+5*N
  198. C This test will not be made if IWORK(1).LE.0.
  199. C
  200. C The length of IWORK(*) must be at least
  201. C
  202. C LIW = ME+MA+N
  203. C This test will not be made if IWORK(2).LE.0.
  204. C
  205. C OUTPUT..
  206. C
  207. C X(*) An array dimensioned at least N, which will
  208. C contain the N components of the solution vector
  209. C on output.
  210. C
  211. C RNORM The residual norm of the solution. The value of
  212. C RNORM contains the residual vector length of the
  213. C equality constraints and least squares equations.
  214. C
  215. C MODE The value of MODE indicates the success or failure
  216. C of the subprogram.
  217. C
  218. C MODE = 0 Subprogram completed successfully.
  219. C
  220. C = 1 Max. number of iterations (equal to
  221. C 3*(N-L)) exceeded. Nearly all problems
  222. C should complete in fewer than this
  223. C number of iterations. An approximate
  224. C solution and its corresponding residual
  225. C vector length are in X(*) and RNORM.
  226. C
  227. C = 2 Usage error occurred. The offending
  228. C condition is noted with the error
  229. C processing subprogram, XERMSG( ).
  230. C
  231. C User-designated
  232. C Working arrays..
  233. C
  234. C WORK(*) A real-valued working array of length at least
  235. C M + 5*N.
  236. C
  237. C IWORK(*) An integer-valued working array of length at least
  238. C M+N.
  239. C
  240. C***REFERENCES K. H. Haskell and R. J. Hanson, An algorithm for
  241. C linear least squares problems with equality and
  242. C nonnegativity constraints, Report SAND77-0552, Sandia
  243. C Laboratories, June 1978.
  244. C K. H. Haskell and R. J. Hanson, Selected algorithms for
  245. C the linearly constrained least squares problem - a
  246. C users guide, Report SAND78-1290, Sandia Laboratories,
  247. C August 1979.
  248. C K. H. Haskell and R. J. Hanson, An algorithm for
  249. C linear least squares problems with equality and
  250. C nonnegativity constraints, Mathematical Programming
  251. C 21 (1981), pp. 98-118.
  252. C R. J. Hanson and K. H. Haskell, Two algorithms for the
  253. C linearly constrained least squares problem, ACM
  254. C Transactions on Mathematical Software, September 1982.
  255. C C. L. Lawson and R. J. Hanson, Solving Least Squares
  256. C Problems, Prentice-Hall, Inc., 1974.
  257. C***ROUTINES CALLED WNLSM, XERMSG
  258. C***REVISION HISTORY (YYMMDD)
  259. C 790701 DATE WRITTEN
  260. C 890206 REVISION DATE from Version 3.2
  261. C 890618 Completely restructured and revised. (WRB & RWC)
  262. C 891214 Prologue converted to Version 4.0 format. (BAB)
  263. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  264. C 900510 Convert XERRWV calls to XERMSG calls. (RWC)
  265. C 920501 Reformatted the REFERENCES section. (WRB)
  266. C***END PROLOGUE WNNLS
  267. REAL PRGOPT(*), RNORM, W(MDW,*), WORK(*), X(*)
  268. INTEGER IWORK(*)
  269. CHARACTER*8 XERN1
  270. C
  271. C
  272. C***FIRST EXECUTABLE STATEMENT WNNLS
  273. MODE = 0
  274. IF (MA+ME.LE.0 .OR. N.LE.0) RETURN
  275. IF (IWORK(1).GT.0) THEN
  276. LW = ME + MA + 5*N
  277. IF (IWORK(1).LT.LW) THEN
  278. WRITE (XERN1, '(I8)') LW
  279. CALL XERMSG ('SLATEC', 'WNNLS', 'INSUFFICIENT STORAGE ' //
  280. * 'ALLOCATED FOR WORK(*), NEED LW = ' // XERN1, 2, 1)
  281. MODE = 2
  282. RETURN
  283. ENDIF
  284. ENDIF
  285. C
  286. IF (IWORK(2).GT.0) THEN
  287. LIW = ME + MA + N
  288. IF (IWORK(2).LT.LIW) THEN
  289. WRITE (XERN1, '(I8)') LIW
  290. CALL XERMSG ('SLATEC', 'WNNLS', 'INSUFFICIENT STORAGE ' //
  291. * 'ALLOCATED FOR IWORK(*), NEED LIW = ' // XERN1, 2, 1)
  292. MODE = 2
  293. RETURN
  294. ENDIF
  295. ENDIF
  296. C
  297. IF (MDW.LT.ME+MA) THEN
  298. CALL XERMSG ('SLATEC', 'WNNLS',
  299. * 'THE VALUE MDW.LT.ME+MA IS AN ERROR', 1, 1)
  300. MODE = 2
  301. RETURN
  302. ENDIF
  303. C
  304. IF (L.LT.0 .OR. L.GT.N) THEN
  305. CALL XERMSG ('SLATEC', 'WNNLS',
  306. * 'L.GE.0 .AND. L.LE.N IS REQUIRED', 2, 1)
  307. MODE = 2
  308. RETURN
  309. ENDIF
  310. C
  311. C THE PURPOSE OF THIS SUBROUTINE IS TO BREAK UP THE ARRAYS
  312. C WORK(*) AND IWORK(*) INTO SEPARATE WORK ARRAYS
  313. C REQUIRED BY THE MAIN SUBROUTINE WNLSM( ).
  314. C
  315. L1 = N + 1
  316. L2 = L1 + N
  317. L3 = L2 + ME + MA
  318. L4 = L3 + N
  319. L5 = L4 + N
  320. C
  321. CALL WNLSM(W, MDW, ME, MA, N, L, PRGOPT, X, RNORM, MODE, IWORK,
  322. * IWORK(L1), WORK(1), WORK(L1), WORK(L2), WORK(L3),
  323. * WORK(L4), WORK(L5))
  324. RETURN
  325. END