steps.f 18 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568
  1. *DECK STEPS
  2. SUBROUTINE STEPS (F, NEQN, Y, X, H, EPS, WT, START, HOLD, K, KOLD,
  3. + CRASH, PHI, P, YP, PSI, ALPHA, BETA, SIG, V, W, G, PHASE1, NS,
  4. + NORND, KSTEPS, TWOU, FOURU, XOLD, KPREV, IVC, IV, KGI, GI,
  5. + RPAR, IPAR)
  6. C***BEGIN PROLOGUE STEPS
  7. C***PURPOSE Integrate a system of first order ordinary differential
  8. C equations one step.
  9. C***LIBRARY SLATEC (DEPAC)
  10. C***CATEGORY I1A1B
  11. C***TYPE SINGLE PRECISION (STEPS-S, DSTEPS-D)
  12. C***KEYWORDS ADAMS METHOD, DEPAC, INITIAL VALUE PROBLEMS, ODE,
  13. C ORDINARY DIFFERENTIAL EQUATIONS, PREDICTOR-CORRECTOR
  14. C***AUTHOR Shampine, L. F., (SNLA)
  15. C Gordon, M. K., (SNLA)
  16. C MODIFIED BY H.A. WATTS
  17. C***DESCRIPTION
  18. C
  19. C Written by L. F. Shampine and M. K. Gordon
  20. C
  21. C Abstract
  22. C
  23. C Subroutine STEPS is normally used indirectly through subroutine
  24. C DEABM . Because DEABM suffices for most problems and is much
  25. C easier to use, using it should be considered before using STEPS
  26. C alone.
  27. C
  28. C Subroutine STEPS integrates a system of NEQN first order ordinary
  29. C differential equations one step, normally from X to X+H, using a
  30. C modified divided difference form of the Adams Pece formulas. Local
  31. C extrapolation is used to improve absolute stability and accuracy.
  32. C The code adjusts its order and step size to control the local error
  33. C per unit step in a generalized sense. Special devices are included
  34. C to control roundoff error and to detect when the user is requesting
  35. C too much accuracy.
  36. C
  37. C This code is completely explained and documented in the text,
  38. C Computer Solution of Ordinary Differential Equations, The Initial
  39. C Value Problem by L. F. Shampine and M. K. Gordon.
  40. C Further details on use of this code are available in "Solving
  41. C Ordinary Differential Equations with ODE, STEP, and INTRP",
  42. C by L. F. Shampine and M. K. Gordon, SLA-73-1060.
  43. C
  44. C
  45. C The parameters represent --
  46. C F -- subroutine to evaluate derivatives
  47. C NEQN -- number of equations to be integrated
  48. C Y(*) -- solution vector at X
  49. C X -- independent variable
  50. C H -- appropriate step size for next step. Normally determined by
  51. C code
  52. C EPS -- local error tolerance
  53. C WT(*) -- vector of weights for error criterion
  54. C START -- logical variable set .TRUE. for first step, .FALSE.
  55. C otherwise
  56. C HOLD -- step size used for last successful step
  57. C K -- appropriate order for next step (determined by code)
  58. C KOLD -- order used for last successful step
  59. C CRASH -- logical variable set .TRUE. when no step can be taken,
  60. C .FALSE. otherwise.
  61. C YP(*) -- derivative of solution vector at X after successful
  62. C step
  63. C KSTEPS -- counter on attempted steps
  64. C TWOU -- 2.*U where U is machine unit roundoff quantity
  65. C FOURU -- 4.*U where U is machine unit roundoff quantity
  66. C RPAR,IPAR -- parameter arrays which you may choose to use
  67. C for communication between your program and subroutine F.
  68. C They are not altered or used by STEPS.
  69. C The variables X,XOLD,KOLD,KGI and IVC and the arrays Y,PHI,ALPHA,G,
  70. C W,P,IV and GI are required for the interpolation subroutine SINTRP.
  71. C The remaining variables and arrays are included in the call list
  72. C only to eliminate local retention of variables between calls.
  73. C
  74. C Input to STEPS
  75. C
  76. C First call --
  77. C
  78. C The user must provide storage in his calling program for all arrays
  79. C in the call list, namely
  80. C
  81. C DIMENSION Y(NEQN),WT(NEQN),PHI(NEQN,16),P(NEQN),YP(NEQN),PSI(12),
  82. C 1 ALPHA(12),BETA(12),SIG(13),V(12),W(12),G(13),GI(11),IV(10),
  83. C 2 RPAR(*),IPAR(*)
  84. C
  85. C **Note**
  86. C
  87. C The user must also declare START , CRASH , PHASE1 and NORND
  88. C logical variables and F an EXTERNAL subroutine, supply the
  89. C subroutine F(X,Y,YP) to evaluate
  90. C DY(I)/DX = YP(I) = F(X,Y(1),Y(2),...,Y(NEQN))
  91. C and initialize only the following parameters.
  92. C NEQN -- number of equations to be integrated
  93. C Y(*) -- vector of initial values of dependent variables
  94. C X -- initial value of the independent variable
  95. C H -- nominal step size indicating direction of integration
  96. C and maximum size of step. Must be variable
  97. C EPS -- local error tolerance per step. Must be variable
  98. C WT(*) -- vector of non-zero weights for error criterion
  99. C START -- .TRUE.
  100. C YP(*) -- vector of initial derivative values
  101. C KSTEPS -- set KSTEPS to zero
  102. C TWOU -- 2.*U where U is machine unit roundoff quantity
  103. C FOURU -- 4.*U where U is machine unit roundoff quantity
  104. C Define U to be the machine unit roundoff quantity by calling
  105. C the function routine R1MACH, U = R1MACH(4), or by
  106. C computing U so that U is the smallest positive number such
  107. C that 1.0+U .GT. 1.0.
  108. C
  109. C STEPS requires that the L2 norm of the vector with components
  110. C LOCAL ERROR(L)/WT(L) be less than EPS for a successful step. The
  111. C array WT allows the user to specify an error test appropriate
  112. C for his problem. For example,
  113. C WT(L) = 1.0 specifies absolute error,
  114. C = ABS(Y(L)) error relative to the most recent value of the
  115. C L-th component of the solution,
  116. C = ABS(YP(L)) error relative to the most recent value of
  117. C the L-th component of the derivative,
  118. C = MAX(WT(L),ABS(Y(L))) error relative to the largest
  119. C magnitude of L-th component obtained so far,
  120. C = ABS(Y(L))*RELERR/EPS + ABSERR/EPS specifies a mixed
  121. C relative-absolute test where RELERR is relative
  122. C error, ABSERR is absolute error and EPS =
  123. C MAX(RELERR,ABSERR) .
  124. C
  125. C Subsequent calls --
  126. C
  127. C Subroutine STEPS is designed so that all information needed to
  128. C continue the integration, including the step size H and the order
  129. C K , is returned with each step. With the exception of the step
  130. C size, the error tolerance, and the weights, none of the parameters
  131. C should be altered. The array WT must be updated after each step
  132. C to maintain relative error tests like those above. Normally the
  133. C integration is continued just beyond the desired endpoint and the
  134. C solution interpolated there with subroutine SINTRP . If it is
  135. C impossible to integrate beyond the endpoint, the step size may be
  136. C reduced to hit the endpoint since the code will not take a step
  137. C larger than the H input. Changing the direction of integration,
  138. C i.e., the sign of H , requires the user set START = .TRUE. before
  139. C calling STEPS again. This is the only situation in which START
  140. C should be altered.
  141. C
  142. C Output from STEPS
  143. C
  144. C Successful Step --
  145. C
  146. C The subroutine returns after each successful step with START and
  147. C CRASH set .FALSE. . X represents the independent variable
  148. C advanced one step of length HOLD from its value on input and Y
  149. C the solution vector at the new value of X . All other parameters
  150. C represent information corresponding to the new X needed to
  151. C continue the integration.
  152. C
  153. C Unsuccessful Step --
  154. C
  155. C When the error tolerance is too small for the machine precision,
  156. C the subroutine returns without taking a step and CRASH = .TRUE. .
  157. C An appropriate step size and error tolerance for continuing are
  158. C estimated and all other information is restored as upon input
  159. C before returning. To continue with the larger tolerance, the user
  160. C just calls the code again. A restart is neither required nor
  161. C desirable.
  162. C
  163. C***REFERENCES L. F. Shampine and M. K. Gordon, Solving ordinary
  164. C differential equations with ODE, STEP, and INTRP,
  165. C Report SLA-73-1060, Sandia Laboratories, 1973.
  166. C***ROUTINES CALLED HSTART, R1MACH
  167. C***REVISION HISTORY (YYMMDD)
  168. C 740101 DATE WRITTEN
  169. C 890531 Changed all specific intrinsics to generic. (WRB)
  170. C 890831 Modified array declarations. (WRB)
  171. C 890831 REVISION DATE from Version 3.2
  172. C 891214 Prologue converted to Version 4.0 format. (BAB)
  173. C 920501 Reformatted the REFERENCES section. (WRB)
  174. C***END PROLOGUE STEPS
  175. C
  176. LOGICAL START,CRASH,PHASE1,NORND
  177. DIMENSION Y(*),WT(*),PHI(NEQN,16),P(*),YP(*),PSI(12),
  178. 1 ALPHA(12),BETA(12),SIG(13),V(12),W(12),G(13),GI(11),IV(10),
  179. 2 RPAR(*),IPAR(*)
  180. DIMENSION TWO(13),GSTR(13)
  181. EXTERNAL F
  182. SAVE TWO, GSTR
  183. C
  184. DATA TWO(1),TWO(2),TWO(3),TWO(4),TWO(5),TWO(6),TWO(7),TWO(8),
  185. 1 TWO(9),TWO(10),TWO(11),TWO(12),TWO(13) /2.0,4.0,8.0,16.0,
  186. 2 32.0,64.0,128.0,256.0,512.0,1024.0,2048.0,4096.0,8192.0/
  187. DATA GSTR(1),GSTR(2),GSTR(3),GSTR(4),GSTR(5),GSTR(6),GSTR(7),
  188. 1 GSTR(8),GSTR(9),GSTR(10),GSTR(11),GSTR(12),GSTR(13)/0.500,
  189. 2 0.0833,0.0417,0.0264,0.0188,0.0143,0.0114,0.00936,0.00789,
  190. 3 0.00679,0.00592,0.00524,0.00468/
  191. C
  192. C
  193. C *** BEGIN BLOCK 0 ***
  194. C CHECK IF STEP SIZE OR ERROR TOLERANCE IS TOO SMALL FOR MACHINE
  195. C PRECISION. IF FIRST STEP, INITIALIZE PHI ARRAY AND ESTIMATE A
  196. C STARTING STEP SIZE.
  197. C ***
  198. C
  199. C IF STEP SIZE IS TOO SMALL, DETERMINE AN ACCEPTABLE ONE
  200. C
  201. C***FIRST EXECUTABLE STATEMENT STEPS
  202. CRASH = .TRUE.
  203. IF(ABS(H) .GE. FOURU*ABS(X)) GO TO 5
  204. H = SIGN(FOURU*ABS(X),H)
  205. RETURN
  206. 5 P5EPS = 0.5*EPS
  207. C
  208. C IF ERROR TOLERANCE IS TOO SMALL, INCREASE IT TO AN ACCEPTABLE VALUE
  209. C
  210. ROUND = 0.0
  211. DO 10 L = 1,NEQN
  212. 10 ROUND = ROUND + (Y(L)/WT(L))**2
  213. ROUND = TWOU*SQRT(ROUND)
  214. IF(P5EPS .GE. ROUND) GO TO 15
  215. EPS = 2.0*ROUND*(1.0 + FOURU)
  216. RETURN
  217. 15 CRASH = .FALSE.
  218. G(1) = 1.0
  219. G(2) = 0.5
  220. SIG(1) = 1.0
  221. IF(.NOT.START) GO TO 99
  222. C
  223. C INITIALIZE. COMPUTE APPROPRIATE STEP SIZE FOR FIRST STEP
  224. C
  225. C CALL F(X,Y,YP,RPAR,IPAR)
  226. C SUM = 0.0
  227. DO 20 L = 1,NEQN
  228. PHI(L,1) = YP(L)
  229. 20 PHI(L,2) = 0.0
  230. C20 SUM = SUM + (YP(L)/WT(L))**2
  231. C SUM = SQRT(SUM)
  232. C ABSH = ABS(H)
  233. C IF(EPS .LT. 16.0*SUM*H*H) ABSH = 0.25*SQRT(EPS/SUM)
  234. C H = SIGN(MAX(ABSH,FOURU*ABS(X)),H)
  235. C
  236. U = R1MACH(4)
  237. BIG = SQRT(R1MACH(2))
  238. CALL HSTART (F,NEQN,X,X+H,Y,YP,WT,1,U,BIG,
  239. 1 PHI(1,3),PHI(1,4),PHI(1,5),PHI(1,6),RPAR,IPAR,H)
  240. C
  241. HOLD = 0.0
  242. K = 1
  243. KOLD = 0
  244. KPREV = 0
  245. START = .FALSE.
  246. PHASE1 = .TRUE.
  247. NORND = .TRUE.
  248. IF(P5EPS .GT. 100.0*ROUND) GO TO 99
  249. NORND = .FALSE.
  250. DO 25 L = 1,NEQN
  251. 25 PHI(L,15) = 0.0
  252. 99 IFAIL = 0
  253. C *** END BLOCK 0 ***
  254. C
  255. C *** BEGIN BLOCK 1 ***
  256. C COMPUTE COEFFICIENTS OF FORMULAS FOR THIS STEP. AVOID COMPUTING
  257. C THOSE QUANTITIES NOT CHANGED WHEN STEP SIZE IS NOT CHANGED.
  258. C ***
  259. C
  260. 100 KP1 = K+1
  261. KP2 = K+2
  262. KM1 = K-1
  263. KM2 = K-2
  264. C
  265. C NS IS THE NUMBER OF STEPS TAKEN WITH SIZE H, INCLUDING THE CURRENT
  266. C ONE. WHEN K.LT.NS, NO COEFFICIENTS CHANGE
  267. C
  268. IF(H .NE. HOLD) NS = 0
  269. IF (NS.LE.KOLD) NS = NS+1
  270. NSP1 = NS+1
  271. IF (K .LT. NS) GO TO 199
  272. C
  273. C COMPUTE THOSE COMPONENTS OF ALPHA(*),BETA(*),PSI(*),SIG(*) WHICH
  274. C ARE CHANGED
  275. C
  276. BETA(NS) = 1.0
  277. REALNS = NS
  278. ALPHA(NS) = 1.0/REALNS
  279. TEMP1 = H*REALNS
  280. SIG(NSP1) = 1.0
  281. IF(K .LT. NSP1) GO TO 110
  282. DO 105 I = NSP1,K
  283. IM1 = I-1
  284. TEMP2 = PSI(IM1)
  285. PSI(IM1) = TEMP1
  286. BETA(I) = BETA(IM1)*PSI(IM1)/TEMP2
  287. TEMP1 = TEMP2 + H
  288. ALPHA(I) = H/TEMP1
  289. REALI = I
  290. 105 SIG(I+1) = REALI*ALPHA(I)*SIG(I)
  291. 110 PSI(K) = TEMP1
  292. C
  293. C COMPUTE COEFFICIENTS G(*)
  294. C
  295. C INITIALIZE V(*) AND SET W(*).
  296. C
  297. IF(NS .GT. 1) GO TO 120
  298. DO 115 IQ = 1,K
  299. TEMP3 = IQ*(IQ+1)
  300. V(IQ) = 1.0/TEMP3
  301. 115 W(IQ) = V(IQ)
  302. IVC = 0
  303. KGI = 0
  304. IF (K .EQ. 1) GO TO 140
  305. KGI = 1
  306. GI(1) = W(2)
  307. GO TO 140
  308. C
  309. C IF ORDER WAS RAISED, UPDATE DIAGONAL PART OF V(*)
  310. C
  311. 120 IF(K .LE. KPREV) GO TO 130
  312. IF (IVC .EQ. 0) GO TO 122
  313. JV = KP1 - IV(IVC)
  314. IVC = IVC - 1
  315. GO TO 123
  316. 122 JV = 1
  317. TEMP4 = K*KP1
  318. V(K) = 1.0/TEMP4
  319. W(K) = V(K)
  320. IF (K .NE. 2) GO TO 123
  321. KGI = 1
  322. GI(1) = W(2)
  323. 123 NSM2 = NS-2
  324. IF(NSM2 .LT. JV) GO TO 130
  325. DO 125 J = JV,NSM2
  326. I = K-J
  327. V(I) = V(I) - ALPHA(J+1)*V(I+1)
  328. 125 W(I) = V(I)
  329. IF (I .NE. 2) GO TO 130
  330. KGI = NS - 1
  331. GI(KGI) = W(2)
  332. C
  333. C UPDATE V(*) AND SET W(*)
  334. C
  335. 130 LIMIT1 = KP1 - NS
  336. TEMP5 = ALPHA(NS)
  337. DO 135 IQ = 1,LIMIT1
  338. V(IQ) = V(IQ) - TEMP5*V(IQ+1)
  339. 135 W(IQ) = V(IQ)
  340. G(NSP1) = W(1)
  341. IF (LIMIT1 .EQ. 1) GO TO 137
  342. KGI = NS
  343. GI(KGI) = W(2)
  344. 137 W(LIMIT1+1) = V(LIMIT1+1)
  345. IF (K .GE. KOLD) GO TO 140
  346. IVC = IVC + 1
  347. IV(IVC) = LIMIT1 + 2
  348. C
  349. C COMPUTE THE G(*) IN THE WORK VECTOR W(*)
  350. C
  351. 140 NSP2 = NS + 2
  352. KPREV = K
  353. IF(KP1 .LT. NSP2) GO TO 199
  354. DO 150 I = NSP2,KP1
  355. LIMIT2 = KP2 - I
  356. TEMP6 = ALPHA(I-1)
  357. DO 145 IQ = 1,LIMIT2
  358. 145 W(IQ) = W(IQ) - TEMP6*W(IQ+1)
  359. 150 G(I) = W(1)
  360. 199 CONTINUE
  361. C *** END BLOCK 1 ***
  362. C
  363. C *** BEGIN BLOCK 2 ***
  364. C PREDICT A SOLUTION P(*), EVALUATE DERIVATIVES USING PREDICTED
  365. C SOLUTION, ESTIMATE LOCAL ERROR AT ORDER K AND ERRORS AT ORDERS K,
  366. C K-1, K-2 AS IF CONSTANT STEP SIZE WERE USED.
  367. C ***
  368. C
  369. C INCREMENT COUNTER ON ATTEMPTED STEPS
  370. C
  371. KSTEPS = KSTEPS + 1
  372. C
  373. C CHANGE PHI TO PHI STAR
  374. C
  375. IF(K .LT. NSP1) GO TO 215
  376. DO 210 I = NSP1,K
  377. TEMP1 = BETA(I)
  378. DO 205 L = 1,NEQN
  379. 205 PHI(L,I) = TEMP1*PHI(L,I)
  380. 210 CONTINUE
  381. C
  382. C PREDICT SOLUTION AND DIFFERENCES
  383. C
  384. 215 DO 220 L = 1,NEQN
  385. PHI(L,KP2) = PHI(L,KP1)
  386. PHI(L,KP1) = 0.0
  387. 220 P(L) = 0.0
  388. DO 230 J = 1,K
  389. I = KP1 - J
  390. IP1 = I+1
  391. TEMP2 = G(I)
  392. DO 225 L = 1,NEQN
  393. P(L) = P(L) + TEMP2*PHI(L,I)
  394. 225 PHI(L,I) = PHI(L,I) + PHI(L,IP1)
  395. 230 CONTINUE
  396. IF(NORND) GO TO 240
  397. DO 235 L = 1,NEQN
  398. TAU = H*P(L) - PHI(L,15)
  399. P(L) = Y(L) + TAU
  400. 235 PHI(L,16) = (P(L) - Y(L)) - TAU
  401. GO TO 250
  402. 240 DO 245 L = 1,NEQN
  403. 245 P(L) = Y(L) + H*P(L)
  404. 250 XOLD = X
  405. X = X + H
  406. ABSH = ABS(H)
  407. CALL F(X,P,YP,RPAR,IPAR)
  408. C
  409. C ESTIMATE ERRORS AT ORDERS K,K-1,K-2
  410. C
  411. ERKM2 = 0.0
  412. ERKM1 = 0.0
  413. ERK = 0.0
  414. DO 265 L = 1,NEQN
  415. TEMP3 = 1.0/WT(L)
  416. TEMP4 = YP(L) - PHI(L,1)
  417. IF(KM2)265,260,255
  418. 255 ERKM2 = ERKM2 + ((PHI(L,KM1)+TEMP4)*TEMP3)**2
  419. 260 ERKM1 = ERKM1 + ((PHI(L,K)+TEMP4)*TEMP3)**2
  420. 265 ERK = ERK + (TEMP4*TEMP3)**2
  421. IF(KM2)280,275,270
  422. 270 ERKM2 = ABSH*SIG(KM1)*GSTR(KM2)*SQRT(ERKM2)
  423. 275 ERKM1 = ABSH*SIG(K)*GSTR(KM1)*SQRT(ERKM1)
  424. 280 TEMP5 = ABSH*SQRT(ERK)
  425. ERR = TEMP5*(G(K)-G(KP1))
  426. ERK = TEMP5*SIG(KP1)*GSTR(K)
  427. KNEW = K
  428. C
  429. C TEST IF ORDER SHOULD BE LOWERED
  430. C
  431. IF(KM2)299,290,285
  432. 285 IF(MAX(ERKM1,ERKM2) .LE. ERK) KNEW = KM1
  433. GO TO 299
  434. 290 IF(ERKM1 .LE. 0.5*ERK) KNEW = KM1
  435. C
  436. C TEST IF STEP SUCCESSFUL
  437. C
  438. 299 IF(ERR .LE. EPS) GO TO 400
  439. C *** END BLOCK 2 ***
  440. C
  441. C *** BEGIN BLOCK 3 ***
  442. C THE STEP IS UNSUCCESSFUL. RESTORE X, PHI(*,*), PSI(*) .
  443. C IF THIRD CONSECUTIVE FAILURE, SET ORDER TO ONE. IF STEP FAILS MORE
  444. C THAN THREE TIMES, CONSIDER AN OPTIMAL STEP SIZE. DOUBLE ERROR
  445. C TOLERANCE AND RETURN IF ESTIMATED STEP SIZE IS TOO SMALL FOR MACHINE
  446. C PRECISION.
  447. C ***
  448. C
  449. C RESTORE X, PHI(*,*) AND PSI(*)
  450. C
  451. PHASE1 = .FALSE.
  452. X = XOLD
  453. DO 310 I = 1,K
  454. TEMP1 = 1.0/BETA(I)
  455. IP1 = I+1
  456. DO 305 L = 1,NEQN
  457. 305 PHI(L,I) = TEMP1*(PHI(L,I) - PHI(L,IP1))
  458. 310 CONTINUE
  459. IF(K .LT. 2) GO TO 320
  460. DO 315 I = 2,K
  461. 315 PSI(I-1) = PSI(I) - H
  462. C
  463. C ON THIRD FAILURE, SET ORDER TO ONE. THEREAFTER, USE OPTIMAL STEP
  464. C SIZE
  465. C
  466. 320 IFAIL = IFAIL + 1
  467. TEMP2 = 0.5
  468. IF(IFAIL - 3) 335,330,325
  469. 325 IF(P5EPS .LT. 0.25*ERK) TEMP2 = SQRT(P5EPS/ERK)
  470. 330 KNEW = 1
  471. 335 H = TEMP2*H
  472. K = KNEW
  473. NS = 0
  474. IF(ABS(H) .GE. FOURU*ABS(X)) GO TO 340
  475. CRASH = .TRUE.
  476. H = SIGN(FOURU*ABS(X),H)
  477. EPS = EPS + EPS
  478. RETURN
  479. 340 GO TO 100
  480. C *** END BLOCK 3 ***
  481. C
  482. C *** BEGIN BLOCK 4 ***
  483. C THE STEP IS SUCCESSFUL. CORRECT THE PREDICTED SOLUTION, EVALUATE
  484. C THE DERIVATIVES USING THE CORRECTED SOLUTION AND UPDATE THE
  485. C DIFFERENCES. DETERMINE BEST ORDER AND STEP SIZE FOR NEXT STEP.
  486. C ***
  487. 400 KOLD = K
  488. HOLD = H
  489. C
  490. C CORRECT AND EVALUATE
  491. C
  492. TEMP1 = H*G(KP1)
  493. IF(NORND) GO TO 410
  494. DO 405 L = 1,NEQN
  495. TEMP3 = Y(L)
  496. RHO = TEMP1*(YP(L) - PHI(L,1)) - PHI(L,16)
  497. Y(L) = P(L) + RHO
  498. PHI(L,15) = (Y(L) - P(L)) - RHO
  499. 405 P(L) = TEMP3
  500. GO TO 420
  501. 410 DO 415 L = 1,NEQN
  502. TEMP3 = Y(L)
  503. Y(L) = P(L) + TEMP1*(YP(L) - PHI(L,1))
  504. 415 P(L) = TEMP3
  505. 420 CALL F(X,Y,YP,RPAR,IPAR)
  506. C
  507. C UPDATE DIFFERENCES FOR NEXT STEP
  508. C
  509. DO 425 L = 1,NEQN
  510. PHI(L,KP1) = YP(L) - PHI(L,1)
  511. 425 PHI(L,KP2) = PHI(L,KP1) - PHI(L,KP2)
  512. DO 435 I = 1,K
  513. DO 430 L = 1,NEQN
  514. 430 PHI(L,I) = PHI(L,I) + PHI(L,KP1)
  515. 435 CONTINUE
  516. C
  517. C ESTIMATE ERROR AT ORDER K+1 UNLESS:
  518. C IN FIRST PHASE WHEN ALWAYS RAISE ORDER,
  519. C ALREADY DECIDED TO LOWER ORDER,
  520. C STEP SIZE NOT CONSTANT SO ESTIMATE UNRELIABLE
  521. C
  522. ERKP1 = 0.0
  523. IF(KNEW .EQ. KM1 .OR. K .EQ. 12) PHASE1 = .FALSE.
  524. IF(PHASE1) GO TO 450
  525. IF(KNEW .EQ. KM1) GO TO 455
  526. IF(KP1 .GT. NS) GO TO 460
  527. DO 440 L = 1,NEQN
  528. 440 ERKP1 = ERKP1 + (PHI(L,KP2)/WT(L))**2
  529. ERKP1 = ABSH*GSTR(KP1)*SQRT(ERKP1)
  530. C
  531. C USING ESTIMATED ERROR AT ORDER K+1, DETERMINE APPROPRIATE ORDER
  532. C FOR NEXT STEP
  533. C
  534. IF(K .GT. 1) GO TO 445
  535. IF(ERKP1 .GE. 0.5*ERK) GO TO 460
  536. GO TO 450
  537. 445 IF(ERKM1 .LE. MIN(ERK,ERKP1)) GO TO 455
  538. IF(ERKP1 .GE. ERK .OR. K .EQ. 12) GO TO 460
  539. C
  540. C HERE ERKP1 .LT. ERK .LT. MAX(ERKM1,ERKM2) ELSE ORDER WOULD HAVE
  541. C BEEN LOWERED IN BLOCK 2. THUS ORDER IS TO BE RAISED
  542. C
  543. C RAISE ORDER
  544. C
  545. 450 K = KP1
  546. ERK = ERKP1
  547. GO TO 460
  548. C
  549. C LOWER ORDER
  550. C
  551. 455 K = KM1
  552. ERK = ERKM1
  553. C
  554. C WITH NEW ORDER DETERMINE APPROPRIATE STEP SIZE FOR NEXT STEP
  555. C
  556. 460 HNEW = H + H
  557. IF(PHASE1) GO TO 465
  558. IF(P5EPS .GE. ERK*TWO(K+1)) GO TO 465
  559. HNEW = H
  560. IF(P5EPS .GE. ERK) GO TO 465
  561. TEMP2 = K+1
  562. R = (P5EPS/ERK)**(1.0/TEMP2)
  563. HNEW = ABSH*MAX(0.5,MIN(0.9,R))
  564. HNEW = SIGN(MAX(HNEW,FOURU*ABS(X)),H)
  565. 465 H = HNEW
  566. RETURN
  567. C *** END BLOCK 4 ***
  568. END