domn.f 16 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364
  1. *DECK DOMN
  2. SUBROUTINE DOMN (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 DOMN
  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 DOUBLE 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 DOUBLE PRECISION B(N), X(N), A(NELT), TOL, ERR, R(N), Z(N)
  26. C DOUBLE PRECISION P(N,0:NSAVE), AP(N,0:NSAVE), EMAP(N,0:NSAVE)
  27. C DOUBLE PRECISION DZ(N), CSAV(NSAVE), RWORK(USER DEFINED)
  28. C EXTERNAL MATVEC, MSOLVE
  29. C
  30. C CALL DOMN(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 Double Precision B(N).
  38. C Right-hand side vector.
  39. C X :INOUT Double Precision 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 Double Precision 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 double precision array
  76. C that can be used to pass necessary preconditioning information
  77. C and/or workspace to MSOLVE. IWORK is an integer work array
  78. C for 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 /DSLBLK/ 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 /DSLBLK/ 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 Double Precision.
  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 Double Precision.
  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*D1MACH(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 Double Precision R(N).
  135. C Z :WORK Double Precision Z(N).
  136. C P :WORK Double Precision P(N,0:NSAVE).
  137. C AP :WORK Double Precision AP(N,0:NSAVE).
  138. C EMAP :WORK Double Precision EMAP(N,0:NSAVE).
  139. C DZ :WORK Double Precision DZ(N).
  140. C CSAV :WORK Double Precision CSAV(NSAVE)
  141. C Double Precision arrays used for workspace.
  142. C RWORK :WORK Double Precision RWORK(USER DEFINED).
  143. C Double Precision array that can be used for workspace in
  144. C MSOLVE.
  145. C IWORK :WORK Integer IWORK(USER DEFINED).
  146. C Integer array that can be used for workspace in MSOLVE.
  147. C
  148. C *Description
  149. C This routine does not care what matrix data structure is
  150. C used for A and M. It simply calls the MATVEC and MSOLVE
  151. C routines, with the arguments as described above. The user
  152. C could write any type of structure and the appropriate MATVEC
  153. C and MSOLVE routines. It is assumed that A is stored in the
  154. C IA, JA, A arrays in some fashion and that M (or INV(M)) is
  155. C stored in IWORK and RWORK) in some fashion. The SLAP
  156. C routines DSDOMN and DSLUOM are examples of this procedure.
  157. C
  158. C Two examples of matrix data structures are the: 1) SLAP
  159. C Triad format and 2) SLAP Column format.
  160. C
  161. C =================== S L A P Triad format ===================
  162. C In this format only the non-zeros are stored. They may
  163. C appear in *ANY* order. The user supplies three arrays of
  164. C length NELT, where NELT is the number of non-zeros in the
  165. C matrix: (IA(NELT), JA(NELT), A(NELT)). For each non-zero
  166. C the user puts the row and column index of that matrix
  167. C element in the IA and JA arrays. The value of the non-zero
  168. C matrix element is placed in the corresponding location of
  169. C the A array. This is an extremely easy data structure to
  170. C generate. On the other hand it is not too efficient on
  171. C vector computers for the iterative solution of linear
  172. C systems. Hence, SLAP changes this input data structure to
  173. C the SLAP Column format for the iteration (but does not
  174. C change it back).
  175. C
  176. C Here is an example of the SLAP Triad storage format for a
  177. C 5x5 Matrix. Recall that the entries may appear in any order.
  178. C
  179. C 5x5 Matrix SLAP Triad format for 5x5 matrix on left.
  180. C 1 2 3 4 5 6 7 8 9 10 11
  181. C |11 12 0 0 15| A: 51 12 11 33 15 53 55 22 35 44 21
  182. C |21 22 0 0 0| IA: 5 1 1 3 1 5 5 2 3 4 2
  183. C | 0 0 33 0 35| JA: 1 2 1 3 5 3 5 2 5 4 1
  184. C | 0 0 0 44 0|
  185. C |51 0 53 0 55|
  186. C
  187. C =================== S L A P Column format ==================
  188. C
  189. C In this format the non-zeros are stored counting down
  190. C columns (except for the diagonal entry, which must appear
  191. C first in each "column") and are stored in the double pre-
  192. C cision array A. In other words, for each column in the
  193. C matrix first put the diagonal entry in A. Then put in the
  194. C other non-zero elements going down the column (except the
  195. C diagonal) in order. The IA array holds the row index for
  196. C each non-zero. The JA array holds the offsets into the IA,
  197. C A arrays for the beginning of each column. That is,
  198. C IA(JA(ICOL)),A(JA(ICOL)) are the first elements of the ICOL-
  199. C th column in IA and A, and IA(JA(ICOL+1)-1), A(JA(ICOL+1)-1)
  200. C are the last elements of the ICOL-th column. Note that we
  201. C always have JA(N+1)=NELT+1, where N is the number of columns
  202. C in the matrix and NELT is the number of non-zeros in the
  203. C matrix.
  204. C
  205. C Here is an example of the SLAP Column storage format for a
  206. C 5x5 Matrix (in the A and IA arrays '|' denotes the end of a
  207. C column):
  208. C
  209. C 5x5 Matrix SLAP Column format for 5x5 matrix on left.
  210. C 1 2 3 4 5 6 7 8 9 10 11
  211. C |11 12 0 0 15| A: 11 21 51 | 22 12 | 33 53 | 44 | 55 15 35
  212. C |21 22 0 0 0| IA: 1 2 5 | 2 1 | 3 5 | 4 | 5 1 3
  213. C | 0 0 33 0 35| JA: 1 4 6 8 9 12
  214. C | 0 0 0 44 0|
  215. C |51 0 53 0 55|
  216. C
  217. C *Cautions:
  218. C This routine will attempt to write to the Fortran logical output
  219. C unit IUNIT, if IUNIT .ne. 0. Thus, the user must make sure that
  220. C this logical unit is attached to a file or terminal before calling
  221. C this routine with a non-zero value for IUNIT. This routine does
  222. C not check for the validity of a non-zero IUNIT unit number.
  223. C
  224. C***SEE ALSO DSDOMN, DSLUOM, ISDOMN
  225. C***REFERENCES 1. Mark K. Seager, A SLAP for the Masses, in
  226. C G. F. Carey, Ed., Parallel Supercomputing: Methods,
  227. C Algorithms and Applications, Wiley, 1989, pp.135-155.
  228. C***ROUTINES CALLED D1MACH, DAXPY, DCOPY, DDOT, ISDOMN
  229. C***REVISION HISTORY (YYMMDD)
  230. C 890404 DATE WRITTEN
  231. C 890404 Previous REVISION DATE
  232. C 890915 Made changes requested at July 1989 CML Meeting. (MKS)
  233. C 890922 Numerous changes to prologue to make closer to SLATEC
  234. C standard. (FNF)
  235. C 890929 Numerous changes to reduce SP/DP differences. (FNF)
  236. C 891004 Added new reference.
  237. C 910411 Prologue converted to Version 4.0 format. (BAB)
  238. C 910502 Removed MATVEC and MSOLVE from ROUTINES CALLED list. (FNF)
  239. C 920407 COMMON BLOCK renamed DSLBLK. (WRB)
  240. C 920511 Added complete declaration section. (WRB)
  241. C 920929 Corrected format of reference. (FNF)
  242. C 921019 Changed 500.0 to 500 to reduce SP/DP differences. (FNF)
  243. C 921113 Corrected C***CATEGORY line. (FNF)
  244. C 930326 Removed unused variable. (FNF)
  245. C***END PROLOGUE DOMN
  246. C .. Scalar Arguments ..
  247. DOUBLE PRECISION ERR, TOL
  248. INTEGER IERR, ISYM, ITER, ITMAX, ITOL, IUNIT, N, NELT, NSAVE
  249. C .. Array Arguments ..
  250. DOUBLE PRECISION A(NELT), AP(N,0:NSAVE), B(N), CSAV(NSAVE),
  251. + DZ(N), EMAP(N,0:NSAVE), P(N,0:NSAVE), R(N),
  252. + RWORK(*), X(N), Z(N)
  253. INTEGER IA(NELT), IWORK(*), JA(NELT)
  254. C .. Subroutine Arguments ..
  255. EXTERNAL MATVEC, MSOLVE
  256. C .. Local Scalars ..
  257. DOUBLE PRECISION AK, AKDEN, AKNUM, BKL, BNRM, FUZZ, SOLNRM
  258. INTEGER I, IP, IPO, K, L, LMAX
  259. C .. External Functions ..
  260. DOUBLE PRECISION D1MACH, DDOT
  261. INTEGER ISDOMN
  262. EXTERNAL D1MACH, DDOT, ISDOMN
  263. C .. External Subroutines ..
  264. EXTERNAL DAXPY, DCOPY
  265. C .. Intrinsic Functions ..
  266. INTRINSIC ABS, MIN, MOD
  267. C***FIRST EXECUTABLE STATEMENT DOMN
  268. C
  269. C Check some of the input data.
  270. C
  271. ITER = 0
  272. IERR = 0
  273. IF( N.LT.1 ) THEN
  274. IERR = 3
  275. RETURN
  276. ENDIF
  277. FUZZ = D1MACH(3)
  278. IF( TOL.LT.500*FUZZ ) THEN
  279. TOL = 500*FUZZ
  280. IERR = 4
  281. ENDIF
  282. FUZZ = FUZZ*FUZZ
  283. C
  284. C Calculate initial residual and pseudo-residual, and check
  285. C stopping criterion.
  286. CALL MATVEC(N, X, R, NELT, IA, JA, A, ISYM)
  287. DO 10 I = 1, N
  288. R(I) = B(I) - R(I)
  289. 10 CONTINUE
  290. CALL MSOLVE(N, R, Z, NELT, IA, JA, A, ISYM, RWORK, IWORK)
  291. C
  292. IF( ISDOMN(N, B, X, NELT, IA, JA, A, ISYM, MSOLVE, NSAVE,
  293. $ ITOL, TOL, ITMAX, ITER, ERR, IERR, IUNIT,
  294. $ R, Z, P, AP, EMAP, DZ, CSAV,
  295. $ RWORK, IWORK, AK, BNRM, SOLNRM) .NE. 0 ) GO TO 200
  296. IF( IERR.NE.0 ) RETURN
  297. C
  298. C
  299. C ***** iteration loop *****
  300. C
  301. CVD$R NOVECTOR
  302. CVD$R NOCONCUR
  303. DO 100 K = 1, ITMAX
  304. ITER = K
  305. IP = MOD( ITER-1, NSAVE+1 )
  306. C
  307. C calculate direction vector p, a*p, and (m-inv)*a*p,
  308. C and save if desired.
  309. CALL DCOPY(N, Z, 1, P(1,IP), 1)
  310. CALL MATVEC(N, P(1,IP), AP(1,IP), NELT, IA, JA, A, ISYM)
  311. CALL MSOLVE(N, AP(1,IP), EMAP(1,IP), NELT, IA, JA, A, ISYM,
  312. $ RWORK, IWORK)
  313. IF( NSAVE.EQ.0 ) THEN
  314. AKDEN = DDOT(N, EMAP, 1, EMAP, 1)
  315. ELSE
  316. IF( ITER.GT.1 ) THEN
  317. LMAX = MIN( NSAVE, ITER-1 )
  318. DO 20 L = 1, LMAX
  319. IPO = MOD(IP+(NSAVE+1-L),NSAVE+1)
  320. BKL = DDOT(N, EMAP(1,IP), 1, EMAP(1,IPO), 1)
  321. BKL = BKL*CSAV(L)
  322. CALL DAXPY(N, -BKL, P(1,IPO), 1, P(1,IP), 1)
  323. CALL DAXPY(N, -BKL, AP(1,IPO), 1, AP(1,IP), 1)
  324. CALL DAXPY(N, -BKL, EMAP(1,IPO), 1, EMAP(1,IP), 1)
  325. 20 CONTINUE
  326. IF( NSAVE.GT.1 ) THEN
  327. DO 30 L = NSAVE-1, 1, -1
  328. CSAV(L+1) = CSAV(L)
  329. 30 CONTINUE
  330. ENDIF
  331. ENDIF
  332. AKDEN = DDOT(N, EMAP(1,IP), 1, EMAP(1,IP), 1)
  333. IF( ABS(AKDEN).LT.FUZZ ) THEN
  334. IERR = 6
  335. RETURN
  336. ENDIF
  337. CSAV(1) = 1.0D0/AKDEN
  338. C
  339. C calculate coefficient ak, new iterate x, new residual r, and
  340. C new pseudo-residual z.
  341. ENDIF
  342. AKNUM = DDOT(N, Z, 1, EMAP(1,IP), 1)
  343. AK = AKNUM/AKDEN
  344. CALL DAXPY(N, AK, P(1,IP), 1, X, 1)
  345. CALL DAXPY(N, -AK, AP(1,IP), 1, R, 1)
  346. CALL DAXPY(N, -AK, EMAP(1,IP), 1, Z, 1)
  347. C
  348. C check stopping criterion.
  349. IF( ISDOMN(N, B, X, NELT, IA, JA, A, ISYM, MSOLVE, NSAVE,
  350. $ ITOL, TOL, ITMAX, ITER, ERR, IERR, IUNIT,
  351. $ R, Z, P, AP, EMAP, DZ, CSAV,
  352. $ RWORK, IWORK, AK, BNRM, SOLNRM) .NE. 0 ) GO TO 200
  353. C
  354. 100 CONTINUE
  355. C
  356. C ***** end of loop *****
  357. C
  358. C Stopping criterion not satisfied.
  359. ITER = ITMAX + 1
  360. IERR = 2
  361. C
  362. 200 RETURN
  363. C------------- LAST LINE OF DOMN FOLLOWS ----------------------------
  364. END