somn.f 16 KB

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