dwupdt.f 4.2 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123
  1. *DECK DWUPDT
  2. SUBROUTINE DWUPDT (N, R, LDR, W, B, ALPHA, COS, SIN)
  3. C***BEGIN PROLOGUE DWUPDT
  4. C***SUBSIDIARY
  5. C***PURPOSE Subsidiary to DNLS1 and DNLS1E
  6. C***LIBRARY SLATEC
  7. C***TYPE DOUBLE PRECISION (RWUPDT-S, DWUPDT-D)
  8. C***AUTHOR (UNKNOWN)
  9. C***DESCRIPTION
  10. C
  11. C Given an N by N upper triangular matrix R, this subroutine
  12. C computes the QR decomposition of the matrix formed when a row
  13. C is added to R. If the row is specified by the vector W, then
  14. C DWUPDT determines an orthogonal matrix Q such that when the
  15. C N+1 by N matrix composed of R augmented by W is premultiplied
  16. C by (Q TRANSPOSE), the resulting matrix is upper trapezoidal.
  17. C The orthogonal matrix Q is the product of N transformations
  18. C
  19. C G(1)*G(2)* ... *G(N)
  20. C
  21. C where G(I) is a Givens rotation in the (I,N+1) plane which
  22. C eliminates elements in the I-th plane. DWUPDT also
  23. C computes the product (Q TRANSPOSE)*C where C is the
  24. C (N+1)-vector (b,alpha). Q itself is not accumulated, rather
  25. C the information to recover the G rotations is supplied.
  26. C
  27. C The subroutine statement is
  28. C
  29. C SUBROUTINE DWUPDT(N,R,LDR,W,B,ALPHA,COS,SIN)
  30. C
  31. C where
  32. C
  33. C N is a positive integer input variable set to the order of R.
  34. C
  35. C R is an N by N array. On input the upper triangular part of
  36. C R must contain the matrix to be updated. On output R
  37. C contains the updated triangular matrix.
  38. C
  39. C LDR is a positive integer input variable not less than N
  40. C which specifies the leading dimension of the array R.
  41. C
  42. C W is an input array of length N which must contain the row
  43. C vector to be added to R.
  44. C
  45. C B is an array of length N. On input B must contain the
  46. C first N elements of the vector C. On output B contains
  47. C the first N elements of the vector (Q TRANSPOSE)*C.
  48. C
  49. C ALPHA is a variable. On input ALPHA must contain the
  50. C (N+1)-st element of the vector C. On output ALPHA contains
  51. C the (N+1)-st element of the vector (Q TRANSPOSE)*C.
  52. C
  53. C COS is an output array of length N which contains the
  54. C cosines of the transforming Givens rotations.
  55. C
  56. C SIN is an output array of length N which contains the
  57. C sines of the transforming Givens rotations.
  58. C
  59. C **********
  60. C
  61. C***SEE ALSO DNLS1, DNLS1E
  62. C***ROUTINES CALLED (NONE)
  63. C***REVISION HISTORY (YYMMDD)
  64. C 800301 DATE WRITTEN
  65. C 890531 Changed all specific intrinsics to generic. (WRB)
  66. C 890831 Modified array declarations. (WRB)
  67. C 891214 Prologue converted to Version 4.0 format. (BAB)
  68. C 900326 Removed duplicate information from DESCRIPTION section.
  69. C (WRB)
  70. C 900328 Added TYPE section. (WRB)
  71. C***END PROLOGUE DWUPDT
  72. INTEGER N,LDR
  73. DOUBLE PRECISION ALPHA
  74. DOUBLE PRECISION R(LDR,*),W(*),B(*),COS(*),SIN(*)
  75. INTEGER I,J,JM1
  76. DOUBLE PRECISION COTAN,ONE,P5,P25,ROWJ,TAN,TEMP,ZERO
  77. SAVE ONE, P5, P25, ZERO
  78. DATA ONE,P5,P25,ZERO /1.0D0,5.0D-1,2.5D-1,0.0D0/
  79. C***FIRST EXECUTABLE STATEMENT DWUPDT
  80. DO 60 J = 1, N
  81. ROWJ = W(J)
  82. JM1 = J - 1
  83. C
  84. C APPLY THE PREVIOUS TRANSFORMATIONS TO
  85. C R(I,J), I=1,2,...,J-1, AND TO W(J).
  86. C
  87. IF (JM1 .LT. 1) GO TO 20
  88. DO 10 I = 1, JM1
  89. TEMP = COS(I)*R(I,J) + SIN(I)*ROWJ
  90. ROWJ = -SIN(I)*R(I,J) + COS(I)*ROWJ
  91. R(I,J) = TEMP
  92. 10 CONTINUE
  93. 20 CONTINUE
  94. C
  95. C DETERMINE A GIVENS ROTATION WHICH ELIMINATES W(J).
  96. C
  97. COS(J) = ONE
  98. SIN(J) = ZERO
  99. IF (ROWJ .EQ. ZERO) GO TO 50
  100. IF (ABS(R(J,J)) .GE. ABS(ROWJ)) GO TO 30
  101. COTAN = R(J,J)/ROWJ
  102. SIN(J) = P5/SQRT(P25+P25*COTAN**2)
  103. COS(J) = SIN(J)*COTAN
  104. GO TO 40
  105. 30 CONTINUE
  106. TAN = ROWJ/R(J,J)
  107. COS(J) = P5/SQRT(P25+P25*TAN**2)
  108. SIN(J) = COS(J)*TAN
  109. 40 CONTINUE
  110. C
  111. C APPLY THE CURRENT TRANSFORMATION TO R(J,J), B(J), AND ALPHA.
  112. C
  113. R(J,J) = COS(J)*R(J,J) + SIN(J)*ROWJ
  114. TEMP = COS(J)*B(J) + SIN(J)*ALPHA
  115. ALPHA = -SIN(J)*B(J) + COS(J)*ALPHA
  116. B(J) = TEMP
  117. 50 CONTINUE
  118. 60 CONTINUE
  119. RETURN
  120. C
  121. C LAST CARD OF SUBROUTINE DWUPDT.
  122. C
  123. END