blktri.f 9.0 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264
  1. *DECK BLKTRI
  2. SUBROUTINE BLKTRI (IFLG, NP, N, AN, BN, CN, MP, M, AM, BM, CM,
  3. + IDIMY, Y, IERROR, W)
  4. C***BEGIN PROLOGUE BLKTRI
  5. C***PURPOSE Solve a block tridiagonal system of linear equations
  6. C (usually resulting from the discretization of separable
  7. C two-dimensional elliptic equations).
  8. C***LIBRARY SLATEC (FISHPACK)
  9. C***CATEGORY I2B4B
  10. C***TYPE SINGLE PRECISION (BLKTRI-S, CBLKTR-C)
  11. C***KEYWORDS ELLIPTIC PDE, FISHPACK, TRIDIAGONAL LINEAR SYSTEM
  12. C***AUTHOR Adams, J., (NCAR)
  13. C Swarztrauber, P. N., (NCAR)
  14. C Sweet, R., (NCAR)
  15. C***DESCRIPTION
  16. C
  17. C Subroutine BLKTRI Solves a System of Linear Equations of the Form
  18. C
  19. C AN(J)*X(I,J-1) + AM(I)*X(I-1,J) + (BN(J)+BM(I))*X(I,J)
  20. C
  21. C + CN(J)*X(I,J+1) + CM(I)*X(I+1,J) = Y(I,J)
  22. C
  23. C for I = 1,2,...,M and J = 1,2,...,N.
  24. C
  25. C I+1 and I-1 are evaluated modulo M and J+1 and J-1 modulo N, i.e.,
  26. C
  27. C X(I,0) = X(I,N), X(I,N+1) = X(I,1),
  28. C X(0,J) = X(M,J), X(M+1,J) = X(1,J).
  29. C
  30. C These equations usually result from the discretization of
  31. C separable elliptic equations. Boundary conditions may be
  32. C Dirichlet, Neumann, or Periodic.
  33. C
  34. C
  35. C * * * * * * * * * * ON INPUT * * * * * * * * * *
  36. C
  37. C IFLG
  38. C = 0 Initialization only. Certain quantities that depend on NP,
  39. C N, AN, BN, and CN are computed and stored in the work
  40. C array W.
  41. C = 1 The quantities that were computed in the initialization are
  42. C used to obtain the solution X(I,J).
  43. C
  44. C NOTE A call with IFLG=0 takes approximately one half the time
  45. C as a call with IFLG = 1 . However, the
  46. C initialization does not have to be repeated unless NP, N,
  47. C AN, BN, or CN change.
  48. C
  49. C NP
  50. C = 0 If AN(1) and CN(N) are not zero, which corresponds to
  51. C periodic boundary conditions.
  52. C = 1 If AN(1) and CN(N) are zero.
  53. C
  54. C N
  55. C The number of unknowns in the J-direction. N must be greater
  56. C than 4. The operation count is proportional to MNlog2(N), hence
  57. C N should be selected less than or equal to M.
  58. C
  59. C AN,BN,CN
  60. C One-dimensional arrays of length N that specify the coefficients
  61. C in the linear equations given above.
  62. C
  63. C MP
  64. C = 0 If AM(1) and CM(M) are not zero, which corresponds to
  65. C periodic boundary conditions.
  66. C = 1 If AM(1) = CM(M) = 0 .
  67. C
  68. C M
  69. C The number of unknowns in the I-direction. M must be greater
  70. C than 4.
  71. C
  72. C AM,BM,CM
  73. C One-dimensional arrays of length M that specify the coefficients
  74. C in the linear equations given above.
  75. C
  76. C IDIMY
  77. C The row (or first) dimension of the two-dimensional array Y as
  78. C it appears in the program calling BLKTRI. This parameter is
  79. C used to specify the variable dimension of Y. IDIMY must be at
  80. C least M.
  81. C
  82. C Y
  83. C A two-dimensional array that specifies the values of the right
  84. C side of the linear system of equations given above. Y must be
  85. C dimensioned at least M*N.
  86. C
  87. C W
  88. C A one-dimensional array that must be provided by the user for
  89. C work space.
  90. C If NP=1 define K=INT(log2(N))+1 and set L=2**(K+1) then
  91. C W must have dimension (K-2)*L+K+5+MAX(2N,6M)
  92. C
  93. C If NP=0 define K=INT(log2(N-1))+1 and set L=2**(K+1) then
  94. C W must have dimension (K-2)*L+K+5+2N+MAX(2N,6M)
  95. C
  96. C **IMPORTANT** For purposes of checking, the required dimension
  97. C of W is computed by BLKTRI and stored in W(1)
  98. C in floating point format.
  99. C
  100. C * * * * * * * * * * On Output * * * * * * * * * *
  101. C
  102. C Y
  103. C Contains the solution X.
  104. C
  105. C IERROR
  106. C An error flag that indicates invalid input parameters. Except
  107. C for number zero, a solution is not attempted.
  108. C
  109. C = 0 No error.
  110. C = 1 M is less than 5.
  111. C = 2 N is less than 5.
  112. C = 3 IDIMY is less than M.
  113. C = 4 BLKTRI failed while computing results that depend on the
  114. C coefficient arrays AN, BN, CN. Check these arrays.
  115. C = 5 AN(J)*CN(J-1) is less than 0 for some J. Possible reasons
  116. C for this condition are
  117. C 1. The arrays AN and CN are not correct.
  118. C 2. Too large a grid spacing was used in the discretization
  119. C of the elliptic equation.
  120. C 3. The linear equations resulted from a partial
  121. C differential equation which was not elliptic.
  122. C
  123. C W
  124. C Contains intermediate values that must not be destroyed if
  125. C BLKTRI will be called again with IFLG=1. W(1) contains the
  126. C number of locations required by W in floating point format.
  127. C
  128. C *Long Description:
  129. C
  130. C * * * * * * * Program Specifications * * * * * * * * * * * *
  131. C
  132. C Dimension of AN(N),BN(N),CN(N),AM(M),BM(M),CM(M),Y(IDIMY,N)
  133. C Arguments W(See argument list)
  134. C
  135. C Latest June 1979
  136. C Revision
  137. C
  138. C Required BLKTRI,BLKTRI,PROD,PRODP,CPROD,CPRODP,COMPB,INDXA,
  139. C Subprograms INDXB,INDXC,PPADD,PSGF,PPSGF,PPSPF,BSRH,TEVLS,
  140. C R1MACH
  141. C
  142. C Special The Algorithm may fail if ABS(BM(I)+BN(J)) is less
  143. C Conditions than ABS(AM(I))+ABS(AN(J))+ABS(CM(I))+ABS(CN(J))
  144. C for some I and J. The Algorithm will also fail if
  145. C AN(J)*CN(J-1) is less than zero for some J.
  146. C See the description of the output parameter IERROR.
  147. C
  148. C Common CBLKT
  149. C Blocks
  150. C
  151. C I/O None
  152. C
  153. C Precision Single
  154. C
  155. C Specialist Paul Swarztrauber
  156. C
  157. C Language FORTRAN
  158. C
  159. C History Version 1 September 1973
  160. C Version 2 April 1976
  161. C Version 3 June 1979
  162. C
  163. C Algorithm Generalized Cyclic Reduction (See Reference below)
  164. C
  165. C Space
  166. C Required Control Data 7600
  167. C
  168. C Portability American National Standards Institute Fortran.
  169. C The machine accuracy is set using function R1MACH.
  170. C
  171. C Required None
  172. C Resident
  173. C Routines
  174. C
  175. C References Swarztrauber,P. and R. Sweet, 'Efficient FORTRAN
  176. C Subprograms For The Solution Of Elliptic Equations'
  177. C NCAR TN/IA-109, July, 1975, 138 PP.
  178. C
  179. C Swarztrauber P. ,'A Direct Method For The Discrete
  180. C Solution Of Separable Elliptic Equations', S.I.A.M.
  181. C J. Numer. Anal.,11(1974) PP. 1136-1150.
  182. C
  183. C***REFERENCES P. N. Swarztrauber and R. Sweet, Efficient Fortran
  184. C subprograms for the solution of elliptic equations,
  185. C NCAR TN/IA-109, July 1975, 138 pp.
  186. C P. N. Swarztrauber, A direct method for the discrete
  187. C solution of separable elliptic equations, SIAM Journal
  188. C on Numerical Analysis 11, (1974), pp. 1136-1150.
  189. C***ROUTINES CALLED BLKTR1, COMPB, CPROD, CPRODP, PROD, PRODP
  190. C***COMMON BLOCKS CBLKT
  191. C***REVISION HISTORY (YYMMDD)
  192. C 801001 DATE WRITTEN
  193. C 890531 Changed all specific intrinsics to generic. (WRB)
  194. C 890531 REVISION DATE from Version 3.2
  195. C 891214 Prologue converted to Version 4.0 format. (BAB)
  196. C 920501 Reformatted the REFERENCES section. (WRB)
  197. C***END PROLOGUE BLKTRI
  198. C
  199. DIMENSION AN(*) ,BN(*) ,CN(*) ,AM(*) ,
  200. 1 BM(*) ,CM(*) ,Y(IDIMY,*) ,W(*)
  201. EXTERNAL PROD ,PRODP ,CPROD ,CPRODP
  202. COMMON /CBLKT/ NPP ,K ,EPS ,CNV ,
  203. 1 NM ,NCMPLX ,IK
  204. C***FIRST EXECUTABLE STATEMENT BLKTRI
  205. NM = N
  206. IERROR = 0
  207. IF (M-5) 101,102,102
  208. 101 IERROR = 1
  209. GO TO 119
  210. 102 IF (NM-3) 103,104,104
  211. 103 IERROR = 2
  212. GO TO 119
  213. 104 IF (IDIMY-M) 105,106,106
  214. 105 IERROR = 3
  215. GO TO 119
  216. 106 NH = N
  217. NPP = NP
  218. IF (NPP) 107,108,107
  219. 107 NH = NH+1
  220. 108 IK = 2
  221. K = 1
  222. 109 IK = IK+IK
  223. K = K+1
  224. IF (NH-IK) 110,110,109
  225. 110 NL = IK
  226. IK = IK+IK
  227. NL = NL-1
  228. IWAH = (K-2)*IK+K+6
  229. IF (NPP) 111,112,111
  230. C
  231. C DIVIDE W INTO WORKING SUB ARRAYS
  232. C
  233. 111 IW1 = IWAH
  234. IWBH = IW1+NM
  235. W(1) = IW1-1+MAX(2*NM,6*M)
  236. GO TO 113
  237. 112 IWBH = IWAH+NM+NM
  238. IW1 = IWBH
  239. W(1) = IW1-1+MAX(2*NM,6*M)
  240. NM = NM-1
  241. C
  242. C SUBROUTINE COMP B COMPUTES THE ROOTS OF THE B POLYNOMIALS
  243. C
  244. 113 IF (IERROR) 119,114,119
  245. 114 IW2 = IW1+M
  246. IW3 = IW2+M
  247. IWD = IW3+M
  248. IWW = IWD+M
  249. IWU = IWW+M
  250. IF (IFLG) 116,115,116
  251. 115 CALL COMPB (NL,IERROR,AN,BN,CN,W(2),W(IWAH),W(IWBH))
  252. GO TO 119
  253. 116 IF (MP) 117,118,117
  254. C
  255. C SUBROUTINE BLKTR1 SOLVES THE LINEAR SYSTEM
  256. C
  257. 117 CALL BLKTR1 (NL,AN,BN,CN,M,AM,BM,CM,IDIMY,Y,W(2),W(IW1),W(IW2),
  258. 1 W(IW3),W(IWD),W(IWW),W(IWU),PROD,CPROD)
  259. GO TO 119
  260. 118 CALL BLKTR1 (NL,AN,BN,CN,M,AM,BM,CM,IDIMY,Y,W(2),W(IW1),W(IW2),
  261. 1 W(IW3),W(IWD),W(IWW),W(IWU),PRODP,CPRODP)
  262. 119 CONTINUE
  263. RETURN
  264. END