dxlcal.f 7.8 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185
  1. *DECK DXLCAL
  2. SUBROUTINE DXLCAL (N, LGMR, X, XL, ZL, HES, MAXLP1, Q, V, R0NRM,
  3. + WK, SZ, JSCAL, JPRE, MSOLVE, NMSL, RPAR, IPAR, NELT, IA, JA, A,
  4. + ISYM)
  5. C***BEGIN PROLOGUE DXLCAL
  6. C***SUBSIDIARY
  7. C***PURPOSE Internal routine for DGMRES.
  8. C***LIBRARY SLATEC (SLAP)
  9. C***CATEGORY D2A4, D2B4
  10. C***TYPE DOUBLE PRECISION (SXLCAL-S, DXLCAL-D)
  11. C***KEYWORDS GENERALIZED MINIMUM RESIDUAL, ITERATIVE PRECONDITION,
  12. C NON-SYMMETRIC LINEAR SYSTEM, SLAP, SPARSE
  13. C***AUTHOR Brown, Peter, (LLNL), pnbrown@llnl.gov
  14. C Hindmarsh, Alan, (LLNL), alanh@llnl.gov
  15. C Seager, Mark K., (LLNL), seager@llnl.gov
  16. C Lawrence Livermore National Laboratory
  17. C PO Box 808, L-60
  18. C Livermore, CA 94550 (510) 423-3141
  19. C***DESCRIPTION
  20. C This routine computes the solution XL, the current DGMRES
  21. C iterate, given the V(I)'s and the QR factorization of the
  22. C Hessenberg matrix HES. This routine is only called when
  23. C ITOL=11.
  24. C
  25. C *Usage:
  26. C INTEGER N, LGMR, MAXLP1, JSCAL, JPRE, NMSL, IPAR(USER DEFINED)
  27. C INTEGER NELT, IA(NELT), JA(NELT), ISYM
  28. C DOUBLE PRECISION X(N), XL(N), ZL(N), HES(MAXLP1,MAXL), Q(2*MAXL),
  29. C $ V(N,MAXLP1), R0NRM, WK(N), SZ(N),
  30. C $ RPAR(USER DEFINED), A(NELT)
  31. C EXTERNAL MSOLVE
  32. C
  33. C CALL DXLCAL(N, LGMR, X, XL, ZL, HES, MAXLP1, Q, V, R0NRM,
  34. C $ WK, SZ, JSCAL, JPRE, MSOLVE, NMSL, RPAR, IPAR,
  35. C $ NELT, IA, JA, A, ISYM)
  36. C
  37. C *Arguments:
  38. C N :IN Integer
  39. C The order of the matrix A, and the lengths
  40. C of the vectors SR, SZ, R0 and Z.
  41. C LGMR :IN Integer
  42. C The number of iterations performed and
  43. C the current order of the upper Hessenberg
  44. C matrix HES.
  45. C X :IN Double Precision X(N)
  46. C The current approximate solution as of the last restart.
  47. C XL :OUT Double Precision XL(N)
  48. C An array of length N used to hold the approximate
  49. C solution X(L).
  50. C Warning: XL and ZL are the same array in the calling routine.
  51. C ZL :IN Double Precision ZL(N)
  52. C An array of length N used to hold the approximate
  53. C solution Z(L).
  54. C HES :IN Double Precision HES(MAXLP1,MAXL)
  55. C The upper triangular factor of the QR decomposition
  56. C of the (LGMR+1) by LGMR upper Hessenberg matrix whose
  57. C entries are the scaled inner-products of A*V(*,i) and V(*,k).
  58. C MAXLP1 :IN Integer
  59. C MAXLP1 = MAXL + 1, used for dynamic dimensioning of HES.
  60. C MAXL is the maximum allowable order of the matrix HES.
  61. C Q :IN Double Precision Q(2*MAXL)
  62. C A double precision array of length 2*MAXL containing the
  63. C components of the Givens rotations used in the QR
  64. C decomposition of HES. It is loaded in DHEQR.
  65. C V :IN Double Precision V(N,MAXLP1)
  66. C The N by(LGMR+1) array containing the LGMR
  67. C orthogonal vectors V(*,1) to V(*,LGMR).
  68. C R0NRM :IN Double Precision
  69. C The scaled norm of the initial residual for the
  70. C current call to DPIGMR.
  71. C WK :IN Double Precision WK(N)
  72. C A double precision work array of length N.
  73. C SZ :IN Double Precision SZ(N)
  74. C A vector of length N containing the non-zero
  75. C elements of the diagonal scaling matrix for Z.
  76. C JSCAL :IN Integer
  77. C A flag indicating whether arrays SR and SZ are used.
  78. C JSCAL=0 means SR and SZ are not used and the
  79. C algorithm will perform as if all
  80. C SR(i) = 1 and SZ(i) = 1.
  81. C JSCAL=1 means only SZ is used, and the algorithm
  82. C performs as if all SR(i) = 1.
  83. C JSCAL=2 means only SR is used, and the algorithm
  84. C performs as if all SZ(i) = 1.
  85. C JSCAL=3 means both SR and SZ are used.
  86. C JPRE :IN Integer
  87. C The preconditioner type flag.
  88. C MSOLVE :EXT External.
  89. C Name of the routine which solves a linear system Mz = r for
  90. C z given r with the preconditioning matrix M (M is supplied via
  91. C RPAR and IPAR arrays. The name of the MSOLVE routine must
  92. C be declared external in the calling program. The calling
  93. C sequence to MSOLVE is:
  94. C CALL MSOLVE(N, R, Z, NELT, IA, JA, A, ISYM, RPAR, IPAR)
  95. C Where N is the number of unknowns, R is the right-hand side
  96. C vector and Z is the solution upon return. NELT, IA, JA, A and
  97. C ISYM are defined as below. RPAR is a double precision array
  98. C that can be used to pass necessary preconditioning information
  99. C and/or workspace to MSOLVE. IPAR is an integer work array
  100. C for the same purpose as RPAR.
  101. C NMSL :IN Integer
  102. C The number of calls to MSOLVE.
  103. C RPAR :IN Double Precision RPAR(USER DEFINED)
  104. C Double Precision workspace passed directly to the MSOLVE
  105. C routine.
  106. C IPAR :IN Integer IPAR(USER DEFINED)
  107. C Integer workspace passed directly to the MSOLVE routine.
  108. C NELT :IN Integer
  109. C The length of arrays IA, JA and A.
  110. C IA :IN Integer IA(NELT)
  111. C An integer array of length NELT containing matrix data.
  112. C It is passed directly to the MATVEC and MSOLVE routines.
  113. C JA :IN Integer JA(NELT)
  114. C An integer array of length NELT containing matrix data.
  115. C It is passed directly to the MATVEC and MSOLVE routines.
  116. C A :IN Double Precision A(NELT)
  117. C A double precision array of length NELT containing matrix
  118. C data.
  119. C It is passed directly to the MATVEC and MSOLVE routines.
  120. C ISYM :IN Integer
  121. C A flag to indicate symmetric matrix storage.
  122. C If ISYM=0, all non-zero entries of the matrix are
  123. C stored. If ISYM=1, the matrix is symmetric and
  124. C only the upper or lower triangular part is stored.
  125. C
  126. C***SEE ALSO DGMRES
  127. C***ROUTINES CALLED DAXPY, DCOPY, DHELS
  128. C***REVISION HISTORY (YYMMDD)
  129. C 890404 DATE WRITTEN
  130. C 890404 Previous REVISION DATE
  131. C 890915 Made changes requested at July 1989 CML Meeting. (MKS)
  132. C 890922 Numerous changes to prologue to make closer to SLATEC
  133. C standard. (FNF)
  134. C 890929 Numerous changes to reduce SP/DP differences. (FNF)
  135. C 910411 Prologue converted to Version 4.0 format. (BAB)
  136. C 910502 Removed MSOLVE from ROUTINES CALLED list. (FNF)
  137. C 910506 Made subsidiary to DGMRES. (FNF)
  138. C 920511 Added complete declaration section. (WRB)
  139. C***END PROLOGUE DXLCAL
  140. C The following is for optimized compilation on LLNL/LTSS Crays.
  141. CLLL. OPTIMIZE
  142. C .. Scalar Arguments ..
  143. DOUBLE PRECISION R0NRM
  144. INTEGER ISYM, JPRE, JSCAL, LGMR, MAXLP1, N, NELT, NMSL
  145. C .. Array Arguments ..
  146. DOUBLE PRECISION A(NELT), HES(MAXLP1,*), Q(*), RPAR(*), SZ(*),
  147. + V(N,*), WK(N), X(N), XL(N), ZL(N)
  148. INTEGER IA(NELT), IPAR(*), JA(NELT)
  149. C .. Subroutine Arguments ..
  150. EXTERNAL MSOLVE
  151. C .. Local Scalars ..
  152. INTEGER I, K, LL, LLP1
  153. C .. External Subroutines ..
  154. EXTERNAL DAXPY, DCOPY, DHELS
  155. C***FIRST EXECUTABLE STATEMENT DXLCAL
  156. LL = LGMR
  157. LLP1 = LL + 1
  158. DO 10 K = 1,LLP1
  159. WK(K) = 0
  160. 10 CONTINUE
  161. WK(1) = R0NRM
  162. CALL DHELS(HES, MAXLP1, LL, Q, WK)
  163. DO 20 K = 1,N
  164. ZL(K) = 0
  165. 20 CONTINUE
  166. DO 30 I = 1,LL
  167. CALL DAXPY(N, WK(I), V(1,I), 1, ZL, 1)
  168. 30 CONTINUE
  169. IF ((JSCAL .EQ. 1) .OR.(JSCAL .EQ. 3)) THEN
  170. DO 40 K = 1,N
  171. ZL(K) = ZL(K)/SZ(K)
  172. 40 CONTINUE
  173. ENDIF
  174. IF (JPRE .GT. 0) THEN
  175. CALL DCOPY(N, ZL, 1, WK, 1)
  176. CALL MSOLVE(N, WK, ZL, NELT, IA, JA, A, ISYM, RPAR, IPAR)
  177. NMSL = NMSL + 1
  178. ENDIF
  179. C calculate XL from X and ZL.
  180. DO 50 K = 1,N
  181. XL(K) = X(K) + ZL(K)
  182. 50 CONTINUE
  183. RETURN
  184. C------------- LAST LINE OF DXLCAL FOLLOWS ----------------------------
  185. END