ddriv2.f 20 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411
  1. *DECK DDRIV2
  2. SUBROUTINE DDRIV2 (N, T, Y, F, TOUT, MSTATE, NROOT, EPS, EWT,
  3. 8 MINT, WORK, LENW, IWORK, LENIW, G, IERFLG)
  4. C***BEGIN PROLOGUE DDRIV2
  5. C***PURPOSE The function of DDRIV2 is to solve N ordinary differential
  6. C equations of the form dY(I)/dT = F(Y(I),T), given the
  7. C initial conditions Y(I) = YI. The program has options to
  8. C allow the solution of both stiff and non-stiff differential
  9. C equations. DDRIV2 uses double precision arithmetic.
  10. C***LIBRARY SLATEC (SDRIVE)
  11. C***CATEGORY I1A2, I1A1B
  12. C***TYPE DOUBLE PRECISION (SDRIV2-S, DDRIV2-D, CDRIV2-C)
  13. C***KEYWORDS DOUBLE PRECISION, GEAR'S METHOD, INITIAL VALUE PROBLEMS,
  14. C ODE, ORDINARY DIFFERENTIAL EQUATIONS, SDRIVE, STIFF
  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 I. PARAMETERS .....................................................
  25. C
  26. C (REMEMBER--To run DDRIV2 correctly in double precision, ALL
  27. C non-integer arguments in the call sequence, including
  28. C arrays, MUST be declared double precision.)
  29. C
  30. C The user should use parameter names in the call sequence of DDRIV2
  31. C for those quantities whose value may be altered by DDRIV2. The
  32. C parameters in the call sequence are:
  33. C
  34. C N = (Input) The number of differential equations.
  35. C
  36. C T = The independent variable. On input for the first call, T
  37. C is the initial point. On output, T is the point at which
  38. C the solution is given.
  39. C
  40. C Y = The vector of dependent variables. Y is used as input on
  41. C the first call, to set the initial values. On output, Y
  42. C is the computed solution vector. This array Y is passed
  43. C in the call sequence of the user-provided routines F and
  44. C G. Thus parameters required by F and G can be stored in
  45. C this array in components N+1 and above. (Note: Changes
  46. C by the user to the first N components of this array will
  47. C take effect only after a restart, i.e., after setting
  48. C MSTATE to +1(-1).)
  49. C
  50. C F = A subroutine supplied by the user. The name must be
  51. C declared EXTERNAL in the user's calling program. This
  52. C subroutine is of the form:
  53. C SUBROUTINE F (N, T, Y, YDOT)
  54. C DOUBLE PRECISION Y(*), YDOT(*)
  55. C .
  56. C .
  57. C YDOT(1) = ...
  58. C .
  59. C .
  60. C YDOT(N) = ...
  61. C END (Sample)
  62. C This computes YDOT = F(Y,T), the right hand side of the
  63. C differential equations. Here Y is a vector of length at
  64. C least N. The actual length of Y is determined by the
  65. C user's declaration in the program which calls DDRIV2.
  66. C Thus the dimensioning of Y in F, while required by FORTRAN
  67. C convention, does not actually allocate any storage. When
  68. C this subroutine is called, the first N components of Y are
  69. C intermediate approximations to the solution components.
  70. C The user should not alter these values. Here YDOT is a
  71. C vector of length N. The user should only compute YDOT(I)
  72. C for I from 1 to N. Normally a return from F passes
  73. C control back to DDRIV2. However, if the user would like
  74. C to abort the calculation, i.e., return control to the
  75. C program which calls DDRIV2, he should set N to zero.
  76. C DDRIV2 will signal this by returning a value of MSTATE
  77. C equal to +6(-6). Altering the value of N in F has no
  78. C effect on the value of N in the call sequence of DDRIV2.
  79. C
  80. C TOUT = (Input) The point at which the solution is desired.
  81. C
  82. C MSTATE = An integer describing the status of integration. The user
  83. C must initialize MSTATE to +1 or -1. If MSTATE is
  84. C positive, the routine will integrate past TOUT and
  85. C interpolate the solution. This is the most efficient
  86. C mode. If MSTATE is negative, the routine will adjust its
  87. C internal step to reach TOUT exactly (useful if a
  88. C singularity exists beyond TOUT.) The meaning of the
  89. C magnitude of MSTATE:
  90. C 1 (Input) Means the first call to the routine. This
  91. C value must be set by the user. On all subsequent
  92. C calls the value of MSTATE should be tested by the
  93. C user. Unless DDRIV2 is to be reinitialized, only the
  94. C sign of MSTATE may be changed by the user. (As a
  95. C convenience to the user who may wish to put out the
  96. C initial conditions, DDRIV2 can be called with
  97. C MSTATE=+1(-1), and TOUT=T. In this case the program
  98. C will return with MSTATE unchanged, i.e.,
  99. C MSTATE=+1(-1).)
  100. C 2 (Output) Means a successful integration. If a normal
  101. C continuation is desired (i.e., a further integration
  102. C in the same direction), simply advance TOUT and call
  103. C again. All other parameters are automatically set.
  104. C 3 (Output)(Unsuccessful) Means the integrator has taken
  105. C 1000 steps without reaching TOUT. The user can
  106. C continue the integration by simply calling DDRIV2
  107. C again. Other than an error in problem setup, the
  108. C most likely cause for this condition is trying to
  109. C integrate a stiff set of equations with the non-stiff
  110. C integrator option. (See description of MINT below.)
  111. C 4 (Output)(Unsuccessful) Means too much accuracy has
  112. C been requested. EPS has been increased to a value
  113. C the program estimates is appropriate. The user can
  114. C continue the integration by simply calling DDRIV2
  115. C again.
  116. C 5 (Output) A root was found at a point less than TOUT.
  117. C The user can continue the integration toward TOUT by
  118. C simply calling DDRIV2 again.
  119. C 6 (Output)(Unsuccessful) N has been set to zero in
  120. C SUBROUTINE F.
  121. C 7 (Output)(Unsuccessful) N has been set to zero in
  122. C FUNCTION G. See description of G below.
  123. C 8 (Output)(Successful) For MSTATE negative, T is beyond
  124. C TOUT. The solution was obtained by interpolation.
  125. C The user can continue the integration by simply
  126. C advancing TOUT and calling DDRIV2 again.
  127. C 9 (Output)(Unsuccessful) The solution could not be
  128. C obtained. The value of IERFLG (see description
  129. C below) for a "Recoverable" situation indicates the
  130. C type of difficulty encountered: either an illegal
  131. C value for a parameter or an inability to continue the
  132. C solution. For this condition the user should take
  133. C corrective action and reset MSTATE to +1(-1) before
  134. C calling DDRIV2 again. Otherwise the program will
  135. C terminate the run.
  136. C
  137. C NROOT = (Input) The number of equations whose roots are desired.
  138. C If NROOT is zero, the root search is not active. This
  139. C option is useful for obtaining output at points which are
  140. C not known in advance, but depend upon the solution, e.g.,
  141. C when some solution component takes on a specified value.
  142. C The root search is carried out using the user-written
  143. C function G (see description of G below.) DDRIV2 attempts
  144. C to find the value of T at which one of the equations
  145. C changes sign. DDRIV2 can find at most one root per
  146. C equation per internal integration step, and will then
  147. C return the solution either at TOUT or at a root, whichever
  148. C occurs first in the direction of integration. The initial
  149. C point is never reported as a root. The index of the
  150. C equation whose root is being reported is stored in the
  151. C sixth element of IWORK.
  152. C NOTE: NROOT is never altered by this program.
  153. C
  154. C EPS = On input, the requested relative accuracy in all solution
  155. C components. EPS = 0 is allowed. On output, the adjusted
  156. C relative accuracy if the input value was too small. The
  157. C value of EPS should be set as large as is reasonable,
  158. C because the amount of work done by DDRIV2 increases as
  159. C EPS decreases.
  160. C
  161. C EWT = (Input) Problem zero, i.e., the smallest physically
  162. C meaningful value for the solution. This is used inter-
  163. C nally to compute an array YWT(I) = MAX(ABS(Y(I)), EWT).
  164. C One step error estimates divided by YWT(I) are kept less
  165. C than EPS. Setting EWT to zero provides pure relative
  166. C error control. However, setting EWT smaller than
  167. C necessary can adversely affect the running time.
  168. C
  169. C MINT = (Input) The integration method flag.
  170. C MINT = 1 Means the Adams methods, and is used for
  171. C non-stiff problems.
  172. C MINT = 2 Means the stiff methods of Gear (i.e., the
  173. C backward differentiation formulas), and is
  174. C used for stiff problems.
  175. C MINT = 3 Means the program dynamically selects the
  176. C Adams methods when the problem is non-stiff
  177. C and the Gear methods when the problem is
  178. C stiff.
  179. C MINT may not be changed without restarting, i.e., setting
  180. C the magnitude of MSTATE to 1.
  181. C
  182. C WORK
  183. C LENW = (Input)
  184. C WORK is an array of LENW double precision words used
  185. C internally for temporary storage. The user must allocate
  186. C space for this array in the calling program by a statement
  187. C such as
  188. C DOUBLE PRECISION WORK(...)
  189. C The length of WORK should be at least
  190. C 16*N + 2*NROOT + 250 if MINT is 1, or
  191. C N*N + 10*N + 2*NROOT + 250 if MINT is 2, or
  192. C N*N + 17*N + 2*NROOT + 250 if MINT is 3,
  193. C and LENW should be set to the value used. The contents of
  194. C WORK should not be disturbed between calls to DDRIV2.
  195. C
  196. C IWORK
  197. C LENIW = (Input)
  198. C IWORK is an integer array of length LENIW used internally
  199. C for temporary storage. The user must allocate space for
  200. C this array in the calling program by a statement such as
  201. C INTEGER IWORK(...)
  202. C The length of IWORK should be at least
  203. C 50 if MINT is 1, or
  204. C N+50 if MINT is 2 or 3,
  205. C and LENIW should be set to the value used. The contents
  206. C of IWORK should not be disturbed between calls to DDRIV2.
  207. C
  208. C G = A double precision FORTRAN function supplied by the user
  209. C if NROOT is not 0. In this case, the name must be
  210. C declared EXTERNAL in the user's calling program. G is
  211. C repeatedly called with different values of IROOT to
  212. C obtain the value of each of the NROOT equations for which
  213. C a root is desired. G is of the form:
  214. C DOUBLE PRECISION FUNCTION G (N, T, Y, IROOT)
  215. C DOUBLE PRECISION Y(*)
  216. C GO TO (10, ...), IROOT
  217. C 10 G = ...
  218. C .
  219. C .
  220. C END (Sample)
  221. C Here, Y is a vector of length at least N, whose first N
  222. C components are the solution components at the point T.
  223. C The user should not alter these values. The actual length
  224. C of Y is determined by the user's declaration in the
  225. C program which calls DDRIV2. Thus the dimensioning of Y in
  226. C G, while required by FORTRAN convention, does not actually
  227. C allocate any storage. Normally a return from G passes
  228. C control back to DDRIV2. However, if the user would like
  229. C to abort the calculation, i.e., return control to the
  230. C program which calls DDRIV2, he should set N to zero.
  231. C DDRIV2 will signal this by returning a value of MSTATE
  232. C equal to +7(-7). In this case, the index of the equation
  233. C being evaluated is stored in the sixth element of IWORK.
  234. C Altering the value of N in G has no effect on the value of
  235. C N in the call sequence of DDRIV2.
  236. C
  237. C IERFLG = An error flag. The error number associated with a
  238. C diagnostic message (see Section II-A below) is the same as
  239. C the corresponding value of IERFLG. The meaning of IERFLG:
  240. C 0 The routine completed successfully. (No message is
  241. C issued.)
  242. C 3 (Warning) The number of steps required to reach TOUT
  243. C exceeds MXSTEP.
  244. C 4 (Warning) The value of EPS is too small.
  245. C 11 (Warning) For MSTATE negative, T is beyond TOUT.
  246. C The solution was obtained by interpolation.
  247. C 15 (Warning) The integration step size is below the
  248. C roundoff level of T. (The program issues this
  249. C message as a warning but does not return control to
  250. C the user.)
  251. C 22 (Recoverable) N is not positive.
  252. C 23 (Recoverable) MINT is less than 1 or greater than 3 .
  253. C 26 (Recoverable) The magnitude of MSTATE is either 0 or
  254. C greater than 9 .
  255. C 27 (Recoverable) EPS is less than zero.
  256. C 32 (Recoverable) Insufficient storage has been allocated
  257. C for the WORK array.
  258. C 33 (Recoverable) Insufficient storage has been allocated
  259. C for the IWORK array.
  260. C 41 (Recoverable) The integration step size has gone
  261. C to zero.
  262. C 42 (Recoverable) The integration step size has been
  263. C reduced about 50 times without advancing the
  264. C solution. The problem setup may not be correct.
  265. C 999 (Fatal) The magnitude of MSTATE is 9 .
  266. C
  267. C II. OTHER COMMUNICATION TO THE USER ...............................
  268. C
  269. C A. The solver communicates to the user through the parameters
  270. C above. In addition it writes diagnostic messages through the
  271. C standard error handling program XERMSG. A complete description
  272. C of XERMSG is given in "Guide to the SLATEC Common Mathematical
  273. C Library" by Kirby W. Fong et al.. At installations which do not
  274. C have this error handling package the short but serviceable
  275. C routine, XERMSG, available with this package, can be used. That
  276. C program uses the file named OUTPUT to transmit messages.
  277. C
  278. C B. The first three elements of WORK and the first five elements of
  279. C IWORK will contain the following statistical data:
  280. C AVGH The average step size used.
  281. C HUSED The step size last used (successfully).
  282. C AVGORD The average order used.
  283. C IMXERR The index of the element of the solution vector that
  284. C contributed most to the last error test.
  285. C NQUSED The order last used (successfully).
  286. C NSTEP The number of steps taken since last initialization.
  287. C NFE The number of evaluations of the right hand side.
  288. C NJE The number of evaluations of the Jacobian matrix.
  289. C
  290. C III. REMARKS ......................................................
  291. C
  292. C A. On any return from DDRIV2 all information necessary to continue
  293. C the calculation is contained in the call sequence parameters,
  294. C including the work arrays. Thus it is possible to suspend one
  295. C problem, integrate another, and then return to the first.
  296. C
  297. C B. If this package is to be used in an overlay situation, the user
  298. C must declare in the primary overlay the variables in the call
  299. C sequence to DDRIV2.
  300. C
  301. C C. When the routine G is not required, difficulties associated with
  302. C an unsatisfied external can be avoided by using the name of the
  303. C routine which calculates the right hand side of the differential
  304. C equations in place of G in the call sequence of DDRIV2.
  305. C
  306. C IV. USAGE .........................................................
  307. C
  308. C PROGRAM SAMPLE
  309. C EXTERNAL F
  310. C PARAMETER(MINT = 1, NROOT = 0, N = ...,
  311. C 8 LENW = 16*N + 2*NROOT + 250, LENIW = 50)
  312. C C N is the number of equations
  313. C DOUBLE PRECISION EPS, EWT, T, TOUT, WORK(LENW), Y(N)
  314. C INTEGER IWORK(LENIW)
  315. C OPEN(FILE='TAPE6', UNIT=6, STATUS='NEW')
  316. C C Initial point
  317. C T = 0.
  318. C C Set initial conditions
  319. C DO 10 I = 1,N
  320. C 10 Y(I) = ...
  321. C TOUT = T
  322. C EWT = ...
  323. C MSTATE = 1
  324. C EPS = ...
  325. C 20 CALL DDRIV2 (N, T, Y, F, TOUT, MSTATE, NROOT, EPS, EWT,
  326. C 8 MINT, WORK, LENW, IWORK, LENIW, F, IERFLG)
  327. C C Next to last argument is not
  328. C C F if rootfinding is used.
  329. C IF (MSTATE .GT. 2) STOP
  330. C WRITE(6, 100) TOUT, (Y(I), I=1,N)
  331. C TOUT = TOUT + 1.
  332. C IF (TOUT .LE. 10.) GO TO 20
  333. C 100 FORMAT(...)
  334. C END (Sample)
  335. C
  336. C***REFERENCES C. W. Gear, Numerical Initial Value Problems in
  337. C Ordinary Differential Equations, Prentice-Hall, 1971.
  338. C***ROUTINES CALLED DDRIV3, XERMSG
  339. C***REVISION HISTORY (YYMMDD)
  340. C 790601 DATE WRITTEN
  341. C 900329 Initial submission to SLATEC.
  342. C***END PROLOGUE DDRIV2
  343. EXTERNAL F, G
  344. DOUBLE PRECISION EPS, EWT, EWTCOM(1), G, HMAX, T, TOUT,
  345. 8 WORK(*), Y(*)
  346. INTEGER IWORK(*)
  347. INTEGER IERFLG, IERROR, IMPL, LENIW, LENW, MINT, MITER, ML,
  348. 8 MSTATE, MU, MXORD, MXSTEP, N, NDE, NROOT, NSTATE, NTASK
  349. CHARACTER INTGR1*8
  350. PARAMETER(IMPL = 0, MXSTEP = 1000)
  351. C***FIRST EXECUTABLE STATEMENT DDRIV2
  352. IF (ABS(MSTATE) .EQ. 9) THEN
  353. IERFLG = 999
  354. CALL XERMSG('SLATEC', 'DDRIV2',
  355. 8 'Illegal input. The magnitude of MSTATE IS 9 .',
  356. 8 IERFLG, 2)
  357. RETURN
  358. ELSE IF (ABS(MSTATE) .EQ. 0 .OR. ABS(MSTATE) .GT. 9) THEN
  359. WRITE(INTGR1, '(I8)') MSTATE
  360. IERFLG = 26
  361. CALL XERMSG('SLATEC', 'DDRIV2',
  362. 8 'Illegal input. The magnitude of MSTATE, '//INTGR1//
  363. 8 ' is not in the range 1 to 8 .', IERFLG, 1)
  364. MSTATE = SIGN(9, MSTATE)
  365. RETURN
  366. END IF
  367. IF (MINT .LT. 1 .OR. MINT .GT. 3) THEN
  368. WRITE(INTGR1, '(I8)') MINT
  369. IERFLG = 23
  370. CALL XERMSG('SLATEC', 'DDRIV2',
  371. 8 'Illegal input. Improper value for the integration method '//
  372. 8 'flag, '//INTGR1//' .', IERFLG, 1)
  373. MSTATE = SIGN(9, MSTATE)
  374. RETURN
  375. END IF
  376. IF (MSTATE .GE. 0) THEN
  377. NSTATE = MSTATE
  378. NTASK = 1
  379. ELSE
  380. NSTATE = - MSTATE
  381. NTASK = 3
  382. END IF
  383. EWTCOM(1) = EWT
  384. IF (EWT .NE. 0.D0) THEN
  385. IERROR = 3
  386. ELSE
  387. IERROR = 2
  388. END IF
  389. IF (MINT .EQ. 1) THEN
  390. MITER = 0
  391. MXORD = 12
  392. ELSE IF (MINT .EQ. 2) THEN
  393. MITER = 2
  394. MXORD = 5
  395. ELSE IF (MINT .EQ. 3) THEN
  396. MITER = 2
  397. MXORD = 12
  398. END IF
  399. HMAX = 2.D0*ABS(TOUT - T)
  400. CALL DDRIV3 (N, T, Y, F, NSTATE, TOUT, NTASK, NROOT, EPS, EWTCOM,
  401. 8 IERROR, MINT, MITER, IMPL, ML, MU, MXORD, HMAX, WORK,
  402. 8 LENW, IWORK, LENIW, F, F, NDE, MXSTEP, G, F, IERFLG)
  403. IF (NSTATE .LE. 7) THEN
  404. MSTATE = SIGN(NSTATE, MSTATE)
  405. ELSE IF (NSTATE .EQ. 11) THEN
  406. MSTATE = SIGN(8, MSTATE)
  407. ELSE IF (NSTATE .GT. 11) THEN
  408. MSTATE = SIGN(9, MSTATE)
  409. END IF
  410. RETURN
  411. END