dchdd.f 6.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202
  1. *DECK DCHDD
  2. SUBROUTINE DCHDD (R, LDR, P, X, Z, LDZ, NZ, Y, RHO, C, S, INFO)
  3. C***BEGIN PROLOGUE DCHDD
  4. C***PURPOSE Downdate an augmented Cholesky decomposition or the
  5. C triangular factor of an augmented QR decomposition.
  6. C***LIBRARY SLATEC (LINPACK)
  7. C***CATEGORY D7B
  8. C***TYPE DOUBLE PRECISION (SCHDD-S, DCHDD-D, CCHDD-C)
  9. C***KEYWORDS CHOLESKY DECOMPOSITION, DOWNDATE, LINEAR ALGEBRA, LINPACK,
  10. C MATRIX
  11. C***AUTHOR Stewart, G. W., (U. of Maryland)
  12. C***DESCRIPTION
  13. C
  14. C DCHDD downdates an augmented Cholesky decomposition or the
  15. C triangular factor of an augmented QR decomposition.
  16. C Specifically, given an upper triangular matrix R of order P, a
  17. C row vector X, a column vector Z, and a scalar Y, DCHDD
  18. C determines an orthogonal matrix U and a scalar ZETA such that
  19. C
  20. C (R Z ) (RR ZZ)
  21. C U * ( ) = ( ) ,
  22. C (0 ZETA) ( X Y)
  23. C
  24. C where RR is upper triangular. If R and Z have been obtained
  25. C from the factorization of a least squares problem, then
  26. C RR and ZZ are the factors corresponding to the problem
  27. C with the observation (X,Y) removed. In this case, if RHO
  28. C is the norm of the residual vector, then the norm of
  29. C the residual vector of the downdated problem is
  30. C SQRT(RHO**2 - ZETA**2). DCHDD will simultaneously downdate
  31. C several triplets (Z,Y,RHO) along with R.
  32. C For a less terse description of what DCHDD does and how
  33. C it may be applied, see the LINPACK guide.
  34. C
  35. C The matrix U is determined as the product U(1)*...*U(P)
  36. C where U(I) is a rotation in the (P+1,I)-plane of the
  37. C form
  38. C
  39. C ( C(I) -S(I) )
  40. C ( ) .
  41. C ( S(I) C(I) )
  42. C
  43. C The rotations are chosen so that C(I) is double precision.
  44. C
  45. C The user is warned that a given downdating problem may
  46. C be impossible to accomplish or may produce
  47. C inaccurate results. For example, this can happen
  48. C if X is near a vector whose removal will reduce the
  49. C rank of R. Beware.
  50. C
  51. C On Entry
  52. C
  53. C R DOUBLE PRECISION(LDR,P), where LDR .GE. P.
  54. C R contains the upper triangular matrix
  55. C that is to be downdated. The part of R
  56. C below the diagonal is not referenced.
  57. C
  58. C LDR INTEGER.
  59. C LDR is the leading dimension of the array R.
  60. C
  61. C P INTEGER.
  62. C P is the order of the matrix R.
  63. C
  64. C X DOUBLE PRECISION(P).
  65. C X contains the row vector that is to
  66. C be removed from R. X is not altered by DCHDD.
  67. C
  68. C Z DOUBLE PRECISION(LDZ,N)Z), where LDZ .GE. P.
  69. C Z is an array of NZ P-vectors which
  70. C are to be downdated along with R.
  71. C
  72. C LDZ INTEGER.
  73. C LDZ is the leading dimension of the array Z.
  74. C
  75. C NZ INTEGER.
  76. C NZ is the number of vectors to be downdated
  77. C NZ may be zero, in which case Z, Y, and RHO
  78. C are not referenced.
  79. C
  80. C Y DOUBLE PRECISION(NZ).
  81. C Y contains the scalars for the downdating
  82. C of the vectors Z. Y is not altered by DCHDD.
  83. C
  84. C RHO DOUBLE PRECISION(NZ).
  85. C RHO contains the norms of the residual
  86. C vectors that are to be downdated.
  87. C
  88. C On Return
  89. C
  90. C R
  91. C Z contain the downdated quantities.
  92. C RHO
  93. C
  94. C C DOUBLE PRECISION(P).
  95. C C contains the cosines of the transforming
  96. C rotations.
  97. C
  98. C S DOUBLE PRECISION(P).
  99. C S contains the sines of the transforming
  100. C rotations.
  101. C
  102. C INFO INTEGER.
  103. C INFO is set as follows.
  104. C
  105. C INFO = 0 if the entire downdating
  106. C was successful.
  107. C
  108. C INFO =-1 if R could not be downdated.
  109. C in this case, all quantities
  110. C are left unaltered.
  111. C
  112. C INFO = 1 if some RHO could not be
  113. C downdated. The offending RHO's are
  114. C set to -1.
  115. C
  116. C***REFERENCES J. J. Dongarra, J. R. Bunch, C. B. Moler, and G. W.
  117. C Stewart, LINPACK Users' Guide, SIAM, 1979.
  118. C***ROUTINES CALLED DDOT, DNRM2
  119. C***REVISION HISTORY (YYMMDD)
  120. C 780814 DATE WRITTEN
  121. C 890531 Changed all specific intrinsics to generic. (WRB)
  122. C 890831 Modified array declarations. (WRB)
  123. C 890831 REVISION DATE from Version 3.2
  124. C 891214 Prologue converted to Version 4.0 format. (BAB)
  125. C 900326 Removed duplicate information from DESCRIPTION section.
  126. C (WRB)
  127. C 920501 Reformatted the REFERENCES section. (WRB)
  128. C***END PROLOGUE DCHDD
  129. INTEGER LDR,P,LDZ,NZ,INFO
  130. DOUBLE PRECISION R(LDR,*),X(*),Z(LDZ,*),Y(*),S(*)
  131. DOUBLE PRECISION RHO(*),C(*)
  132. C
  133. INTEGER I,II,J
  134. DOUBLE PRECISION A,ALPHA,AZETA,NORM,DNRM2
  135. DOUBLE PRECISION DDOT,T,ZETA,B,XX,SCALE
  136. C
  137. C SOLVE THE SYSTEM TRANS(R)*A = X, PLACING THE RESULT
  138. C IN THE ARRAY S.
  139. C
  140. C***FIRST EXECUTABLE STATEMENT DCHDD
  141. INFO = 0
  142. S(1) = X(1)/R(1,1)
  143. IF (P .LT. 2) GO TO 20
  144. DO 10 J = 2, P
  145. S(J) = X(J) - DDOT(J-1,R(1,J),1,S,1)
  146. S(J) = S(J)/R(J,J)
  147. 10 CONTINUE
  148. 20 CONTINUE
  149. NORM = DNRM2(P,S,1)
  150. IF (NORM .LT. 1.0D0) GO TO 30
  151. INFO = -1
  152. GO TO 120
  153. 30 CONTINUE
  154. ALPHA = SQRT(1.0D0-NORM**2)
  155. C
  156. C DETERMINE THE TRANSFORMATIONS.
  157. C
  158. DO 40 II = 1, P
  159. I = P - II + 1
  160. SCALE = ALPHA + ABS(S(I))
  161. A = ALPHA/SCALE
  162. B = S(I)/SCALE
  163. NORM = SQRT(A**2+B**2)
  164. C(I) = A/NORM
  165. S(I) = B/NORM
  166. ALPHA = SCALE*NORM
  167. 40 CONTINUE
  168. C
  169. C APPLY THE TRANSFORMATIONS TO R.
  170. C
  171. DO 60 J = 1, P
  172. XX = 0.0D0
  173. DO 50 II = 1, J
  174. I = J - II + 1
  175. T = C(I)*XX + S(I)*R(I,J)
  176. R(I,J) = C(I)*R(I,J) - S(I)*XX
  177. XX = T
  178. 50 CONTINUE
  179. 60 CONTINUE
  180. C
  181. C IF REQUIRED, DOWNDATE Z AND RHO.
  182. C
  183. IF (NZ .LT. 1) GO TO 110
  184. DO 100 J = 1, NZ
  185. ZETA = Y(J)
  186. DO 70 I = 1, P
  187. Z(I,J) = (Z(I,J) - S(I)*ZETA)/C(I)
  188. ZETA = C(I)*ZETA - S(I)*Z(I,J)
  189. 70 CONTINUE
  190. AZETA = ABS(ZETA)
  191. IF (AZETA .LE. RHO(J)) GO TO 80
  192. INFO = 1
  193. RHO(J) = -1.0D0
  194. GO TO 90
  195. 80 CONTINUE
  196. RHO(J) = RHO(J)*SQRT(1.0D0-(AZETA/RHO(J))**2)
  197. 90 CONTINUE
  198. 100 CONTINUE
  199. 110 CONTINUE
  200. 120 CONTINUE
  201. RETURN
  202. END