ddstp.f 18 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459
  1. *DECK DDSTP
  2. SUBROUTINE DDSTP (EPS, F, FA, HMAX, IMPL, IERROR, JACOBN, MATDIM,
  3. 8 MAXORD, MINT, MITER, ML, MU, N, NDE, YWT, UROUND, USERS, AVGH,
  4. 8 AVGORD, H, HUSED, JTASK, MNTOLD, MTROLD, NFE, NJE, NQUSED,
  5. 8 NSTEP, T, Y, YH, A, CONVRG, DFDY, EL, FAC, HOLD, IPVT, JSTATE,
  6. 8 JSTEPL, NQ, NWAIT, RC, RMAX, SAVE1, SAVE2, TQ, TREND, ISWFLG,
  7. 8 MTRSV, MXRDSV)
  8. C***BEGIN PROLOGUE DDSTP
  9. C***SUBSIDIARY
  10. C***PURPOSE DDSTP performs one step of the integration of an initial
  11. C value problem for a system of ordinary differential
  12. C equations.
  13. C***LIBRARY SLATEC (SDRIVE)
  14. C***TYPE DOUBLE PRECISION (SDSTP-S, DDSTP-D, CDSTP-C)
  15. C***AUTHOR Kahaner, D. K., (NIST)
  16. C National Institute of Standards and Technology
  17. C Gaithersburg, MD 20899
  18. C Sutherland, C. D., (LANL)
  19. C Mail Stop D466
  20. C Los Alamos National Laboratory
  21. C Los Alamos, NM 87545
  22. C***DESCRIPTION
  23. C
  24. C Communication with DDSTP is done with the following variables:
  25. C
  26. C YH An N by MAXORD+1 array containing the dependent variables
  27. C and their scaled derivatives. MAXORD, the maximum order
  28. C used, is currently 12 for the Adams methods and 5 for the
  29. C Gear methods. YH(I,J+1) contains the J-th derivative of
  30. C Y(I), scaled by H**J/factorial(J). Only Y(I),
  31. C 1 .LE. I .LE. N, need be set by the calling program on
  32. C the first entry. The YH array should not be altered by
  33. C the calling program. When referencing YH as a
  34. C 2-dimensional array, use a column length of N, as this is
  35. C the value used in DDSTP.
  36. C DFDY A block of locations used for partial derivatives if MITER
  37. C is not 0. If MITER is 1 or 2 its length must be at least
  38. C N*N. If MITER is 4 or 5 its length must be at least
  39. C (2*ML+MU+1)*N.
  40. C YWT An array of N locations used in convergence and error tests
  41. C SAVE1
  42. C SAVE2 Arrays of length N used for temporary storage.
  43. C IPVT An integer array of length N used by the linear system
  44. C solvers for the storage of row interchange information.
  45. C A A block of locations used to store the matrix A, when using
  46. C the implicit method. If IMPL is 1, A is a MATDIM by N
  47. C array. If MITER is 1 or 2 MATDIM is N, and if MITER is 4
  48. C or 5 MATDIM is 2*ML+MU+1. If IMPL is 2 its length is N.
  49. C If IMPL is 3, A is a MATDIM by NDE array.
  50. C JTASK An integer used on input.
  51. C It has the following values and meanings:
  52. C .EQ. 0 Perform the first step. This value enables
  53. C the subroutine to initialize itself.
  54. C .GT. 0 Take a new step continuing from the last.
  55. C Assumes the last step was successful and
  56. C user has not changed any parameters.
  57. C .LT. 0 Take a new step with a new value of H and/or
  58. C MINT and/or MITER.
  59. C JSTATE A completion code with the following meanings:
  60. C 1 The step was successful.
  61. C 2 A solution could not be obtained with H .NE. 0.
  62. C 3 A solution was not obtained in MXTRY attempts.
  63. C 4 For IMPL .NE. 0, the matrix A is singular.
  64. C On a return with JSTATE .GT. 1, the values of T and
  65. C the YH array are as of the beginning of the last
  66. C step, and H is the last step size attempted.
  67. C
  68. C***ROUTINES CALLED DDCOR, DDCST, DDNTL, DDPSC, DDPST, DDSCL, DNRM2
  69. C***REVISION HISTORY (YYMMDD)
  70. C 790601 DATE WRITTEN
  71. C 900329 Initial submission to SLATEC.
  72. C***END PROLOGUE DDSTP
  73. EXTERNAL F, JACOBN, FA, USERS
  74. INTEGER I, IERROR, IMPL, IPVT(*), ISWFLG, ITER, J, JSTATE, JSTEPL,
  75. 8 JTASK, MATDIM, MAXORD, MINT, MITER, ML, MNTOLD, MTROLD,
  76. 8 MTRSV, MU, MXFAIL, MXITER, MXRDSV, MXTRY, N, NDE, NDJSTP,
  77. 8 NFAIL, NFE, NJE, NQ, NQUSED, NSTEP, NSV, NTRY, NWAIT
  78. DOUBLE PRECISION A(MATDIM,*), AVGH, AVGORD, BIAS1, BIAS2, BIAS3,
  79. 8 BND, CTEST, D, DENOM, DFDY(MATDIM,*), D1, EL(13,12), EPS,
  80. 8 ERDN, ERUP, ETEST, FAC(*), H, HMAX, HN, HOLD, HS, HUSED,
  81. 8 NUMER, RC, RCTEST, RH, RH1, RH2, RH3, RMAX, RMFAIL, RMNORM,
  82. 8 SAVE1(*), SAVE2(*), DNRM2, T, TOLD, TQ(3,12), TREND, TRSHLD,
  83. 8 UROUND, Y(*), YH(N,*), YWT(*), Y0NRM
  84. LOGICAL CONVRG, EVALFA, EVALJC, IER, SWITCH
  85. PARAMETER(BIAS1 = 1.3D0, BIAS2 = 1.2D0, BIAS3 = 1.4D0, MXFAIL = 3,
  86. 8 MXITER = 3, MXTRY = 50, RCTEST = .3D0, RMFAIL = 2.D0,
  87. 8 RMNORM = 10.D0, TRSHLD = 1.D0)
  88. PARAMETER (NDJSTP = 10)
  89. DATA IER /.FALSE./
  90. C***FIRST EXECUTABLE STATEMENT DDSTP
  91. NSV = N
  92. BND = 0.D0
  93. SWITCH = .FALSE.
  94. NTRY = 0
  95. TOLD = T
  96. NFAIL = 0
  97. IF (JTASK .LE. 0) THEN
  98. CALL DDNTL (EPS, F, FA, HMAX, HOLD, IMPL, JTASK, MATDIM,
  99. 8 MAXORD, MINT, MITER, ML, MU, N, NDE, SAVE1, T,
  100. 8 UROUND, USERS, Y, YWT, H, MNTOLD, MTROLD, NFE, RC,
  101. 8 YH, A, CONVRG, EL, FAC, IER, IPVT, NQ, NWAIT, RH,
  102. 8 RMAX, SAVE2, TQ, TREND, ISWFLG, JSTATE)
  103. IF (N .EQ. 0) GO TO 440
  104. IF (H .EQ. 0.D0) GO TO 400
  105. IF (IER) GO TO 420
  106. END IF
  107. 100 NTRY = NTRY + 1
  108. IF (NTRY .GT. MXTRY) GO TO 410
  109. T = T + H
  110. CALL DDPSC (1, N, NQ, YH)
  111. EVALJC = (((ABS(RC - 1.D0) .GT. RCTEST) .OR.
  112. 8 (NSTEP .GE. JSTEPL + NDJSTP)) .AND. (MITER .NE. 0))
  113. EVALFA = .NOT. EVALJC
  114. C
  115. 110 ITER = 0
  116. DO 115 I = 1,N
  117. 115 Y(I) = YH(I,1)
  118. CALL F (N, T, Y, SAVE2)
  119. IF (N .EQ. 0) THEN
  120. JSTATE = 6
  121. GO TO 430
  122. END IF
  123. NFE = NFE + 1
  124. IF (EVALJC .OR. IER) THEN
  125. CALL DDPST (EL, F, FA, H, IMPL, JACOBN, MATDIM, MITER, ML,
  126. 8 MU, N, NDE, NQ, SAVE2, T, USERS, Y, YH, YWT, UROUND,
  127. 8 NFE, NJE, A, DFDY, FAC, IER, IPVT, SAVE1, ISWFLG,
  128. 8 BND, JSTATE)
  129. IF (N .EQ. 0) GO TO 430
  130. IF (IER) GO TO 160
  131. CONVRG = .FALSE.
  132. RC = 1.D0
  133. JSTEPL = NSTEP
  134. END IF
  135. DO 125 I = 1,N
  136. 125 SAVE1(I) = 0.D0
  137. C Up to MXITER corrector iterations are taken.
  138. C Convergence is tested by requiring the r.m.s.
  139. C norm of changes to be less than EPS. The sum of
  140. C the corrections is accumulated in the vector
  141. C SAVE1(I). It is approximately equal to the L-th
  142. C derivative of Y multiplied by
  143. C H**L/(factorial(L-1)*EL(L,NQ)), and is thus
  144. C proportional to the actual errors to the lowest
  145. C power of H present (H**L). The YH array is not
  146. C altered in the correction loop. The norm of the
  147. C iterate difference is stored in D. If
  148. C ITER .GT. 0, an estimate of the convergence rate
  149. C constant is stored in TREND, and this is used in
  150. C the convergence test.
  151. C
  152. 130 CALL DDCOR (DFDY, EL, FA, H, IERROR, IMPL, IPVT, MATDIM, MITER,
  153. 8 ML, MU, N, NDE, NQ, T, USERS, Y, YH, YWT, EVALFA,
  154. 8 SAVE1, SAVE2, A, D, JSTATE)
  155. IF (N .EQ. 0) GO TO 430
  156. IF (ISWFLG .EQ. 3 .AND. MINT .EQ. 1) THEN
  157. IF (ITER .EQ. 0) THEN
  158. NUMER = DNRM2(N, SAVE1, 1)
  159. DO 132 I = 1,N
  160. 132 DFDY(1,I) = SAVE1(I)
  161. Y0NRM = DNRM2(N, YH, 1)
  162. ELSE
  163. DENOM = NUMER
  164. DO 134 I = 1,N
  165. 134 DFDY(1,I) = SAVE1(I) - DFDY(1,I)
  166. NUMER = DNRM2(N, DFDY, MATDIM)
  167. IF (EL(1,NQ)*NUMER .LE. 100.D0*UROUND*Y0NRM) THEN
  168. IF (RMAX .EQ. RMFAIL) THEN
  169. SWITCH = .TRUE.
  170. GO TO 170
  171. END IF
  172. END IF
  173. DO 136 I = 1,N
  174. 136 DFDY(1,I) = SAVE1(I)
  175. IF (DENOM .NE. 0.D0)
  176. 8 BND = MAX(BND, NUMER/(DENOM*ABS(H)*EL(1,NQ)))
  177. END IF
  178. END IF
  179. IF (ITER .GT. 0) TREND = MAX(.9D0*TREND, D/D1)
  180. D1 = D
  181. CTEST = MIN(2.D0*TREND, 1.D0)*D
  182. IF (CTEST .LE. EPS) GO TO 170
  183. ITER = ITER + 1
  184. IF (ITER .LT. MXITER) THEN
  185. DO 140 I = 1,N
  186. 140 Y(I) = YH(I,1) + EL(1,NQ)*SAVE1(I)
  187. CALL F (N, T, Y, SAVE2)
  188. IF (N .EQ. 0) THEN
  189. JSTATE = 6
  190. GO TO 430
  191. END IF
  192. NFE = NFE + 1
  193. GO TO 130
  194. END IF
  195. C The corrector iteration failed to converge in
  196. C MXITER tries. If partials are involved but are
  197. C not up to date, they are reevaluated for the next
  198. C try. Otherwise the YH array is retracted to its
  199. C values before prediction, and H is reduced, if
  200. C possible. If not, a no-convergence exit is taken.
  201. IF (CONVRG) THEN
  202. EVALJC = .TRUE.
  203. EVALFA = .FALSE.
  204. GO TO 110
  205. END IF
  206. 160 T = TOLD
  207. CALL DDPSC (-1, N, NQ, YH)
  208. NWAIT = NQ + 2
  209. IF (JTASK .NE. 0 .AND. JTASK .NE. 2) RMAX = RMFAIL
  210. IF (ITER .EQ. 0) THEN
  211. RH = .3D0
  212. ELSE
  213. RH = .9D0*(EPS/CTEST)**(.2D0)
  214. END IF
  215. IF (RH*H .EQ. 0.D0) GO TO 400
  216. CALL DDSCL (HMAX, N, NQ, RMAX, H, RC, RH, YH)
  217. GO TO 100
  218. C The corrector has converged. CONVRG is set
  219. C to .TRUE. if partial derivatives were used,
  220. C to indicate that they may need updating on
  221. C subsequent steps. The error test is made.
  222. 170 CONVRG = (MITER .NE. 0)
  223. IF (IERROR .EQ. 1 .OR. IERROR .EQ. 5) THEN
  224. DO 180 I = 1,NDE
  225. 180 SAVE2(I) = SAVE1(I)/YWT(I)
  226. ELSE
  227. DO 185 I = 1,NDE
  228. 185 SAVE2(I) = SAVE1(I)/MAX(ABS(Y(I)), YWT(I))
  229. END IF
  230. ETEST = DNRM2(NDE, SAVE2, 1)/(TQ(2,NQ)*SQRT(DBLE(NDE)))
  231. C
  232. C The error test failed. NFAIL keeps track of
  233. C multiple failures. Restore T and the YH
  234. C array to their previous values, and prepare
  235. C to try the step again. Compute the optimum
  236. C step size for this or one lower order.
  237. IF (ETEST .GT. EPS) THEN
  238. T = TOLD
  239. CALL DDPSC (-1, N, NQ, YH)
  240. NFAIL = NFAIL + 1
  241. IF (NFAIL .LT. MXFAIL .OR. NQ .EQ. 1) THEN
  242. IF (JTASK .NE. 0 .AND. JTASK .NE. 2) RMAX = RMFAIL
  243. RH2 = 1.D0/(BIAS2*(ETEST/EPS)**(1.D0/(NQ+1)))
  244. IF (NQ .GT. 1) THEN
  245. IF (IERROR .EQ. 1 .OR. IERROR .EQ. 5) THEN
  246. DO 190 I = 1,NDE
  247. 190 SAVE2(I) = YH(I,NQ+1)/YWT(I)
  248. ELSE
  249. DO 195 I = 1,NDE
  250. 195 SAVE2(I) = YH(I,NQ+1)/MAX(ABS(Y(I)), YWT(I))
  251. END IF
  252. ERDN = DNRM2(NDE, SAVE2, 1)/(TQ(1,NQ)*SQRT(DBLE(NDE)))
  253. RH1 = 1.D0/MAX(1.D0, BIAS1*(ERDN/EPS)**(1.D0/NQ))
  254. IF (RH2 .LT. RH1) THEN
  255. NQ = NQ - 1
  256. RC = RC*EL(1,NQ)/EL(1,NQ+1)
  257. RH = RH1
  258. ELSE
  259. RH = RH2
  260. END IF
  261. ELSE
  262. RH = RH2
  263. END IF
  264. NWAIT = NQ + 2
  265. IF (RH*H .EQ. 0.D0) GO TO 400
  266. CALL DDSCL (HMAX, N, NQ, RMAX, H, RC, RH, YH)
  267. GO TO 100
  268. END IF
  269. C Control reaches this section if the error test has
  270. C failed MXFAIL or more times. It is assumed that the
  271. C derivatives that have accumulated in the YH array have
  272. C errors of the wrong order. Hence the first derivative
  273. C is recomputed, the order is set to 1, and the step is
  274. C retried.
  275. NFAIL = 0
  276. JTASK = 2
  277. DO 215 I = 1,N
  278. 215 Y(I) = YH(I,1)
  279. CALL DDNTL (EPS, F, FA, HMAX, HOLD, IMPL, JTASK, MATDIM,
  280. 8 MAXORD, MINT, MITER, ML, MU, N, NDE, SAVE1, T,
  281. 8 UROUND, USERS, Y, YWT, H, MNTOLD, MTROLD, NFE, RC,
  282. 8 YH, A, CONVRG, EL, FAC, IER, IPVT, NQ, NWAIT, RH,
  283. 8 RMAX, SAVE2, TQ, TREND, ISWFLG, JSTATE)
  284. RMAX = RMNORM
  285. IF (N .EQ. 0) GO TO 440
  286. IF (H .EQ. 0.D0) GO TO 400
  287. IF (IER) GO TO 420
  288. GO TO 100
  289. END IF
  290. C After a successful step, update the YH array.
  291. NSTEP = NSTEP + 1
  292. HUSED = H
  293. NQUSED = NQ
  294. AVGH = ((NSTEP-1)*AVGH + H)/NSTEP
  295. AVGORD = ((NSTEP-1)*AVGORD + NQ)/NSTEP
  296. DO 230 J = 1,NQ+1
  297. DO 230 I = 1,N
  298. 230 YH(I,J) = YH(I,J) + EL(J,NQ)*SAVE1(I)
  299. DO 235 I = 1,N
  300. 235 Y(I) = YH(I,1)
  301. C If ISWFLG is 3, consider
  302. C changing integration methods.
  303. IF (ISWFLG .EQ. 3) THEN
  304. IF (BND .NE. 0.D0) THEN
  305. IF (MINT .EQ. 1 .AND. NQ .LE. 5) THEN
  306. HN = ABS(H)/MAX(UROUND, (ETEST/EPS)**(1.D0/(NQ+1)))
  307. HN = MIN(HN, 1.D0/(2.D0*EL(1,NQ)*BND))
  308. HS = ABS(H)/MAX(UROUND,
  309. 8 (ETEST/(EPS*EL(NQ+1,1)))**(1.D0/(NQ+1)))
  310. IF (HS .GT. 1.2D0*HN) THEN
  311. MINT = 2
  312. MNTOLD = MINT
  313. MITER = MTRSV
  314. MTROLD = MITER
  315. MAXORD = MIN(MXRDSV, 5)
  316. RC = 0.D0
  317. RMAX = RMNORM
  318. TREND = 1.D0
  319. CALL DDCST (MAXORD, MINT, ISWFLG, EL, TQ)
  320. NWAIT = NQ + 2
  321. END IF
  322. ELSE IF (MINT .EQ. 2) THEN
  323. HS = ABS(H)/MAX(UROUND, (ETEST/EPS)**(1.D0/(NQ+1)))
  324. HN = ABS(H)/MAX(UROUND,
  325. 8 (ETEST*EL(NQ+1,1)/EPS)**(1.D0/(NQ+1)))
  326. HN = MIN(HN, 1.D0/(2.D0*EL(1,NQ)*BND))
  327. IF (HN .GE. HS) THEN
  328. MINT = 1
  329. MNTOLD = MINT
  330. MITER = 0
  331. MTROLD = MITER
  332. MAXORD = MIN(MXRDSV, 12)
  333. RMAX = RMNORM
  334. TREND = 1.D0
  335. CONVRG = .FALSE.
  336. CALL DDCST (MAXORD, MINT, ISWFLG, EL, TQ)
  337. NWAIT = NQ + 2
  338. END IF
  339. END IF
  340. END IF
  341. END IF
  342. IF (SWITCH) THEN
  343. MINT = 2
  344. MNTOLD = MINT
  345. MITER = MTRSV
  346. MTROLD = MITER
  347. MAXORD = MIN(MXRDSV, 5)
  348. NQ = MIN(NQ, MAXORD)
  349. RC = 0.D0
  350. RMAX = RMNORM
  351. TREND = 1.D0
  352. CALL DDCST (MAXORD, MINT, ISWFLG, EL, TQ)
  353. NWAIT = NQ + 2
  354. END IF
  355. C Consider changing H if NWAIT = 1. Otherwise
  356. C decrease NWAIT by 1. If NWAIT is then 1 and
  357. C NQ.LT.MAXORD, then SAVE1 is saved for use in
  358. C a possible order increase on the next step.
  359. C
  360. IF (JTASK .EQ. 0 .OR. JTASK .EQ. 2) THEN
  361. RH = 1.D0/MAX(UROUND, BIAS2*(ETEST/EPS)**(1.D0/(NQ+1)))
  362. IF (RH.GT.TRSHLD) CALL DDSCL (HMAX, N, NQ, RMAX, H, RC, RH, YH)
  363. ELSE IF (NWAIT .GT. 1) THEN
  364. NWAIT = NWAIT - 1
  365. IF (NWAIT .EQ. 1 .AND. NQ .LT. MAXORD) THEN
  366. DO 250 I = 1,NDE
  367. 250 YH(I,MAXORD+1) = SAVE1(I)
  368. END IF
  369. C If a change in H is considered, an increase or decrease in
  370. C order by one is considered also. A change in H is made
  371. C only if it is by a factor of at least TRSHLD. Factors
  372. C RH1, RH2, and RH3 are computed, by which H could be
  373. C multiplied at order NQ - 1, order NQ, or order NQ + 1,
  374. C respectively. The largest of these is determined and the
  375. C new order chosen accordingly. If the order is to be
  376. C increased, we compute one additional scaled derivative.
  377. C If there is a change of order, reset NQ and the
  378. C coefficients. In any case H is reset according to RH and
  379. C the YH array is rescaled.
  380. ELSE
  381. IF (NQ .EQ. 1) THEN
  382. RH1 = 0.D0
  383. ELSE
  384. IF (IERROR .EQ. 1 .OR. IERROR .EQ. 5) THEN
  385. DO 270 I = 1,NDE
  386. 270 SAVE2(I) = YH(I,NQ+1)/YWT(I)
  387. ELSE
  388. DO 275 I = 1,NDE
  389. 275 SAVE2(I) = YH(I,NQ+1)/MAX(ABS(Y(I)), YWT(I))
  390. END IF
  391. ERDN = DNRM2(NDE, SAVE2, 1)/(TQ(1,NQ)*SQRT(DBLE(NDE)))
  392. RH1 = 1.D0/MAX(UROUND, BIAS1*(ERDN/EPS)**(1.D0/NQ))
  393. END IF
  394. RH2 = 1.D0/MAX(UROUND, BIAS2*(ETEST/EPS)**(1.D0/(NQ+1)))
  395. IF (NQ .EQ. MAXORD) THEN
  396. RH3 = 0.D0
  397. ELSE
  398. IF (IERROR .EQ. 1 .OR. IERROR .EQ. 5) THEN
  399. DO 290 I = 1,NDE
  400. 290 SAVE2(I) = (SAVE1(I) - YH(I,MAXORD+1))/YWT(I)
  401. ELSE
  402. DO 295 I = 1,NDE
  403. SAVE2(I) = (SAVE1(I) - YH(I,MAXORD+1))/
  404. 8 MAX(ABS(Y(I)), YWT(I))
  405. 295 CONTINUE
  406. END IF
  407. ERUP = DNRM2(NDE, SAVE2, 1)/(TQ(3,NQ)*SQRT(DBLE(NDE)))
  408. RH3 = 1.D0/MAX(UROUND, BIAS3*(ERUP/EPS)**(1.D0/(NQ+2)))
  409. END IF
  410. IF (RH1 .GT. RH2 .AND. RH1 .GE. RH3) THEN
  411. RH = RH1
  412. IF (RH .LE. TRSHLD) GO TO 380
  413. NQ = NQ - 1
  414. RC = RC*EL(1,NQ)/EL(1,NQ+1)
  415. ELSE IF (RH2 .GE. RH1 .AND. RH2 .GE. RH3) THEN
  416. RH = RH2
  417. IF (RH .LE. TRSHLD) GO TO 380
  418. ELSE
  419. RH = RH3
  420. IF (RH .LE. TRSHLD) GO TO 380
  421. DO 360 I = 1,N
  422. 360 YH(I,NQ+2) = SAVE1(I)*EL(NQ+1,NQ)/(NQ+1)
  423. NQ = NQ + 1
  424. RC = RC*EL(1,NQ)/EL(1,NQ-1)
  425. END IF
  426. IF (ISWFLG .EQ. 3 .AND. MINT .EQ. 1) THEN
  427. IF (BND.NE.0.D0) RH = MIN(RH, 1.D0/(2.D0*EL(1,NQ)*BND*ABS(H)))
  428. END IF
  429. CALL DDSCL (HMAX, N, NQ, RMAX, H, RC, RH, YH)
  430. RMAX = RMNORM
  431. 380 NWAIT = NQ + 2
  432. END IF
  433. C All returns are made through this section. H is saved
  434. C in HOLD to allow the caller to change H on the next step
  435. JSTATE = 1
  436. HOLD = H
  437. RETURN
  438. C
  439. 400 JSTATE = 2
  440. HOLD = H
  441. DO 405 I = 1,N
  442. 405 Y(I) = YH(I,1)
  443. RETURN
  444. C
  445. 410 JSTATE = 3
  446. HOLD = H
  447. RETURN
  448. C
  449. 420 JSTATE = 4
  450. HOLD = H
  451. RETURN
  452. C
  453. 430 T = TOLD
  454. CALL DDPSC (-1, NSV, NQ, YH)
  455. DO 435 I = 1,NSV
  456. 435 Y(I) = YH(I,1)
  457. 440 HOLD = H
  458. RETURN
  459. END