sir.f 15 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332
  1. *DECK SIR
  2. SUBROUTINE SIR (N, B, X, NELT, IA, JA, A, ISYM, MATVEC, MSOLVE,
  3. + ITOL, TOL, ITMAX, ITER, ERR, IERR, IUNIT, R, Z, DZ, RWORK,
  4. + IWORK)
  5. C***BEGIN PROLOGUE SIR
  6. C***PURPOSE Preconditioned Iterative Refinement Sparse Ax = b Solver.
  7. C Routine to solve a general linear system Ax = b using
  8. C iterative refinement with a matrix splitting.
  9. C***LIBRARY SLATEC (SLAP)
  10. C***CATEGORY D2A4, D2B4
  11. C***TYPE SINGLE PRECISION (SIR-S, DIR-D)
  12. C***KEYWORDS ITERATIVE PRECONDITION, LINEAR SYSTEM, SLAP, SPARSE
  13. C***AUTHOR Greenbaum, Anne, (Courant Institute)
  14. C Seager, Mark K., (LLNL)
  15. C Lawrence Livermore National Laboratory
  16. C PO BOX 808, L-60
  17. C Livermore, CA 94550 (510) 423-3141
  18. C seager@llnl.gov
  19. C***DESCRIPTION
  20. C
  21. C *Usage:
  22. C INTEGER N, NELT, IA(NELT), JA(NELT), ISYM, ITOL, ITMAX
  23. C INTEGER ITER, IERR, IUNIT, IWORK(USER DEFINED)
  24. C REAL B(N), X(N), A(NELT), TOL, ERR, R(N), Z(N), DZ(N),
  25. C REAL RWORK(USER DEFINED)
  26. C EXTERNAL MATVEC, MSOLVE
  27. C
  28. C CALL SIR(N, B, X, NELT, IA, JA, A, ISYM, MATVEC, MSOLVE, ITOL,
  29. C $ TOL, ITMAX, ITER, ERR, IERR, IUNIT, R, Z, DZ, RWORK, IWORK)
  30. C
  31. C *Arguments:
  32. C N :IN Integer.
  33. C Order of the Matrix.
  34. C B :IN Real B(N).
  35. C Right-hand side vector.
  36. C X :INOUT Real X(N).
  37. C On input X is your initial guess for solution vector.
  38. C On output X is the final approximate solution.
  39. C NELT :IN Integer.
  40. C Number of Non-Zeros stored in A.
  41. C IA :IN Integer IA(NELT).
  42. C JA :IN Integer JA(NELT).
  43. C A :IN Real A(NELT).
  44. C These arrays contain the matrix data structure for A.
  45. C It could take any form. See "Description", below,
  46. C for more details.
  47. C ISYM :IN Integer.
  48. C Flag to indicate symmetric storage format.
  49. C If ISYM=0, all non-zero entries of the matrix are stored.
  50. C If ISYM=1, the matrix is symmetric, and only the upper
  51. C or lower triangle of the matrix is stored.
  52. C MATVEC :EXT External.
  53. C Name of a routine which performs the matrix vector multiply
  54. C Y = A*X given A and X. The name of the MATVEC routine must
  55. C be declared external in the calling program. The calling
  56. C sequence to MATVEC is:
  57. C CALL MATVEC( N, X, Y, NELT, IA, JA, A, ISYM )
  58. C Where N is the number of unknowns, Y is the product A*X
  59. C upon return, X is an input vector, NELT is the number of
  60. C non-zeros in the SLAP IA, JA, A storage for the matrix A.
  61. C ISYM is a flag which, if non-zero, denotes that A is
  62. C symmetric and only the lower or upper triangle is stored.
  63. C MSOLVE :EXT External.
  64. C Name of a routine which solves a linear system MZ = R for
  65. C Z given R with the preconditioning matrix M (M is supplied via
  66. C RWORK and IWORK arrays). The name of the MSOLVE routine must
  67. C be declared external in the calling program. The calling
  68. C sequence to MSOLVE is:
  69. C CALL MSOLVE(N, R, Z, NELT, IA, JA, A, ISYM, RWORK, IWORK)
  70. C Where N is the number of unknowns, R is the right-hand side
  71. C vector and Z is the solution upon return. NELT, IA, JA, A and
  72. C ISYM are defined as above. RWORK is a real array that can
  73. C be used to pass necessary preconditioning information and/or
  74. C workspace to MSOLVE. IWORK is an integer work array for
  75. C the same purpose as RWORK.
  76. C ITOL :IN Integer.
  77. C Flag to indicate type of convergence criterion.
  78. C If ITOL=1, iteration stops when the 2-norm of the residual
  79. C divided by the 2-norm of the right-hand side is less than TOL.
  80. C If ITOL=2, iteration stops when the 2-norm of M-inv times the
  81. C residual divided by the 2-norm of M-inv times the right hand
  82. C side is less than TOL, where M-inv is the inverse of the
  83. C diagonal of A.
  84. C ITOL=11 is often useful for checking and comparing different
  85. C routines. For this case, the user must supply the "exact"
  86. C solution or a very accurate approximation (one with an error
  87. C much less than TOL) through a common block,
  88. C COMMON /SSLBLK/ SOLN( )
  89. C If ITOL=11, iteration stops when the 2-norm of the difference
  90. C between the iterative approximation and the user-supplied
  91. C solution divided by the 2-norm of the user-supplied solution
  92. C is less than TOL. Note that this requires the user to set up
  93. C the "COMMON /SSLBLK/ SOLN(LENGTH)" in the calling routine.
  94. C The routine with this declaration should be loaded before the
  95. C stop test so that the correct length is used by the loader.
  96. C This procedure is not standard Fortran and may not work
  97. C correctly on your system (although it has worked on every
  98. C system the authors have tried). If ITOL is not 11 then this
  99. C common block is indeed standard Fortran.
  100. C TOL :INOUT Real.
  101. C Convergence criterion, as described above. (Reset if IERR=4.)
  102. C ITMAX :IN Integer.
  103. C Maximum number of iterations.
  104. C ITER :OUT Integer.
  105. C Number of iterations required to reach convergence, or
  106. C ITMAX+1 if convergence criterion could not be achieved in
  107. C ITMAX iterations.
  108. C ERR :OUT Real.
  109. C Error estimate of error in final approximate solution, as
  110. C defined by ITOL.
  111. C IERR :OUT Integer.
  112. C Return error flag.
  113. C IERR = 0 => All went well.
  114. C IERR = 1 => Insufficient space allocated for WORK or IWORK.
  115. C IERR = 2 => Method failed to converge in ITMAX steps.
  116. C IERR = 3 => Error in user input.
  117. C Check input values of N, ITOL.
  118. C IERR = 4 => User error tolerance set too tight.
  119. C Reset to 500*R1MACH(3). Iteration proceeded.
  120. C IERR = 5 => Preconditioning matrix, M, is not positive
  121. C definite. (r,z) < 0.
  122. C IERR = 6 => Matrix A is not positive definite. (p,Ap) < 0.
  123. C IUNIT :IN Integer.
  124. C Unit number on which to write the error at each iteration,
  125. C if this is desired for monitoring convergence. If unit
  126. C number is 0, no writing will occur.
  127. C R :WORK Real R(N).
  128. C Z :WORK Real Z(N).
  129. C DZ :WORK Real DZ(N).
  130. C Real arrays used for workspace.
  131. C RWORK :WORK Real RWORK(USER DEFINED).
  132. C Real array that can be used by MSOLVE.
  133. C IWORK :WORK Integer IWORK(USER DEFINED).
  134. C Integer array that can be used by MSOLVE.
  135. C
  136. C *Description:
  137. C The basic algorithm for iterative refinement (also known as
  138. C iterative improvement) is:
  139. C
  140. C n+1 n -1 n
  141. C X = X + M (B - AX ).
  142. C
  143. C -1 -1
  144. C If M = A then this is the standard iterative refinement
  145. C algorithm and the "subtraction" in the residual calculation
  146. C should be done in double precision (which it is not in this
  147. C routine).
  148. C If M = DIAG(A), the diagonal of A, then iterative refinement
  149. C is known as Jacobi's method. The SLAP routine SSJAC
  150. C implements this iterative strategy.
  151. C If M = L, the lower triangle of A, then iterative refinement
  152. C is known as Gauss-Seidel. The SLAP routine SSGS implements
  153. C this iterative strategy.
  154. C
  155. C This routine does not care what matrix data structure is
  156. C used for A and M. It simply calls the MATVEC and MSOLVE
  157. C routines, with the arguments as described above. The user
  158. C could write any type of structure and the appropriate MATVEC
  159. C and MSOLVE routines. It is assumed that A is stored in the
  160. C IA, JA, A arrays in some fashion and that M (or INV(M)) is
  161. C stored in IWORK and RWORK) in some fashion. The SLAP
  162. C routines SSJAC and SSGS are examples of this procedure.
  163. C
  164. C Two examples of matrix data structures are the: 1) SLAP
  165. C Triad format and 2) SLAP Column format.
  166. C
  167. C =================== S L A P Triad format ===================
  168. C
  169. C In this format only the non-zeros are stored. They may
  170. C appear in *ANY* order. The user supplies three arrays of
  171. C length NELT, where NELT is the number of non-zeros in the
  172. C matrix: (IA(NELT), JA(NELT), A(NELT)). For each non-zero
  173. C the user puts the row and column index of that matrix
  174. C element in the IA and JA arrays. The value of the non-zero
  175. C matrix element is placed in the corresponding location of
  176. C the A array. This is an extremely easy data structure to
  177. C generate. On the other hand it is not too efficient on
  178. C vector computers for the iterative solution of linear
  179. C systems. Hence, SLAP changes this input data structure to
  180. C the SLAP Column format for the iteration (but does not
  181. C change it back).
  182. C
  183. C Here is an example of the SLAP Triad storage format for a
  184. C 5x5 Matrix. Recall that the entries may appear in any order.
  185. C
  186. C
  187. C 5x5 Matrix SLAP Triad format for 5x5 matrix on left.
  188. C 1 2 3 4 5 6 7 8 9 10 11
  189. C |11 12 0 0 15| A: 51 12 11 33 15 53 55 22 35 44 21
  190. C |21 22 0 0 0| IA: 5 1 1 3 1 5 5 2 3 4 2
  191. C | 0 0 33 0 35| JA: 1 2 1 3 5 3 5 2 5 4 1
  192. C | 0 0 0 44 0|
  193. C |51 0 53 0 55|
  194. C
  195. C =================== S L A P Column format ==================
  196. C
  197. C In this format the non-zeros are stored counting down
  198. C columns (except for the diagonal entry, which must appear
  199. C first in each "column") and are stored in the real array A.
  200. C In other words, for each column in the matrix put the
  201. C diagonal entry in A. Then put in the other non-zero
  202. C elements going down the column (except the diagonal) in
  203. C order. The IA array holds the row index for each non-zero.
  204. C The JA array holds the offsets into the IA, A arrays for the
  205. C beginning of each column. That is, IA(JA(ICOL)),
  206. C A(JA(ICOL)) points to the beginning of the ICOL-th column in
  207. C IA and A. IA(JA(ICOL+1)-1), A(JA(ICOL+1)-1) points to the
  208. C end of the ICOL-th column. Note that we always have JA(N+1)
  209. C = NELT+1, where N is the number of columns in the matrix and
  210. C NELT is the number of non-zeros in the matrix.
  211. C
  212. C Here is an example of the SLAP Column storage format for a
  213. C 5x5 Matrix (in the A and IA arrays '|' denotes the end of a
  214. C column):
  215. C
  216. C 5x5 Matrix SLAP Column format for 5x5 matrix on left.
  217. C 1 2 3 4 5 6 7 8 9 10 11
  218. C |11 12 0 0 15| A: 11 21 51 | 22 12 | 33 53 | 44 | 55 15 35
  219. C |21 22 0 0 0| IA: 1 2 5 | 2 1 | 3 5 | 4 | 5 1 3
  220. C | 0 0 33 0 35| JA: 1 4 6 8 9 12
  221. C | 0 0 0 44 0|
  222. C |51 0 53 0 55|
  223. C
  224. C *Examples:
  225. C See the SLAP routines SSJAC, SSGS
  226. C
  227. C *Cautions:
  228. C This routine will attempt to write to the Fortran logical output
  229. C unit IUNIT, if IUNIT .ne. 0. Thus, the user must make sure that
  230. C this logical unit is attached to a file or terminal before calling
  231. C this routine with a non-zero value for IUNIT. This routine does
  232. C not check for the validity of a non-zero IUNIT unit number.
  233. C
  234. C***SEE ALSO SSJAC, SSGS
  235. C***REFERENCES 1. Gene Golub and Charles Van Loan, Matrix Computations,
  236. C Johns Hopkins University Press, Baltimore, Maryland,
  237. C 1983.
  238. C 2. Mark K. Seager, A SLAP for the Masses, in
  239. C G. F. Carey, Ed., Parallel Supercomputing: Methods,
  240. C Algorithms and Applications, Wiley, 1989, pp.135-155.
  241. C***ROUTINES CALLED ISSIR, R1MACH
  242. C***REVISION HISTORY (YYMMDD)
  243. C 871119 DATE WRITTEN
  244. C 881213 Previous REVISION DATE
  245. C 890915 Made changes requested at July 1989 CML Meeting. (MKS)
  246. C 890921 Removed TeX from comments. (FNF)
  247. C 890922 Numerous changes to prologue to make closer to SLATEC
  248. C standard. (FNF)
  249. C 890929 Numerous changes to reduce SP/DP differences. (FNF)
  250. C 891004 Added new reference.
  251. C 910411 Prologue converted to Version 4.0 format. (BAB)
  252. C 910502 Removed MATVEC and MSOLVE from ROUTINES CALLED list. (FNF)
  253. C 920407 COMMON BLOCK renamed SSLBLK. (WRB)
  254. C 920511 Added complete declaration section. (WRB)
  255. C 920929 Corrected format of references. (FNF)
  256. C 921019 Changed 500.0 to 500 to reduce SP/DP differences. (FNF)
  257. C***END PROLOGUE SIR
  258. C .. Scalar Arguments ..
  259. REAL ERR, TOL
  260. INTEGER IERR, ISYM, ITER, ITMAX, ITOL, IUNIT, N, NELT
  261. C .. Array Arguments ..
  262. REAL A(NELT), B(N), DZ(N), R(N), RWORK(*), X(N), Z(N)
  263. INTEGER IA(NELT), IWORK(*), JA(NELT)
  264. C .. Subroutine Arguments ..
  265. EXTERNAL MATVEC, MSOLVE
  266. C .. Local Scalars ..
  267. REAL BNRM, SOLNRM, TOLMIN
  268. INTEGER I, K
  269. C .. External Functions ..
  270. REAL R1MACH
  271. INTEGER ISSIR
  272. EXTERNAL R1MACH, ISSIR
  273. C***FIRST EXECUTABLE STATEMENT SIR
  274. C
  275. C Check some of the input data.
  276. C
  277. ITER = 0
  278. IERR = 0
  279. IF( N.LT.1 ) THEN
  280. IERR = 3
  281. RETURN
  282. ENDIF
  283. TOLMIN = 500*R1MACH(3)
  284. IF( TOL.LT.TOLMIN ) THEN
  285. TOL = TOLMIN
  286. IERR = 4
  287. ENDIF
  288. C
  289. C Calculate initial residual and pseudo-residual, and check
  290. C stopping criterion.
  291. CALL MATVEC(N, X, R, NELT, IA, JA, A, ISYM)
  292. DO 10 I = 1, N
  293. R(I) = B(I) - R(I)
  294. 10 CONTINUE
  295. CALL MSOLVE(N, R, Z, NELT, IA, JA, A, ISYM, RWORK, IWORK)
  296. C
  297. IF( ISSIR(N, B, X, NELT, IA, JA, A, ISYM, MSOLVE, ITOL, TOL,
  298. $ ITMAX, ITER, ERR, IERR, IUNIT, R, Z, DZ, RWORK,
  299. $ IWORK, BNRM, SOLNRM) .NE. 0 ) GO TO 200
  300. IF( IERR.NE.0 ) RETURN
  301. C
  302. C ***** iteration loop *****
  303. C
  304. DO 100 K=1,ITMAX
  305. ITER = K
  306. C
  307. C Calculate new iterate x, new residual r, and new
  308. C pseudo-residual z.
  309. DO 20 I = 1, N
  310. X(I) = X(I) + Z(I)
  311. 20 CONTINUE
  312. CALL MATVEC(N, X, R, NELT, IA, JA, A, ISYM)
  313. DO 30 I = 1, N
  314. R(I) = B(I) - R(I)
  315. 30 CONTINUE
  316. CALL MSOLVE(N, R, Z, NELT, IA, JA, A, ISYM, RWORK, IWORK)
  317. C
  318. C check stopping criterion.
  319. IF( ISSIR(N, B, X, NELT, IA, JA, A, ISYM, MSOLVE, ITOL, TOL,
  320. $ ITMAX, ITER, ERR, IERR, IUNIT, R, Z, DZ, RWORK,
  321. $ IWORK, BNRM, SOLNRM) .NE. 0 ) GO TO 200
  322. C
  323. 100 CONTINUE
  324. C
  325. C ***** end of loop *****
  326. C Stopping criterion not satisfied.
  327. ITER = ITMAX + 1
  328. IERR = 2
  329. C
  330. 200 RETURN
  331. C------------- LAST LINE OF SIR FOLLOWS -------------------------------
  332. END