cblktr.f 9.1 KB

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