cqrsl.f 9.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291
  1. *DECK CQRSL
  2. SUBROUTINE CQRSL (X, LDX, N, K, QRAUX, Y, QY, QTY, B, RSD, XB,
  3. + JOB, INFO)
  4. C***BEGIN PROLOGUE CQRSL
  5. C***PURPOSE Apply the output of CQRDC to compute coordinate transfor-
  6. C mations, projections, and least squares solutions.
  7. C***LIBRARY SLATEC (LINPACK)
  8. C***CATEGORY D9, D2C1
  9. C***TYPE COMPLEX (SQRSL-S, DQRSL-D, CQRSL-C)
  10. C***KEYWORDS LINEAR ALGEBRA, LINPACK, MATRIX, ORTHOGONAL TRIANGULAR,
  11. C SOLVE
  12. C***AUTHOR Stewart, G. W., (U. of Maryland)
  13. C***DESCRIPTION
  14. C
  15. C CQRSL applies the output of CQRDC to compute coordinate
  16. C transformations, projections, and least squares solutions.
  17. C For K .LE. MIN(N,P), let XK be the matrix
  18. C
  19. C XK = (X(JVPT(1)),X(JVPT(2)), ... ,X(JVPT(K)))
  20. C
  21. C formed from columns JVPT(1), ... ,JVPT(K) of the original
  22. C N x P matrix X that was input to CQRDC (if no pivoting was
  23. C done, XK consists of the first K columns of X in their
  24. C original order). CQRDC produces a factored unitary matrix Q
  25. C and an upper triangular matrix R such that
  26. C
  27. C XK = Q * (R)
  28. C (0)
  29. C
  30. C This information is contained in coded form in the arrays
  31. C X and QRAUX.
  32. C
  33. C On Entry
  34. C
  35. C X COMPLEX(LDX,P).
  36. C X contains the output of CQRDC.
  37. C
  38. C LDX INTEGER.
  39. C LDX is the leading dimension of the array X.
  40. C
  41. C N INTEGER.
  42. C N is the number of rows of the matrix XK. It must
  43. C have the same value as N in CQRDC.
  44. C
  45. C K INTEGER.
  46. C K is the number of columns of the matrix XK. K
  47. C must not be greater than (N,P), where P is the
  48. C same as in the calling sequence to CQRDC.
  49. C
  50. C QRAUX COMPLEX(P).
  51. C QRAUX contains the auxiliary output from CQRDC.
  52. C
  53. C Y COMPLEX(N)
  54. C Y contains an N-vector that is to be manipulated
  55. C by CQRSL.
  56. C
  57. C JOB INTEGER.
  58. C JOB specifies what is to be computed. JOB has
  59. C the decimal expansion ABCDE, with the following
  60. C meaning.
  61. C
  62. C If A .NE. 0, compute QY.
  63. C If B,C,D, or E .NE. 0, compute QTY.
  64. C If C .NE. 0, compute B.
  65. C If D .NE. 0, compute RSD .
  66. C If E .NE. 0, compute XB.
  67. C
  68. C Note that a request to compute B, RSD, or XB
  69. C automatically triggers the computation of QTY, for
  70. C which an array must be provided in the calling
  71. C sequence.
  72. C
  73. C On Return
  74. C
  75. C QY COMPLEX(N).
  76. C QY contains Q*Y, if its computation has been
  77. C requested.
  78. C
  79. C QTY COMPLEX(N).
  80. C QTY contains CTRANS(Q)*Y, if its computation has
  81. C been requested. Here CTRANS(Q) is the conjugate
  82. C transpose of the matrix Q.
  83. C
  84. C B COMPLEX(K)
  85. C B contains the solution of the least squares problem
  86. C
  87. C minimize NORM2(Y - XK*B),
  88. C
  89. C if its computation has been requested. (Note that
  90. C if pivoting was requested in CQRDC, the J-th
  91. C component of B will be associated with column JVPT(J)
  92. C of the original matrix X that was input into CQRDC.)
  93. C
  94. C RSD COMPLEX(N).
  95. C RSD contains the least squares residual Y - XK*B,
  96. C if its computation has been requested. RSD is
  97. C also the orthogonal projection of Y onto the
  98. C orthogonal complement of the column space of XK.
  99. C
  100. C XB COMPLEX(N).
  101. C XB contains the least squares approximation XK*B,
  102. C if its computation has been requested. XB is also
  103. C the orthogonal projection of Y onto the column space
  104. C of X.
  105. C
  106. C INFO INTEGER.
  107. C INFO is zero unless the computation of B has
  108. C been requested and R is exactly singular. In
  109. C this case, INFO is the index of the first zero
  110. C diagonal element of R and B is left unaltered.
  111. C
  112. C The parameters QY, QTY, B, RSD, and XB are not referenced
  113. C if their computation is not requested and in this case
  114. C can be replaced by dummy variables in the calling program.
  115. C To save storage, the user may in some cases use the same
  116. C array for different parameters in the calling sequence. A
  117. C frequently occurring example is when one wishes to compute
  118. C any of B, RSD, or XB and does not need Y or QTY. In this
  119. C case one may identify Y, QTY, and one of B, RSD, or XB, while
  120. C providing separate arrays for anything else that is to be
  121. C computed. Thus the calling sequence
  122. C
  123. C CALL CQRSL(X,LDX,N,K,QRAUX,Y,DUM,Y,B,Y,DUM,110,INFO)
  124. C
  125. C will result in the computation of B and RSD, with RSD
  126. C overwriting Y. More generally, each item in the following
  127. C list contains groups of permissible identifications for
  128. C a single calling sequence.
  129. C
  130. C 1. (Y,QTY,B) (RSD) (XB) (QY)
  131. C
  132. C 2. (Y,QTY,RSD) (B) (XB) (QY)
  133. C
  134. C 3. (Y,QTY,XB) (B) (RSD) (QY)
  135. C
  136. C 4. (Y,QY) (QTY,B) (RSD) (XB)
  137. C
  138. C 5. (Y,QY) (QTY,RSD) (B) (XB)
  139. C
  140. C 6. (Y,QY) (QTY,XB) (B) (RSD)
  141. C
  142. C In any group the value returned in the array allocated to
  143. C the group corresponds to the last member of the group.
  144. C
  145. C***REFERENCES J. J. Dongarra, J. R. Bunch, C. B. Moler, and G. W.
  146. C Stewart, LINPACK Users' Guide, SIAM, 1979.
  147. C***ROUTINES CALLED CAXPY, CCOPY, CDOTC
  148. C***REVISION HISTORY (YYMMDD)
  149. C 780814 DATE WRITTEN
  150. C 890531 Changed all specific intrinsics to generic. (WRB)
  151. C 890831 Modified array declarations. (WRB)
  152. C 890831 REVISION DATE from Version 3.2
  153. C 891214 Prologue converted to Version 4.0 format. (BAB)
  154. C 900326 Removed duplicate information from DESCRIPTION section.
  155. C (WRB)
  156. C 920501 Reformatted the REFERENCES section. (WRB)
  157. C***END PROLOGUE CQRSL
  158. INTEGER LDX,N,K,JOB,INFO
  159. COMPLEX X(LDX,*),QRAUX(*),Y(*),QY(*),QTY(*),B(*),RSD(*),XB(*)
  160. C
  161. INTEGER I,J,JJ,JU,KP1
  162. COMPLEX CDOTC,T,TEMP
  163. LOGICAL CB,CQY,CQTY,CR,CXB
  164. COMPLEX ZDUM
  165. REAL CABS1
  166. CABS1(ZDUM) = ABS(REAL(ZDUM)) + ABS(AIMAG(ZDUM))
  167. C***FIRST EXECUTABLE STATEMENT CQRSL
  168. C
  169. C SET INFO FLAG.
  170. C
  171. INFO = 0
  172. C
  173. C DETERMINE WHAT IS TO BE COMPUTED.
  174. C
  175. CQY = JOB/10000 .NE. 0
  176. CQTY = MOD(JOB,10000) .NE. 0
  177. CB = MOD(JOB,1000)/100 .NE. 0
  178. CR = MOD(JOB,100)/10 .NE. 0
  179. CXB = MOD(JOB,10) .NE. 0
  180. JU = MIN(K,N-1)
  181. C
  182. C SPECIAL ACTION WHEN N=1.
  183. C
  184. IF (JU .NE. 0) GO TO 40
  185. IF (CQY) QY(1) = Y(1)
  186. IF (CQTY) QTY(1) = Y(1)
  187. IF (CXB) XB(1) = Y(1)
  188. IF (.NOT.CB) GO TO 30
  189. IF (CABS1(X(1,1)) .NE. 0.0E0) GO TO 10
  190. INFO = 1
  191. GO TO 20
  192. 10 CONTINUE
  193. B(1) = Y(1)/X(1,1)
  194. 20 CONTINUE
  195. 30 CONTINUE
  196. IF (CR) RSD(1) = (0.0E0,0.0E0)
  197. GO TO 250
  198. 40 CONTINUE
  199. C
  200. C SET UP TO COMPUTE QY OR QTY.
  201. C
  202. IF (CQY) CALL CCOPY(N,Y,1,QY,1)
  203. IF (CQTY) CALL CCOPY(N,Y,1,QTY,1)
  204. IF (.NOT.CQY) GO TO 70
  205. C
  206. C COMPUTE QY.
  207. C
  208. DO 60 JJ = 1, JU
  209. J = JU - JJ + 1
  210. IF (CABS1(QRAUX(J)) .EQ. 0.0E0) GO TO 50
  211. TEMP = X(J,J)
  212. X(J,J) = QRAUX(J)
  213. T = -CDOTC(N-J+1,X(J,J),1,QY(J),1)/X(J,J)
  214. CALL CAXPY(N-J+1,T,X(J,J),1,QY(J),1)
  215. X(J,J) = TEMP
  216. 50 CONTINUE
  217. 60 CONTINUE
  218. 70 CONTINUE
  219. IF (.NOT.CQTY) GO TO 100
  220. C
  221. C COMPUTE CTRANS(Q)*Y.
  222. C
  223. DO 90 J = 1, JU
  224. IF (CABS1(QRAUX(J)) .EQ. 0.0E0) GO TO 80
  225. TEMP = X(J,J)
  226. X(J,J) = QRAUX(J)
  227. T = -CDOTC(N-J+1,X(J,J),1,QTY(J),1)/X(J,J)
  228. CALL CAXPY(N-J+1,T,X(J,J),1,QTY(J),1)
  229. X(J,J) = TEMP
  230. 80 CONTINUE
  231. 90 CONTINUE
  232. 100 CONTINUE
  233. C
  234. C SET UP TO COMPUTE B, RSD, OR XB.
  235. C
  236. IF (CB) CALL CCOPY(K,QTY,1,B,1)
  237. KP1 = K + 1
  238. IF (CXB) CALL CCOPY(K,QTY,1,XB,1)
  239. IF (CR .AND. K .LT. N) CALL CCOPY(N-K,QTY(KP1),1,RSD(KP1),1)
  240. IF (.NOT.CXB .OR. KP1 .GT. N) GO TO 120
  241. DO 110 I = KP1, N
  242. XB(I) = (0.0E0,0.0E0)
  243. 110 CONTINUE
  244. 120 CONTINUE
  245. IF (.NOT.CR) GO TO 140
  246. DO 130 I = 1, K
  247. RSD(I) = (0.0E0,0.0E0)
  248. 130 CONTINUE
  249. 140 CONTINUE
  250. IF (.NOT.CB) GO TO 190
  251. C
  252. C COMPUTE B.
  253. C
  254. DO 170 JJ = 1, K
  255. J = K - JJ + 1
  256. IF (CABS1(X(J,J)) .NE. 0.0E0) GO TO 150
  257. INFO = J
  258. GO TO 180
  259. 150 CONTINUE
  260. B(J) = B(J)/X(J,J)
  261. IF (J .EQ. 1) GO TO 160
  262. T = -B(J)
  263. CALL CAXPY(J-1,T,X(1,J),1,B,1)
  264. 160 CONTINUE
  265. 170 CONTINUE
  266. 180 CONTINUE
  267. 190 CONTINUE
  268. IF (.NOT.CR .AND. .NOT.CXB) GO TO 240
  269. C
  270. C COMPUTE RSD OR XB AS REQUIRED.
  271. C
  272. DO 230 JJ = 1, JU
  273. J = JU - JJ + 1
  274. IF (CABS1(QRAUX(J)) .EQ. 0.0E0) GO TO 220
  275. TEMP = X(J,J)
  276. X(J,J) = QRAUX(J)
  277. IF (.NOT.CR) GO TO 200
  278. T = -CDOTC(N-J+1,X(J,J),1,RSD(J),1)/X(J,J)
  279. CALL CAXPY(N-J+1,T,X(J,J),1,RSD(J),1)
  280. 200 CONTINUE
  281. IF (.NOT.CXB) GO TO 210
  282. T = -CDOTC(N-J+1,X(J,J),1,XB(J),1)/X(J,J)
  283. CALL CAXPY(N-J+1,T,X(J,J),1,XB(J),1)
  284. 210 CONTINUE
  285. X(J,J) = TEMP
  286. 220 CONTINUE
  287. 230 CONTINUE
  288. 240 CONTINUE
  289. 250 CONTINUE
  290. RETURN
  291. END