sqrdc.f 7.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223
  1. *DECK SQRDC
  2. SUBROUTINE SQRDC (X, LDX, N, P, QRAUX, JPVT, WORK, JOB)
  3. C***BEGIN PROLOGUE SQRDC
  4. C***PURPOSE Use Householder transformations to compute the QR
  5. C factorization of an N by P matrix. Column pivoting is a
  6. C users option.
  7. C***LIBRARY SLATEC (LINPACK)
  8. C***CATEGORY D5
  9. C***TYPE SINGLE PRECISION (SQRDC-S, DQRDC-D, CQRDC-C)
  10. C***KEYWORDS LINEAR ALGEBRA, LINPACK, MATRIX, ORTHOGONAL TRIANGULAR,
  11. C QR DECOMPOSITION
  12. C***AUTHOR Stewart, G. W., (U. of Maryland)
  13. C***DESCRIPTION
  14. C
  15. C SQRDC uses Householder transformations to compute the QR
  16. C factorization of an N by P matrix X. Column pivoting
  17. C based on the 2-norms of the reduced columns may be
  18. C performed at the user's option.
  19. C
  20. C On Entry
  21. C
  22. C X REAL(LDX,P), where LDX .GE. N.
  23. C X contains the matrix whose decomposition is to be
  24. C computed.
  25. C
  26. C LDX INTEGER.
  27. C LDX is the leading dimension of the array X.
  28. C
  29. C N INTEGER.
  30. C N is the number of rows of the matrix X.
  31. C
  32. C P INTEGER.
  33. C P is the number of columns of the matrix X.
  34. C
  35. C JPVT INTEGER(P).
  36. C JPVT contains integers that control the selection
  37. C of the pivot columns. The K-th column X(K) of X
  38. C is placed in one of three classes according to the
  39. C value of JPVT(K).
  40. C
  41. C If JPVT(K) .GT. 0, then X(K) is an initial
  42. C column.
  43. C
  44. C If JPVT(K) .EQ. 0, then X(K) is a free column.
  45. C
  46. C If JPVT(K) .LT. 0, then X(K) is a final column.
  47. C
  48. C Before the decomposition is computed, initial columns
  49. C are moved to the beginning of the array X and final
  50. C columns to the end. Both initial and final columns
  51. C are frozen in place during the computation and only
  52. C free columns are moved. At the K-th stage of the
  53. C reduction, if X(K) is occupied by a free column,
  54. C it is interchanged with the free column of largest
  55. C reduced norm. JPVT is not referenced if
  56. C JOB .EQ. 0.
  57. C
  58. C WORK REAL(P).
  59. C WORK is a work array. WORK is not referenced if
  60. C JOB .EQ. 0.
  61. C
  62. C JOB INTEGER.
  63. C JOB is an integer that initiates column pivoting.
  64. C If JOB .EQ. 0, no pivoting is done.
  65. C If JOB .NE. 0, pivoting is done.
  66. C
  67. C On Return
  68. C
  69. C X X contains in its upper triangle the upper
  70. C triangular matrix R of the QR factorization.
  71. C Below its diagonal X contains information from
  72. C which the orthogonal part of the decomposition
  73. C can be recovered. Note that if pivoting has
  74. C been requested, the decomposition is not that
  75. C of the original matrix X but that of X
  76. C with its columns permuted as described by JPVT.
  77. C
  78. C QRAUX REAL(P).
  79. C QRAUX contains further information required to recover
  80. C the orthogonal part of the decomposition.
  81. C
  82. C JPVT JPVT(K) contains the index of the column of the
  83. C original matrix that has been interchanged into
  84. C the K-th column, if pivoting was requested.
  85. C
  86. C***REFERENCES J. J. Dongarra, J. R. Bunch, C. B. Moler, and G. W.
  87. C Stewart, LINPACK Users' Guide, SIAM, 1979.
  88. C***ROUTINES CALLED SAXPY, SDOT, SNRM2, SSCAL, SSWAP
  89. C***REVISION HISTORY (YYMMDD)
  90. C 780814 DATE WRITTEN
  91. C 890531 Changed all specific intrinsics to generic. (WRB)
  92. C 890831 Modified array declarations. (WRB)
  93. C 890831 REVISION DATE from Version 3.2
  94. C 891214 Prologue converted to Version 4.0 format. (BAB)
  95. C 900326 Removed duplicate information from DESCRIPTION section.
  96. C (WRB)
  97. C 920501 Reformatted the REFERENCES section. (WRB)
  98. C***END PROLOGUE SQRDC
  99. INTEGER LDX,N,P,JOB
  100. INTEGER JPVT(*)
  101. REAL X(LDX,*),QRAUX(*),WORK(*)
  102. C
  103. INTEGER J,JP,L,LP1,LUP,MAXJ,PL,PU
  104. REAL MAXNRM,SNRM2,TT
  105. REAL SDOT,NRMXL,T
  106. LOGICAL NEGJ,SWAPJ
  107. C
  108. C***FIRST EXECUTABLE STATEMENT SQRDC
  109. PL = 1
  110. PU = 0
  111. IF (JOB .EQ. 0) GO TO 60
  112. C
  113. C PIVOTING HAS BEEN REQUESTED. REARRANGE THE COLUMNS
  114. C ACCORDING TO JPVT.
  115. C
  116. DO 20 J = 1, P
  117. SWAPJ = JPVT(J) .GT. 0
  118. NEGJ = JPVT(J) .LT. 0
  119. JPVT(J) = J
  120. IF (NEGJ) JPVT(J) = -J
  121. IF (.NOT.SWAPJ) GO TO 10
  122. IF (J .NE. PL) CALL SSWAP(N,X(1,PL),1,X(1,J),1)
  123. JPVT(J) = JPVT(PL)
  124. JPVT(PL) = J
  125. PL = PL + 1
  126. 10 CONTINUE
  127. 20 CONTINUE
  128. PU = P
  129. DO 50 JJ = 1, P
  130. J = P - JJ + 1
  131. IF (JPVT(J) .GE. 0) GO TO 40
  132. JPVT(J) = -JPVT(J)
  133. IF (J .EQ. PU) GO TO 30
  134. CALL SSWAP(N,X(1,PU),1,X(1,J),1)
  135. JP = JPVT(PU)
  136. JPVT(PU) = JPVT(J)
  137. JPVT(J) = JP
  138. 30 CONTINUE
  139. PU = PU - 1
  140. 40 CONTINUE
  141. 50 CONTINUE
  142. 60 CONTINUE
  143. C
  144. C COMPUTE THE NORMS OF THE FREE COLUMNS.
  145. C
  146. IF (PU .LT. PL) GO TO 80
  147. DO 70 J = PL, PU
  148. QRAUX(J) = SNRM2(N,X(1,J),1)
  149. WORK(J) = QRAUX(J)
  150. 70 CONTINUE
  151. 80 CONTINUE
  152. C
  153. C PERFORM THE HOUSEHOLDER REDUCTION OF X.
  154. C
  155. LUP = MIN(N,P)
  156. DO 200 L = 1, LUP
  157. IF (L .LT. PL .OR. L .GE. PU) GO TO 120
  158. C
  159. C LOCATE THE COLUMN OF LARGEST NORM AND BRING IT
  160. C INTO THE PIVOT POSITION.
  161. C
  162. MAXNRM = 0.0E0
  163. MAXJ = L
  164. DO 100 J = L, PU
  165. IF (QRAUX(J) .LE. MAXNRM) GO TO 90
  166. MAXNRM = QRAUX(J)
  167. MAXJ = J
  168. 90 CONTINUE
  169. 100 CONTINUE
  170. IF (MAXJ .EQ. L) GO TO 110
  171. CALL SSWAP(N,X(1,L),1,X(1,MAXJ),1)
  172. QRAUX(MAXJ) = QRAUX(L)
  173. WORK(MAXJ) = WORK(L)
  174. JP = JPVT(MAXJ)
  175. JPVT(MAXJ) = JPVT(L)
  176. JPVT(L) = JP
  177. 110 CONTINUE
  178. 120 CONTINUE
  179. QRAUX(L) = 0.0E0
  180. IF (L .EQ. N) GO TO 190
  181. C
  182. C COMPUTE THE HOUSEHOLDER TRANSFORMATION FOR COLUMN L.
  183. C
  184. NRMXL = SNRM2(N-L+1,X(L,L),1)
  185. IF (NRMXL .EQ. 0.0E0) GO TO 180
  186. IF (X(L,L) .NE. 0.0E0) NRMXL = SIGN(NRMXL,X(L,L))
  187. CALL SSCAL(N-L+1,1.0E0/NRMXL,X(L,L),1)
  188. X(L,L) = 1.0E0 + X(L,L)
  189. C
  190. C APPLY THE TRANSFORMATION TO THE REMAINING COLUMNS,
  191. C UPDATING THE NORMS.
  192. C
  193. LP1 = L + 1
  194. IF (P .LT. LP1) GO TO 170
  195. DO 160 J = LP1, P
  196. T = -SDOT(N-L+1,X(L,L),1,X(L,J),1)/X(L,L)
  197. CALL SAXPY(N-L+1,T,X(L,L),1,X(L,J),1)
  198. IF (J .LT. PL .OR. J .GT. PU) GO TO 150
  199. IF (QRAUX(J) .EQ. 0.0E0) GO TO 150
  200. TT = 1.0E0 - (ABS(X(L,J))/QRAUX(J))**2
  201. TT = MAX(TT,0.0E0)
  202. T = TT
  203. TT = 1.0E0 + 0.05E0*TT*(QRAUX(J)/WORK(J))**2
  204. IF (TT .EQ. 1.0E0) GO TO 130
  205. QRAUX(J) = QRAUX(J)*SQRT(T)
  206. GO TO 140
  207. 130 CONTINUE
  208. QRAUX(J) = SNRM2(N-L,X(L+1,J),1)
  209. WORK(J) = QRAUX(J)
  210. 140 CONTINUE
  211. 150 CONTINUE
  212. 160 CONTINUE
  213. 170 CONTINUE
  214. C
  215. C SAVE THE TRANSFORMATION.
  216. C
  217. QRAUX(L) = X(L,L)
  218. X(L,L) = -NRMXL
  219. 180 CONTINUE
  220. 190 CONTINUE
  221. 200 CONTINUE
  222. RETURN
  223. END