lssuds.f 9.5 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273
  1. *DECK LSSUDS
  2. SUBROUTINE LSSUDS (A, X, B, N, M, NRDA, U, NRDU, IFLAG, MLSO,
  3. + IRANK, ISCALE, Q, DIAG, KPIVOT, S, DIV, TD, ISFLG, SCALES)
  4. C***BEGIN PROLOGUE LSSUDS
  5. C***SUBSIDIARY
  6. C***PURPOSE Subsidiary to BVSUP
  7. C***LIBRARY SLATEC
  8. C***TYPE SINGLE PRECISION (LSSUDS-S, DLSSUD-D)
  9. C***AUTHOR Watts, H. A., (SNLA)
  10. C***DESCRIPTION
  11. C
  12. C LSSUDS solves the underdetermined system of equations A Z = B,
  13. C where A is N by M and N .LE. M. In particular, if rank A equals
  14. C IRA, a vector X and a matrix U are determined such that X is the
  15. C UNIQUE solution of smallest length, satisfying A X = B, and the
  16. C columns of U form an orthonormal basis for the null space of A,
  17. C satisfying A U = 0 . Then all solutions Z are given by
  18. C Z = X + C(1)*U(1) + ..... + C(M-IRA)*U(M-IRA)
  19. C where U(J) represents the J-th column of U and the C(J) are
  20. C arbitrary constants.
  21. C If the system of equations are not compatible, only the least
  22. C squares solution of minimal length is computed.
  23. C
  24. C *********************************************************************
  25. C INPUT
  26. C *********************************************************************
  27. C
  28. C A -- Contains the matrix of N equations in M unknowns, A remains
  29. C unchanged, must be dimensioned NRDA by M.
  30. C X -- Solution array of length at least M.
  31. C B -- Given constant vector of length N, B remains unchanged.
  32. C N -- Number of equations, N greater or equal to 1.
  33. C M -- Number of unknowns, M greater or equal to N.
  34. C NRDA -- Row dimension of A, NRDA greater or equal to N.
  35. C U -- Matrix used for solution, must be dimensioned NRDU by
  36. C (M - rank of A).
  37. C (storage for U may be ignored when only the minimal length
  38. C solution X is desired)
  39. C NRDU -- Row dimension of U, NRDU greater or equal to M.
  40. C (if only the minimal length solution is wanted,
  41. C NRDU=0 is acceptable)
  42. C IFLAG -- Status indicator
  43. C =0 for the first call (and for each new problem defined by
  44. C a new matrix A) when the matrix data is treated as exact
  45. C =-K for the first call (and for each new problem defined by
  46. C a new matrix A) when the matrix data is assumed to be
  47. C accurate to about K digits.
  48. C =1 for subsequent calls whenever the matrix A has already
  49. C been decomposed (problems with new vectors B but
  50. C same matrix A can be handled efficiently).
  51. C MLSO -- =0 if only the minimal length solution is wanted.
  52. C =1 if the complete solution is wanted, includes the
  53. C linear space defined by the matrix U.
  54. C IRANK -- Variable used for the rank of A, set by the code.
  55. C ISCALE -- Scaling indicator
  56. C =-1 if the matrix A is to be pre-scaled by
  57. C columns when appropriate.
  58. C If the scaling indicator is not equal to -1
  59. C no scaling will be attempted.
  60. C For most problems scaling will probably not be necessary.
  61. C Q -- Matrix used for the transformation, must be dimensioned
  62. C NRDA by M.
  63. C DIAG,KPIVOT,S, -- Arrays of length at least N used for internal
  64. C DIV,TD,SCALES storage (except for SCALES which is M).
  65. C ISFLG -- Storage for an internal variable.
  66. C
  67. C *********************************************************************
  68. C OUTPUT
  69. C *********************************************************************
  70. C
  71. C IFLAG -- Status indicator
  72. C =1 if solution was obtained.
  73. C =2 if improper input is detected.
  74. C =3 if rank of matrix is less than N.
  75. C To continue, simply reset IFLAG=1 and call LSSUDS again.
  76. C =4 if the system of equations appears to be inconsistent.
  77. C However, the least squares solution of minimal length
  78. C was obtained.
  79. C X -- Minimal length least squares solution of A Z = B
  80. C IRANK -- Numerically determined rank of A, must not be altered
  81. C on succeeding calls with input values of IFLAG=1.
  82. C U -- Matrix whose M-IRANK columns are mutually orthogonal unit
  83. C vectors which span the null space of A. This is to be ignored
  84. C when MLSO was set to zero or IFLAG=4 on output.
  85. C Q -- Contains the strictly upper triangular part of the reduced
  86. C matrix and transformation information.
  87. C DIAG -- Contains the diagonal elements of the triangular reduced
  88. C matrix.
  89. C KPIVOT -- Contains the pivotal information. The row interchanges
  90. C performed on the original matrix are recorded here.
  91. C S -- Contains the solution of the lower triangular system.
  92. C DIV,TD -- Contains transformation information for rank
  93. C deficient problems.
  94. C SCALES -- Contains the column scaling parameters.
  95. C
  96. C *********************************************************************
  97. C
  98. C***SEE ALSO BVSUP
  99. C***REFERENCES H. A. Watts, Solving linear least squares problems
  100. C using SODS/SUDS/CODS, Sandia Report SAND77-0683,
  101. C Sandia Laboratories, 1977.
  102. C***ROUTINES CALLED J4SAVE, OHTROL, ORTHOR, R1MACH, SDOT, XERMAX,
  103. C XERMSG, XGETF, XSETF
  104. C***REVISION HISTORY (YYMMDD)
  105. C 750601 DATE WRITTEN
  106. C 890531 Changed all specific intrinsics to generic. (WRB)
  107. C 890831 Modified array declarations. (WRB)
  108. C 891214 Prologue converted to Version 4.0 format. (BAB)
  109. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  110. C 900328 Added TYPE section. (WRB)
  111. C 900510 Fixed an error message. (RWC)
  112. C 910408 Updated the AUTHOR and REFERENCES sections. (WRB)
  113. C 920501 Reformatted the REFERENCES section. (WRB)
  114. C***END PROLOGUE LSSUDS
  115. DIMENSION A(NRDA,*),X(*),B(*),U(NRDU,*),Q(NRDA,*),
  116. 1 DIAG(*),KPIVOT(*),S(*),DIV(*),TD(*),SCALES(*)
  117. C
  118. C **********************************************************************
  119. C
  120. C MACHINE PRECISION (COMPUTER UNIT ROUNDOFF VALUE) IS DEFINED
  121. C BY THE FUNCTION R1MACH.
  122. C
  123. C***FIRST EXECUTABLE STATEMENT LSSUDS
  124. URO = R1MACH(4)
  125. C
  126. C **********************************************************************
  127. C
  128. IF (N .LT. 1 .OR. M .LT. N .OR. NRDA .LT. N) GO TO 1
  129. IF (NRDU .NE. 0 .AND. NRDU .LT. M) GO TO 1
  130. IF (IFLAG .LE. 0) GO TO 5
  131. IF (IFLAG .EQ. 1) GO TO 25
  132. C
  133. C INVALID INPUT FOR LSSUDS
  134. 1 IFLAG=2
  135. CALL XERMSG ('SLATEC', 'LSSUDS', 'INVALID INPUT PARAMETERS.', 2,
  136. + 1)
  137. RETURN
  138. C
  139. 5 CALL XGETF(NFATAL)
  140. MAXMES = J4SAVE (4,0,.FALSE.)
  141. ISFLG=-15
  142. IF (IFLAG .EQ. 0) GO TO 7
  143. ISFLG=IFLAG
  144. NFAT = -1
  145. IF (NFATAL .EQ. 0) NFAT=0
  146. CALL XSETF(NFAT)
  147. CALL XERMAX(1)
  148. C
  149. C COPY MATRIX A INTO MATRIX Q
  150. C
  151. 7 DO 10 K=1,M
  152. DO 10 J=1,N
  153. 10 Q(J,K)=A(J,K)
  154. C
  155. C USE ORTHOGONAL TRANSFORMATIONS TO REDUCE Q TO LOWER
  156. C TRIANGULAR FORM
  157. C
  158. CALL ORTHOR(Q,N,M,NRDA,IFLAG,IRANK,ISCALE,DIAG,KPIVOT,SCALES,
  159. 1 DIV,TD)
  160. C
  161. CALL XSETF(NFATAL)
  162. CALL XERMAX(MAXMES)
  163. IF (IRANK .EQ. N) GO TO 15
  164. C
  165. C FOR RANK DEFICIENT PROBLEMS USE ADDITIONAL ORTHOGONAL
  166. C TRANSFORMATIONS TO FURTHER REDUCE Q
  167. C
  168. IF (IRANK .NE. 0) CALL OHTROL(Q,N,NRDA,DIAG,IRANK,DIV,TD)
  169. RETURN
  170. C
  171. C STORE DIVISORS FOR THE TRIANGULAR SOLUTION
  172. C
  173. 15 DO 20 K=1,N
  174. 20 DIV(K)=DIAG(K)
  175. C
  176. C
  177. 25 IF (IRANK .GT. 0) GO TO 40
  178. C
  179. C SPECIAL CASE FOR THE NULL MATRIX
  180. DO 35 K=1,M
  181. X(K)=0.
  182. IF (MLSO .EQ. 0) GO TO 35
  183. U(K,K)=1.
  184. DO 30 J=1,M
  185. IF (J .EQ. K) GO TO 30
  186. U(J,K)=0.
  187. 30 CONTINUE
  188. 35 CONTINUE
  189. DO 37 K=1,N
  190. IF (B(K) .GT. 0.) IFLAG=4
  191. 37 CONTINUE
  192. RETURN
  193. C
  194. C COPY CONSTANT VECTOR INTO S AFTER FIRST INTERCHANGING
  195. C THE ELEMENTS ACCORDING TO THE PIVOTAL SEQUENCE
  196. C
  197. 40 DO 45 K=1,N
  198. KP=KPIVOT(K)
  199. 45 X(K)=B(KP)
  200. DO 50 K=1,N
  201. 50 S(K)=X(K)
  202. C
  203. IRP=IRANK+1
  204. NU=1
  205. IF (MLSO .EQ. 0) NU=0
  206. IF (IRANK .EQ. N) GO TO 60
  207. C
  208. C FOR RANK DEFICIENT PROBLEMS WE MUST APPLY THE
  209. C ORTHOGONAL TRANSFORMATION TO S
  210. C WE ALSO CHECK TO SEE IF THE SYSTEM APPEARS TO BE INCONSISTENT
  211. C
  212. NMIR=N-IRANK
  213. SS=SDOT(N,S(1),1,S(1),1)
  214. DO 55 L=1,IRANK
  215. K=IRP-L
  216. GAM=((TD(K)*S(K))+SDOT(NMIR,Q(IRP,K),1,S(IRP),1))/
  217. 1 (TD(K)*DIV(K))
  218. S(K)=S(K)+GAM*TD(K)
  219. DO 55 J=IRP,N
  220. 55 S(J)=S(J)+GAM*Q(J,K)
  221. RES=SDOT(NMIR,S(IRP),1,S(IRP),1)
  222. IF (RES .LE. SS*(10.*MAX(10.**ISFLG,10.*URO))**2) GO TO 60
  223. C
  224. C INCONSISTENT SYSTEM
  225. IFLAG=4
  226. NU=0
  227. C
  228. C APPLY FORWARD SUBSTITUTION TO SOLVE LOWER TRIANGULAR SYSTEM
  229. C
  230. 60 S(1)=S(1)/DIV(1)
  231. IF (IRANK .EQ. 1) GO TO 70
  232. DO 65 K=2,IRANK
  233. 65 S(K)=(S(K)-SDOT(K-1,Q(K,1),NRDA,S(1),1))/DIV(K)
  234. C
  235. C INITIALIZE X VECTOR AND THEN APPLY ORTHOGONAL TRANSFORMATION
  236. C
  237. 70 DO 75 K=1,M
  238. X(K)=0.
  239. IF (K .LE. IRANK) X(K)=S(K)
  240. 75 CONTINUE
  241. C
  242. DO 80 JR=1,IRANK
  243. J=IRP-JR
  244. MJ=M-J+1
  245. GAMMA=SDOT(MJ,Q(J,J),NRDA,X(J),1)/(DIAG(J)*Q(J,J))
  246. DO 80 K=J,M
  247. 80 X(K)=X(K)+GAMMA*Q(J,K)
  248. C
  249. C RESCALE ANSWERS AS DICTATED
  250. C
  251. DO 85 K=1,M
  252. 85 X(K)=X(K)*SCALES(K)
  253. C
  254. IF ((NU .EQ. 0) .OR. (M .EQ. IRANK)) RETURN
  255. C
  256. C INITIALIZE U MATRIX AND THEN APPLY ORTHOGONAL TRANSFORMATION
  257. C
  258. L=M-IRANK
  259. DO 100 K=1,L
  260. DO 90 I=1,M
  261. U(I,K)=0.
  262. IF (I .EQ. IRANK+K) U(I,K)=1.
  263. 90 CONTINUE
  264. C
  265. DO 100 JR=1,IRANK
  266. J=IRP-JR
  267. MJ=M-J+1
  268. GAMMA=SDOT(MJ,Q(J,J),NRDA,U(J,K),1)/(DIAG(J)*Q(J,J))
  269. DO 100 I=J,M
  270. 100 U(I,K)=U(I,K)+GAMMA*Q(J,I)
  271. C
  272. RETURN
  273. END