GNU Octave 7.1.0
A high-level interpreted language, primarily intended for numerical computations, mostly compatible with Matlab
slsode.f
Go to the documentation of this file.
1 SUBROUTINE slsode (F, NEQ, Y, T, TOUT, ITOL, RTOL, ATOL, ITASK,
2 1 ISTATE, IOPT, RWORK, LRW, IWORK, LIW, JAC, MF)
3 EXTERNAL f, jac
4 INTEGER NEQ, ITOL, ITASK, ISTATE, IOPT, LRW, IWORK, LIW, MF
5 REAL Y, T, TOUT, RTOL, ATOL, RWORK
6 dimension neq(*), y(*), rtol(*), atol(*), rwork(lrw), iwork(liw)
7C***BEGIN PROLOGUE SLSODE
8C***PURPOSE Livermore Solver for Ordinary Differential Equations.
9C SLSODE solves the initial-value problem for stiff or
10C nonstiff systems of first-order ODE's,
11C dy/dt = f(t,y), or, in component form,
12C dy(i)/dt = f(i) = f(i,t,y(1),y(2),...,y(N)), i=1,...,N.
13C***CATEGORY I1A
14C***TYPE SINGLE PRECISION (SLSODE-S, DLSODE-D)
15C***KEYWORDS ORDINARY DIFFERENTIAL EQUATIONS, INITIAL VALUE PROBLEM,
16C STIFF, NONSTIFF
17C***AUTHOR Hindmarsh, Alan C., (LLNL)
18C Center for Applied Scientific Computing, L-561
19C Lawrence Livermore National Laboratory
20C Livermore, CA 94551.
21C***DESCRIPTION
22C
23C NOTE: The "Usage" and "Arguments" sections treat only a subset of
24C available options, in condensed fashion. The options
25C covered and the information supplied will support most
26C standard uses of SLSODE.
27C
28C For more sophisticated uses, full details on all options are
29C given in the concluding section, headed "Long Description."
30C A synopsis of the SLSODE Long Description is provided at the
31C beginning of that section; general topics covered are:
32C - Elements of the call sequence; optional input and output
33C - Optional supplemental routines in the SLSODE package
34C - internal COMMON block
35C
36C *Usage:
37C Communication between the user and the SLSODE package, for normal
38C situations, is summarized here. This summary describes a subset
39C of the available options. See "Long Description" for complete
40C details, including optional communication, nonstandard options,
41C and instructions for special situations.
42C
43C A sample program is given in the "Examples" section.
44C
45C Refer to the argument descriptions for the definitions of the
46C quantities that appear in the following sample declarations.
47C
48C For MF = 10,
49C PARAMETER (LRW = 20 + 16*NEQ, LIW = 20)
50C For MF = 21 or 22,
51C PARAMETER (LRW = 22 + 9*NEQ + NEQ**2, LIW = 20 + NEQ)
52C For MF = 24 or 25,
53C PARAMETER (LRW = 22 + 10*NEQ + (2*ML+MU)*NEQ,
54C * LIW = 20 + NEQ)
55C
56C EXTERNAL F, JAC
57C INTEGER NEQ, ITOL, ITASK, ISTATE, IOPT, LRW, IWORK(LIW),
58C * LIW, MF
59C REAL Y(NEQ), T, TOUT, RTOL, ATOL(ntol), RWORK(LRW)
60C
61C CALL SLSODE (F, NEQ, Y, T, TOUT, ITOL, RTOL, ATOL, ITASK,
62C * ISTATE, IOPT, RWORK, LRW, IWORK, LIW, JAC, MF)
63C
64C *Arguments:
65C F :EXT Name of subroutine for right-hand-side vector f.
66C This name must be declared EXTERNAL in calling
67C program. The form of F must be:
68C
69C SUBROUTINE F (NEQ, T, Y, YDOT)
70C INTEGER NEQ
71C REAL T, Y(*), YDOT(*)
72C
73C The inputs are NEQ, T, Y. F is to set
74C
75C YDOT(i) = f(i,T,Y(1),Y(2),...,Y(NEQ)),
76C i = 1, ..., NEQ .
77C
78C NEQ :IN Number of first-order ODE's.
79C
80C Y :INOUT Array of values of the y(t) vector, of length NEQ.
81C Input: For the first call, Y should contain the
82C values of y(t) at t = T. (Y is an input
83C variable only if ISTATE = 1.)
84C Output: On return, Y will contain the values at the
85C new t-value.
86C
87C T :INOUT Value of the independent variable. On return it
88C will be the current value of t (normally TOUT).
89C
90C TOUT :IN Next point where output is desired (.NE. T).
91C
92C ITOL :IN 1 or 2 according as ATOL (below) is a scalar or
93C an array.
94C
95C RTOL :IN Relative tolerance parameter (scalar).
96C
97C ATOL :IN Absolute tolerance parameter (scalar or array).
98C If ITOL = 1, ATOL need not be dimensioned.
99C If ITOL = 2, ATOL must be dimensioned at least NEQ.
100C
101C The estimated local error in Y(i) will be controlled
102C so as to be roughly less (in magnitude) than
103C
104C EWT(i) = RTOL*ABS(Y(i)) + ATOL if ITOL = 1, or
105C EWT(i) = RTOL*ABS(Y(i)) + ATOL(i) if ITOL = 2.
106C
107C Thus the local error test passes if, in each
108C component, either the absolute error is less than
109C ATOL (or ATOL(i)), or the relative error is less
110C than RTOL.
111C
112C Use RTOL = 0.0 for pure absolute error control, and
113C use ATOL = 0.0 (or ATOL(i) = 0.0) for pure relative
114C error control. Caution: Actual (global) errors may
115C exceed these local tolerances, so choose them
116C conservatively.
117C
118C ITASK :IN Flag indicating the task SLSODE is to perform.
119C Use ITASK = 1 for normal computation of output
120C values of y at t = TOUT.
121C
122C ISTATE:INOUT Index used for input and output to specify the state
123C of the calculation.
124C Input:
125C 1 This is the first call for a problem.
126C 2 This is a subsequent call.
127C Output:
128C 1 Nothing was done, as TOUT was equal to T.
129C 2 SLSODE was successful (otherwise, negative).
130C Note that ISTATE need not be modified after a
131C successful return.
132C -1 Excess work done on this call (perhaps wrong
133C MF).
134C -2 Excess accuracy requested (tolerances too
135C small).
136C -3 Illegal input detected (see printed message).
137C -4 Repeated error test failures (check all
138C inputs).
139C -5 Repeated convergence failures (perhaps bad
140C Jacobian supplied or wrong choice of MF or
141C tolerances).
142C -6 Error weight became zero during problem
143C (solution component i vanished, and ATOL or
144C ATOL(i) = 0.).
145C
146C IOPT :IN Flag indicating whether optional inputs are used:
147C 0 No.
148C 1 Yes. (See "Optional inputs" under "Long
149C Description," Part 1.)
150C
151C RWORK :WORK Real work array of length at least:
152C 20 + 16*NEQ for MF = 10,
153C 22 + 9*NEQ + NEQ**2 for MF = 21 or 22,
154C 22 + 10*NEQ + (2*ML + MU)*NEQ for MF = 24 or 25.
155C
156C LRW :IN Declared length of RWORK (in user's DIMENSION
157C statement).
158C
159C IWORK :WORK Integer work array of length at least:
160C 20 for MF = 10,
161C 20 + NEQ for MF = 21, 22, 24, or 25.
162C
163C If MF = 24 or 25, input in IWORK(1),IWORK(2) the
164C lower and upper Jacobian half-bandwidths ML,MU.
165C
166C On return, IWORK contains information that may be
167C of interest to the user:
168C
169C Name Location Meaning
170C ----- --------- -----------------------------------------
171C NST IWORK(11) Number of steps taken for the problem so
172C far.
173C NFE IWORK(12) Number of f evaluations for the problem
174C so far.
175C NJE IWORK(13) Number of Jacobian evaluations (and of
176C matrix LU decompositions) for the problem
177C so far.
178C NQU IWORK(14) Method order last used (successfully).
179C LENRW IWORK(17) Length of RWORK actually required. This
180C is defined on normal returns and on an
181C illegal input return for insufficient
182C storage.
183C LENIW IWORK(18) Length of IWORK actually required. This
184C is defined on normal returns and on an
185C illegal input return for insufficient
186C storage.
187C
188C LIW :IN Declared length of IWORK (in user's DIMENSION
189C statement).
190C
191C JAC :EXT Name of subroutine for Jacobian matrix (MF =
192C 21 or 24). If used, this name must be declared
193C EXTERNAL in calling program. If not used, pass a
194C dummy name. The form of JAC must be:
195C
196C SUBROUTINE JAC (NEQ, T, Y, ML, MU, PD, NROWPD)
197C INTEGER NEQ, ML, MU, NROWPD
198C REAL T, Y(*), PD(NROWPD,*)
199C
200C See item c, under "Description" below for more
201C information about JAC.
202C
203C MF :IN Method flag. Standard values are:
204C 10 Nonstiff (Adams) method, no Jacobian used.
205C 21 Stiff (BDF) method, user-supplied full Jacobian.
206C 22 Stiff method, internally generated full
207C Jacobian.
208C 24 Stiff method, user-supplied banded Jacobian.
209C 25 Stiff method, internally generated banded
210C Jacobian.
211C
212C *Description:
213C SLSODE solves the initial value problem for stiff or nonstiff
214C systems of first-order ODE's,
215C
216C dy/dt = f(t,y) ,
217C
218C or, in component form,
219C
220C dy(i)/dt = f(i) = f(i,t,y(1),y(2),...,y(NEQ))
221C (i = 1, ..., NEQ) .
222C
223C SLSODE is a package based on the GEAR and GEARB packages, and on
224C the October 23, 1978, version of the tentative ODEPACK user
225C interface standard, with minor modifications.
226C
227C The steps in solving such a problem are as follows.
228C
229C a. First write a subroutine of the form
230C
231C SUBROUTINE F (NEQ, T, Y, YDOT)
232C INTEGER NEQ
233C REAL T, Y(*), YDOT(*)
234C
235C which supplies the vector function f by loading YDOT(i) with
236C f(i).
237C
238C b. Next determine (or guess) whether or not the problem is stiff.
239C Stiffness occurs when the Jacobian matrix df/dy has an
240C eigenvalue whose real part is negative and large in magnitude
241C compared to the reciprocal of the t span of interest. If the
242C problem is nonstiff, use method flag MF = 10. If it is stiff,
243C there are four standard choices for MF, and SLSODE requires the
244C Jacobian matrix in some form. This matrix is regarded either
245C as full (MF = 21 or 22), or banded (MF = 24 or 25). In the
246C banded case, SLSODE requires two half-bandwidth parameters ML
247C and MU. These are, respectively, the widths of the lower and
248C upper parts of the band, excluding the main diagonal. Thus the
249C band consists of the locations (i,j) with
250C
251C i - ML <= j <= i + MU ,
252C
253C and the full bandwidth is ML + MU + 1 .
254C
255C c. If the problem is stiff, you are encouraged to supply the
256C Jacobian directly (MF = 21 or 24), but if this is not feasible,
257C SLSODE will compute it internally by difference quotients (MF =
258C 22 or 25). If you are supplying the Jacobian, write a
259C subroutine of the form
260C
261C SUBROUTINE JAC (NEQ, T, Y, ML, MU, PD, NROWPD)
262C INTEGER NEQ, ML, MU, NRWOPD
263C REAL T, Y(*), PD(NROWPD,*)
264C
265C which provides df/dy by loading PD as follows:
266C - For a full Jacobian (MF = 21), load PD(i,j) with df(i)/dy(j),
267C the partial derivative of f(i) with respect to y(j). (Ignore
268C the ML and MU arguments in this case.)
269C - For a banded Jacobian (MF = 24), load PD(i-j+MU+1,j) with
270C df(i)/dy(j); i.e., load the diagonal lines of df/dy into the
271C rows of PD from the top down.
272C - In either case, only nonzero elements need be loaded.
273C
274C d. Write a main program that calls subroutine SLSODE once for each
275C point at which answers are desired. This should also provide
276C for possible use of logical unit 6 for output of error messages
277C by SLSODE.
278C
279C Before the first call to SLSODE, set ISTATE = 1, set Y and T to
280C the initial values, and set TOUT to the first output point. To
281C continue the integration after a successful return, simply
282C reset TOUT and call SLSODE again. No other parameters need be
283C reset.
284C
285C *Examples:
286C The following is a simple example problem, with the coding needed
287C for its solution by SLSODE. The problem is from chemical kinetics,
288C and consists of the following three rate equations:
289C
290C dy1/dt = -.04*y1 + 1.E4*y2*y3
291C dy2/dt = .04*y1 - 1.E4*y2*y3 - 3.E7*y2**2
292C dy3/dt = 3.E7*y2**2
293C
294C on the interval from t = 0.0 to t = 4.E10, with initial conditions
295C y1 = 1.0, y2 = y3 = 0. The problem is stiff.
296C
297C The following coding solves this problem with SLSODE, using
298C MF = 21 and printing results at t = .4, 4., ..., 4.E10. It uses
299C ITOL = 2 and ATOL much smaller for y2 than for y1 or y3 because y2
300C has much smaller values. At the end of the run, statistical
301C quantities of interest are printed.
302C
303C EXTERNAL FEX, JEX
304C INTEGER IOPT, IOUT, ISTATE, ITASK, ITOL, IWORK(23), LIW, LRW,
305C * MF, NEQ
306C REAL ATOL(3), RTOL, RWORK(58), T, TOUT, Y(3)
307C NEQ = 3
308C Y(1) = 1.
309C Y(2) = 0.
310C Y(3) = 0.
311C T = 0.
312C TOUT = .4
313C ITOL = 2
314C RTOL = 1.E-4
315C ATOL(1) = 1.E-6
316C ATOL(2) = 1.E-10
317C ATOL(3) = 1.E-6
318C ITASK = 1
319C ISTATE = 1
320C IOPT = 0
321C LRW = 58
322C LIW = 23
323C MF = 21
324C DO 40 IOUT = 1,12
325C CALL SLSODE (FEX, NEQ, Y, T, TOUT, ITOL, RTOL, ATOL, ITASK,
326C * ISTATE, IOPT, RWORK, LRW, IWORK, LIW, JEX, MF)
327C WRITE(6,20) T, Y(1), Y(2), Y(3)
328C 20 FORMAT(' At t =',E12.4,' y =',3E14.6)
329C IF (ISTATE .LT. 0) GO TO 80
330C 40 TOUT = TOUT*10.
331C WRITE(6,60) IWORK(11), IWORK(12), IWORK(13)
332C 60 FORMAT(/' No. steps =',i4,', No. f-s =',i4,', No. J-s =',i4)
333C STOP
334C 80 WRITE(6,90) ISTATE
335C 90 FORMAT(///' Error halt.. ISTATE =',I3)
336C STOP
337C END
338C
339C SUBROUTINE FEX (NEQ, T, Y, YDOT)
340C INTEGER NEQ
341C REAL T, Y(3), YDOT(3)
342C YDOT(1) = -.04*Y(1) + 1.E4*Y(2)*Y(3)
343C YDOT(3) = 3.E7*Y(2)*Y(2)
344C YDOT(2) = -YDOT(1) - YDOT(3)
345C RETURN
346C END
347C
348C SUBROUTINE JEX (NEQ, T, Y, ML, MU, PD, NRPD)
349C INTEGER NEQ, ML, MU, NRPD
350C REAL T, Y(3), PD(NRPD,3)
351C PD(1,1) = -.04
352C PD(1,2) = 1.E4*Y(3)
353C PD(1,3) = 1.E4*Y(2)
354C PD(2,1) = .04
355C PD(2,3) = -PD(1,3)
356C PD(3,2) = 6.E7*Y(2)
357C PD(2,2) = -PD(1,2) - PD(3,2)
358C RETURN
359C END
360C
361C The output from this program (on a Cray-1 in single precision)
362C is as follows.
363C
364C At t = 4.0000e-01 y = 9.851726e-01 3.386406e-05 1.479357e-02
365C At t = 4.0000e+00 y = 9.055142e-01 2.240418e-05 9.446344e-02
366C At t = 4.0000e+01 y = 7.158050e-01 9.184616e-06 2.841858e-01
367C At t = 4.0000e+02 y = 4.504846e-01 3.222434e-06 5.495122e-01
368C At t = 4.0000e+03 y = 1.831701e-01 8.940379e-07 8.168290e-01
369C At t = 4.0000e+04 y = 3.897016e-02 1.621193e-07 9.610297e-01
370C At t = 4.0000e+05 y = 4.935213e-03 1.983756e-08 9.950648e-01
371C At t = 4.0000e+06 y = 5.159269e-04 2.064759e-09 9.994841e-01
372C At t = 4.0000e+07 y = 5.306413e-05 2.122677e-10 9.999469e-01
373C At t = 4.0000e+08 y = 5.494530e-06 2.197825e-11 9.999945e-01
374C At t = 4.0000e+09 y = 5.129458e-07 2.051784e-12 9.999995e-01
375C At t = 4.0000e+10 y = -7.170603e-08 -2.868241e-13 1.000000e+00
376C
377C No. steps = 330, No. f-s = 405, No. J-s = 69
378C
379C *Accuracy:
380C The accuracy of the solution depends on the choice of tolerances
381C RTOL and ATOL. Actual (global) errors may exceed these local
382C tolerances, so choose them conservatively.
383C
384C *Cautions:
385C The work arrays should not be altered between calls to SLSODE for
386C the same problem, except possibly for the conditional and optional
387C inputs.
388C
389C *Portability:
390C Since NEQ is dimensioned inside SLSODE, some compilers may object
391C to a call to SLSODE with NEQ a scalar variable. In this event,
392C use DIMENSION NEQ(1). Similar remarks apply to RTOL and ATOL.
393C
394C Note to Cray users:
395C For maximum efficiency, use the CFT77 compiler. Appropriate
396C compiler optimization directives have been inserted for CFT77.
397C
398C *Reference:
399C Alan C. Hindmarsh, "ODEPACK, A Systematized Collection of ODE
400C Solvers," in Scientific Computing, R. S. Stepleman, et al., Eds.
401C (North-Holland, Amsterdam, 1983), pp. 55-64.
402C
403C *Long Description:
404C The following complete description of the user interface to
405C SLSODE consists of four parts:
406C
407C 1. The call sequence to subroutine SLSODE, which is a driver
408C routine for the solver. This includes descriptions of both
409C the call sequence arguments and user-supplied routines.
410C Following these descriptions is a description of optional
411C inputs available through the call sequence, and then a
412C description of optional outputs in the work arrays.
413C
414C 2. Descriptions of other routines in the SLSODE package that may
415C be (optionally) called by the user. These provide the ability
416C to alter error message handling, save and restore the internal
417C COMMON, and obtain specified derivatives of the solution y(t).
418C
419C 3. Descriptions of COMMON block to be declared in overlay or
420C similar environments, or to be saved when doing an interrupt
421C of the problem and continued solution later.
422C
423C 4. Description of two routines in the SLSODE package, either of
424C which the user may replace with his own version, if desired.
425C These relate to the measurement of errors.
426C
427C
428C Part 1. Call Sequence
429C ----------------------
430C
431C Arguments
432C ---------
433C The call sequence parameters used for input only are
434C
435C F, NEQ, TOUT, ITOL, RTOL, ATOL, ITASK, IOPT, LRW, LIW, JAC, MF,
436C
437C and those used for both input and output are
438C
439C Y, T, ISTATE.
440C
441C The work arrays RWORK and IWORK are also used for conditional and
442C optional inputs and optional outputs. (The term output here
443C refers to the return from subroutine SLSODE to the user's calling
444C program.)
445C
446C The legality of input parameters will be thoroughly checked on the
447C initial call for the problem, but not checked thereafter unless a
448C change in input parameters is flagged by ISTATE = 3 on input.
449C
450C The descriptions of the call arguments are as follows.
451C
452C F The name of the user-supplied subroutine defining the ODE
453C system. The system must be put in the first-order form
454C dy/dt = f(t,y), where f is a vector-valued function of
455C the scalar t and the vector y. Subroutine F is to compute
456C the function f. It is to have the form
457C
458C SUBROUTINE F (NEQ, T, Y, YDOT)
459C REAL T, Y(*), YDOT(*)
460C
461C where NEQ, T, and Y are input, and the array YDOT =
462C f(T,Y) is output. Y and YDOT are arrays of length NEQ.
463C Subroutine F should not alter Y(1),...,Y(NEQ). F must be
464C declared EXTERNAL in the calling program.
465C
466C Subroutine F may access user-defined quantities in
467C NEQ(2),... and/or in Y(NEQ(1)+1),..., if NEQ is an array
468C (dimensioned in F) and/or Y has length exceeding NEQ(1).
469C See the descriptions of NEQ and Y below.
470C
471C If quantities computed in the F routine are needed
472C externally to SLSODE, an extra call to F should be made
473C for this purpose, for consistent and accurate results.
474C If only the derivative dy/dt is needed, use SINTDY
475C instead.
476C
477C NEQ The size of the ODE system (number of first-order
478C ordinary differential equations). Used only for input.
479C NEQ may be decreased, but not increased, during the
480C problem. If NEQ is decreased (with ISTATE = 3 on input),
481C the remaining components of Y should be left undisturbed,
482C if these are to be accessed in F and/or JAC.
483C
484C Normally, NEQ is a scalar, and it is generally referred
485C to as a scalar in this user interface description.
486C However, NEQ may be an array, with NEQ(1) set to the
487C system size. (The SLSODE package accesses only NEQ(1).)
488C In either case, this parameter is passed as the NEQ
489C argument in all calls to F and JAC. Hence, if it is an
490C array, locations NEQ(2),... may be used to store other
491C integer data and pass it to F and/or JAC. Subroutines
492C F and/or JAC must include NEQ in a DIMENSION statement
493C in that case.
494C
495C Y A real array for the vector of dependent variables, of
496C length NEQ or more. Used for both input and output on
497C the first call (ISTATE = 1), and only for output on
498C other calls. On the first call, Y must contain the
499C vector of initial values. On output, Y contains the
500C computed solution vector, evaluated at T. If desired,
501C the Y array may be used for other purposes between
502C calls to the solver.
503C
504C This array is passed as the Y argument in all calls to F
505C and JAC. Hence its length may exceed NEQ, and locations
506C Y(NEQ+1),... may be used to store other real data and
507C pass it to F and/or JAC. (The SLSODE package accesses
508C only Y(1),...,Y(NEQ).)
509C
510C T The independent variable. On input, T is used only on
511C the first call, as the initial point of the integration.
512C On output, after each call, T is the value at which a
513C computed solution Y is evaluated (usually the same as
514C TOUT). On an error return, T is the farthest point
515C reached.
516C
517C TOUT The next value of T at which a computed solution is
518C desired. Used only for input.
519C
520C When starting the problem (ISTATE = 1), TOUT may be equal
521C to T for one call, then should not equal T for the next
522C call. For the initial T, an input value of TOUT .NE. T
523C is used in order to determine the direction of the
524C integration (i.e., the algebraic sign of the step sizes)
525C and the rough scale of the problem. Integration in
526C either direction (forward or backward in T) is permitted.
527C
528C If ITASK = 2 or 5 (one-step modes), TOUT is ignored
529C after the first call (i.e., the first call with
530C TOUT .NE. T). Otherwise, TOUT is required on every call.
531C
532C If ITASK = 1, 3, or 4, the values of TOUT need not be
533C monotone, but a value of TOUT which backs up is limited
534C to the current internal T interval, whose endpoints are
535C TCUR - HU and TCUR. (See "Optional Outputs" below for
536C TCUR and HU.)
537C
538C
539C ITOL An indicator for the type of error control. See
540C description below under ATOL. Used only for input.
541C
542C RTOL A relative error tolerance parameter, either a scalar or
543C an array of length NEQ. See description below under
544C ATOL. Input only.
545C
546C ATOL An absolute error tolerance parameter, either a scalar or
547C an array of length NEQ. Input only.
548C
549C The input parameters ITOL, RTOL, and ATOL determine the
550C error control performed by the solver. The solver will
551C control the vector e = (e(i)) of estimated local errors
552C in Y, according to an inequality of the form
553C
554C rms-norm of ( e(i)/EWT(i) ) <= 1,
555C
556C where
557C
558C EWT(i) = RTOL(i)*ABS(Y(i)) + ATOL(i),
559C
560C and the rms-norm (root-mean-square norm) here is
561C
562C rms-norm(v) = SQRT(sum v(i)**2 / NEQ).
563C
564C Here EWT = (EWT(i)) is a vector of weights which must
565C always be positive, and the values of RTOL and ATOL
566C should all be nonnegative. The following table gives the
567C types (scalar/array) of RTOL and ATOL, and the
568C corresponding form of EWT(i).
569C
570C ITOL RTOL ATOL EWT(i)
571C ---- ------ ------ -----------------------------
572C 1 scalar scalar RTOL*ABS(Y(i)) + ATOL
573C 2 scalar array RTOL*ABS(Y(i)) + ATOL(i)
574C 3 array scalar RTOL(i)*ABS(Y(i)) + ATOL
575C 4 array array RTOL(i)*ABS(Y(i)) + ATOL(i)
576C
577C When either of these parameters is a scalar, it need not
578C be dimensioned in the user's calling program.
579C
580C If none of the above choices (with ITOL, RTOL, and ATOL
581C fixed throughout the problem) is suitable, more general
582C error controls can be obtained by substituting
583C user-supplied routines for the setting of EWT and/or for
584C the norm calculation. See Part 4 below.
585C
586C If global errors are to be estimated by making a repeated
587C run on the same problem with smaller tolerances, then all
588C components of RTOL and ATOL (i.e., of EWT) should be
589C scaled down uniformly.
590C
591C ITASK An index specifying the task to be performed. Input
592C only. ITASK has the following values and meanings:
593C 1 Normal computation of output values of y(t) at
594C t = TOUT (by overshooting and interpolating).
595C 2 Take one step only and return.
596C 3 Stop at the first internal mesh point at or beyond
597C t = TOUT and return.
598C 4 Normal computation of output values of y(t) at
599C t = TOUT but without overshooting t = TCRIT. TCRIT
600C must be input as RWORK(1). TCRIT may be equal to or
601C beyond TOUT, but not behind it in the direction of
602C integration. This option is useful if the problem
603C has a singularity at or beyond t = TCRIT.
604C 5 Take one step, without passing TCRIT, and return.
605C TCRIT must be input as RWORK(1).
606C
607C Note: If ITASK = 4 or 5 and the solver reaches TCRIT
608C (within roundoff), it will return T = TCRIT (exactly) to
609C indicate this (unless ITASK = 4 and TOUT comes before
610C TCRIT, in which case answers at T = TOUT are returned
611C first).
612C
613C ISTATE An index used for input and output to specify the state
614C of the calculation.
615C
616C On input, the values of ISTATE are as follows:
617C 1 This is the first call for the problem
618C (initializations will be done). See "Note" below.
619C 2 This is not the first call, and the calculation is to
620C continue normally, with no change in any input
621C parameters except possibly TOUT and ITASK. (If ITOL,
622C RTOL, and/or ATOL are changed between calls with
623C ISTATE = 2, the new values will be used but not
624C tested for legality.)
625C 3 This is not the first call, and the calculation is to
626C continue normally, but with a change in input
627C parameters other than TOUT and ITASK. Changes are
628C allowed in NEQ, ITOL, RTOL, ATOL, IOPT, LRW, LIW, MF,
629C ML, MU, and any of the optional inputs except H0.
630C (See IWORK description for ML and MU.)
631C
632C Note: A preliminary call with TOUT = T is not counted as
633C a first call here, as no initialization or checking of
634C input is done. (Such a call is sometimes useful for the
635C purpose of outputting the initial conditions.) Thus the
636C first call for which TOUT .NE. T requires ISTATE = 1 on
637C input.
638C
639C On output, ISTATE has the following values and meanings:
640C 1 Nothing was done, as TOUT was equal to T with
641C ISTATE = 1 on input.
642C 2 The integration was performed successfully.
643C -1 An excessive amount of work (more than MXSTEP steps)
644C was done on this call, before completing the
645C requested task, but the integration was otherwise
646C successful as far as T. (MXSTEP is an optional input
647C and is normally 500.) To continue, the user may
648C simply reset ISTATE to a value >1 and call again (the
649C excess work step counter will be reset to 0). In
650C addition, the user may increase MXSTEP to avoid this
651C error return; see "Optional Inputs" below.
652C -2 Too much accuracy was requested for the precision of
653C the machine being used. This was detected before
654C completing the requested task, but the integration
655C was successful as far as T. To continue, the
656C tolerance parameters must be reset, and ISTATE must
657C be set to 3. The optional output TOLSF may be used
658C for this purpose. (Note: If this condition is
659C detected before taking any steps, then an illegal
660C input return (ISTATE = -3) occurs instead.)
661C -3 Illegal input was detected, before taking any
662C integration steps. See written message for details.
663C (Note: If the solver detects an infinite loop of
664C calls to the solver with illegal input, it will cause
665C the run to stop.)
666C -4 There were repeated error-test failures on one
667C attempted step, before completing the requested task,
668C but the integration was successful as far as T. The
669C problem may have a singularity, or the input may be
670C inappropriate.
671C -5 There were repeated convergence-test failures on one
672C attempted step, before completing the requested task,
673C but the integration was successful as far as T. This
674C may be caused by an inaccurate Jacobian matrix, if
675C one is being used.
676C -6 EWT(i) became zero for some i during the integration.
677C Pure relative error control (ATOL(i)=0.0) was
678C requested on a variable which has now vanished. The
679C integration was successful as far as T.
680C
681C Note: Since the normal output value of ISTATE is 2, it
682C does not need to be reset for normal continuation. Also,
683C since a negative input value of ISTATE will be regarded
684C as illegal, a negative output value requires the user to
685C change it, and possibly other inputs, before calling the
686C solver again.
687C
688C IOPT An integer flag to specify whether any optional inputs
689C are being used on this call. Input only. The optional
690C inputs are listed under a separate heading below.
691C 0 No optional inputs are being used. Default values
692C will be used in all cases.
693C 1 One or more optional inputs are being used.
694C
695C RWORK A real working array (single precision). The length of
696C RWORK must be at least
697C
698C 20 + NYH*(MAXORD + 1) + 3*NEQ + LWM
699C
700C where
701C NYH = the initial value of NEQ,
702C MAXORD = 12 (if METH = 1) or 5 (if METH = 2) (unless a
703C smaller value is given as an optional input),
704C LWM = 0 if MITER = 0,
705C LWM = NEQ**2 + 2 if MITER = 1 or 2,
706C LWM = NEQ + 2 if MITER = 3, and
707C LWM = (2*ML + MU + 1)*NEQ + 2
708C if MITER = 4 or 5.
709C (See the MF description below for METH and MITER.)
710C
711C Thus if MAXORD has its default value and NEQ is constant,
712C this length is:
713C 20 + 16*NEQ for MF = 10,
714C 22 + 16*NEQ + NEQ**2 for MF = 11 or 12,
715C 22 + 17*NEQ for MF = 13,
716C 22 + 17*NEQ + (2*ML + MU)*NEQ for MF = 14 or 15,
717C 20 + 9*NEQ for MF = 20,
718C 22 + 9*NEQ + NEQ**2 for MF = 21 or 22,
719C 22 + 10*NEQ for MF = 23,
720C 22 + 10*NEQ + (2*ML + MU)*NEQ for MF = 24 or 25.
721C
722C The first 20 words of RWORK are reserved for conditional
723C and optional inputs and optional outputs.
724C
725C The following word in RWORK is a conditional input:
726C RWORK(1) = TCRIT, the critical value of t which the
727C solver is not to overshoot. Required if ITASK
728C is 4 or 5, and ignored otherwise. See ITASK.
729C
730C LRW The length of the array RWORK, as declared by the user.
731C (This will be checked by the solver.)
732C
733C IWORK An integer work array. Its length must be at least
734C 20 if MITER = 0 or 3 (MF = 10, 13, 20, 23), or
735C 20 + NEQ otherwise (MF = 11, 12, 14, 15, 21, 22, 24, 25).
736C (See the MF description below for MITER.) The first few
737C words of IWORK are used for conditional and optional
738C inputs and optional outputs.
739C
740C The following two words in IWORK are conditional inputs:
741C IWORK(1) = ML These are the lower and upper half-
742C IWORK(2) = MU bandwidths, respectively, of the banded
743C Jacobian, excluding the main diagonal.
744C The band is defined by the matrix locations
745C (i,j) with i - ML <= j <= i + MU. ML and MU
746C must satisfy 0 <= ML,MU <= NEQ - 1. These are
747C required if MITER is 4 or 5, and ignored
748C otherwise. ML and MU may in fact be the band
749C parameters for a matrix to which df/dy is only
750C approximately equal.
751C
752C LIW The length of the array IWORK, as declared by the user.
753C (This will be checked by the solver.)
754C
755C Note: The work arrays must not be altered between calls to SLSODE
756C for the same problem, except possibly for the conditional and
757C optional inputs, and except for the last 3*NEQ words of RWORK.
758C The latter space is used for internal scratch space, and so is
759C available for use by the user outside SLSODE between calls, if
760C desired (but not for use by F or JAC).
761C
762C JAC The name of the user-supplied routine (MITER = 1 or 4) to
763C compute the Jacobian matrix, df/dy, as a function of the
764C scalar t and the vector y. (See the MF description below
765C for MITER.) It is to have the form
766C
767C SUBROUTINE JAC (NEQ, T, Y, ML, MU, PD, NROWPD)
768C REAL T, Y(*), PD(NROWPD,*)
769C
770C where NEQ, T, Y, ML, MU, and NROWPD are input and the
771C array PD is to be loaded with partial derivatives
772C (elements of the Jacobian matrix) on output. PD must be
773C given a first dimension of NROWPD. T and Y have the same
774C meaning as in subroutine F.
775C
776C In the full matrix case (MITER = 1), ML and MU are
777C ignored, and the Jacobian is to be loaded into PD in
778C columnwise manner, with df(i)/dy(j) loaded into PD(i,j).
779C
780C In the band matrix case (MITER = 4), the elements within
781C the band are to be loaded into PD in columnwise manner,
782C with diagonal lines of df/dy loaded into the rows of PD.
783C Thus df(i)/dy(j) is to be loaded into PD(i-j+MU+1,j). ML
784C and MU are the half-bandwidth parameters (see IWORK).
785C The locations in PD in the two triangular areas which
786C correspond to nonexistent matrix elements can be ignored
787C or loaded arbitrarily, as they are overwritten by SLSODE.
788C
789C JAC need not provide df/dy exactly. A crude approximation
790C (possibly with a smaller bandwidth) will do.
791C
792C In either case, PD is preset to zero by the solver, so
793C that only the nonzero elements need be loaded by JAC.
794C Each call to JAC is preceded by a call to F with the same
795C arguments NEQ, T, and Y. Thus to gain some efficiency,
796C intermediate quantities shared by both calculations may
797C be saved in a user COMMON block by F and not recomputed
798C by JAC, if desired. Also, JAC may alter the Y array, if
799C desired. JAC must be declared EXTERNAL in the calling
800C program.
801C
802C Subroutine JAC may access user-defined quantities in
803C NEQ(2),... and/or in Y(NEQ(1)+1),... if NEQ is an array
804C (dimensioned in JAC) and/or Y has length exceeding
805C NEQ(1). See the descriptions of NEQ and Y above.
806C
807C MF The method flag. Used only for input. The legal values
808C of MF are 10, 11, 12, 13, 14, 15, 20, 21, 22, 23, 24,
809C and 25. MF has decimal digits METH and MITER:
810C MF = 10*METH + MITER .
811C
812C METH indicates the basic linear multistep method:
813C 1 Implicit Adams method.
814C 2 Method based on backward differentiation formulas
815C (BDF's).
816C
817C MITER indicates the corrector iteration method:
818C 0 Functional iteration (no Jacobian matrix is
819C involved).
820C 1 Chord iteration with a user-supplied full (NEQ by
821C NEQ) Jacobian.
822C 2 Chord iteration with an internally generated
823C (difference quotient) full Jacobian (using NEQ
824C extra calls to F per df/dy value).
825C 3 Chord iteration with an internally generated
826C diagonal Jacobian approximation (using one extra call
827C to F per df/dy evaluation).
828C 4 Chord iteration with a user-supplied banded Jacobian.
829C 5 Chord iteration with an internally generated banded
830C Jacobian (using ML + MU + 1 extra calls to F per
831C df/dy evaluation).
832C
833C If MITER = 1 or 4, the user must supply a subroutine JAC
834C (the name is arbitrary) as described above under JAC.
835C For other values of MITER, a dummy argument can be used.
836C
837C Optional Inputs
838C ---------------
839C The following is a list of the optional inputs provided for in the
840C call sequence. (See also Part 2.) For each such input variable,
841C this table lists its name as used in this documentation, its
842C location in the call sequence, its meaning, and the default value.
843C The use of any of these inputs requires IOPT = 1, and in that case
844C all of these inputs are examined. A value of zero for any of
845C these optional inputs will cause the default value to be used.
846C Thus to use a subset of the optional inputs, simply preload
847C locations 5 to 10 in RWORK and IWORK to 0.0 and 0 respectively,
848C and then set those of interest to nonzero values.
849C
850C Name Location Meaning and default value
851C ------ --------- -----------------------------------------------
852C H0 RWORK(5) Step size to be attempted on the first step.
853C The default value is determined by the solver.
854C HMAX RWORK(6) Maximum absolute step size allowed. The
855C default value is infinite.
856C HMIN RWORK(7) Minimum absolute step size allowed. The
857C default value is 0. (This lower bound is not
858C enforced on the final step before reaching
859C TCRIT when ITASK = 4 or 5.)
860C MAXORD IWORK(5) Maximum order to be allowed. The default value
861C is 12 if METH = 1, and 5 if METH = 2. (See the
862C MF description above for METH.) If MAXORD
863C exceeds the default value, it will be reduced
864C to the default value. If MAXORD is changed
865C during the problem, it may cause the current
866C order to be reduced.
867C MXSTEP IWORK(6) Maximum number of (internally defined) steps
868C allowed during one call to the solver. The
869C default value is 500.
870C MXHNIL IWORK(7) Maximum number of messages printed (per
871C problem) warning that T + H = T on a step
872C (H = step size). This must be positive to
873C result in a nondefault value. The default
874C value is 10.
875C
876C Optional Outputs
877C ----------------
878C As optional additional output from SLSODE, the variables listed
879C below are quantities related to the performance of SLSODE which
880C are available to the user. These are communicated by way of the
881C work arrays, but also have internal mnemonic names as shown.
882C Except where stated otherwise, all of these outputs are defined on
883C any successful return from SLSODE, and on any return with ISTATE =
884C -1, -2, -4, -5, or -6. On an illegal input return (ISTATE = -3),
885C they will be unchanged from their existing values (if any), except
886C possibly for TOLSF, LENRW, and LENIW. On any error return,
887C outputs relevant to the error will be defined, as noted below.
888C
889C Name Location Meaning
890C ----- --------- ------------------------------------------------
891C HU RWORK(11) Step size in t last used (successfully).
892C HCUR RWORK(12) Step size to be attempted on the next step.
893C TCUR RWORK(13) Current value of the independent variable which
894C the solver has actually reached, i.e., the
895C current internal mesh point in t. On output,
896C TCUR will always be at least as far as the
897C argument T, but may be farther (if interpolation
898C was done).
899C TOLSF RWORK(14) Tolerance scale factor, greater than 1.0,
900C computed when a request for too much accuracy
901C was detected (ISTATE = -3 if detected at the
902C start of the problem, ISTATE = -2 otherwise).
903C If ITOL is left unaltered but RTOL and ATOL are
904C uniformly scaled up by a factor of TOLSF for the
905C next call, then the solver is deemed likely to
906C succeed. (The user may also ignore TOLSF and
907C alter the tolerance parameters in any other way
908C appropriate.)
909C NST IWORK(11) Number of steps taken for the problem so far.
910C NFE IWORK(12) Number of F evaluations for the problem so far.
911C NJE IWORK(13) Number of Jacobian evaluations (and of matrix LU
912C decompositions) for the problem so far.
913C NQU IWORK(14) Method order last used (successfully).
914C NQCUR IWORK(15) Order to be attempted on the next step.
915C IMXER IWORK(16) Index of the component of largest magnitude in
916C the weighted local error vector ( e(i)/EWT(i) ),
917C on an error return with ISTATE = -4 or -5.
918C LENRW IWORK(17) Length of RWORK actually required. This is
919C defined on normal returns and on an illegal
920C input return for insufficient storage.
921C LENIW IWORK(18) Length of IWORK actually required. This is
922C defined on normal returns and on an illegal
923C input return for insufficient storage.
924C
925C The following two arrays are segments of the RWORK array which may
926C also be of interest to the user as optional outputs. For each
927C array, the table below gives its internal name, its base address
928C in RWORK, and its description.
929C
930C Name Base address Description
931C ---- ------------ ----------------------------------------------
932C YH 21 The Nordsieck history array, of size NYH by
933C (NQCUR + 1), where NYH is the initial value of
934C NEQ. For j = 0,1,...,NQCUR, column j + 1 of
935C YH contains HCUR**j/factorial(j) times the jth
936C derivative of the interpolating polynomial
937C currently representing the solution, evaluated
938C at t = TCUR.
939C ACOR LENRW-NEQ+1 Array of size NEQ used for the accumulated
940C corrections on each step, scaled on output to
941C represent the estimated local error in Y on
942C the last step. This is the vector e in the
943C description of the error control. It is
944C defined only on successful return from SLSODE.
945C
946C
947C Part 2. Other Callable Routines
948C --------------------------------
949C
950C The following are optional calls which the user may make to gain
951C additional capabilities in conjunction with SLSODE.
952C
953C Form of call Function
954C ------------------------ ----------------------------------------
955C CALL XSETUN(LUN) Set the logical unit number, LUN, for
956C output of messages from SLSODE, if the
957C default is not desired. The default
958C value of LUN is 6. This call may be made
959C at any time and will take effect
960C immediately.
961C CALL XSETF(MFLAG) Set a flag to control the printing of
962C messages by SLSODE. MFLAG = 0 means do
963C not print. (Danger: this risks losing
964C valuable information.) MFLAG = 1 means
965C print (the default). This call may be
966C made at any time and will take effect
967C immediately.
968C CALL SSRCOM(RSAV,ISAV,JOB) Saves and restores the contents of the
969C internal COMMON blocks used by SLSODE
970C (see Part 3 below). RSAV must be a
971C real array of length 218 or more, and
972C ISAV must be an integer array of length
973C 37 or more. JOB = 1 means save COMMON
974C into RSAV/ISAV. JOB = 2 means restore
975C COMMON from same. SSRCOM is useful if
976C one is interrupting a run and restarting
977C later, or alternating between two or
978C more problems solved with SLSODE.
979C CALL SINTDY(,,,,,) Provide derivatives of y, of various
980C (see below) orders, at a specified point t, if
981C desired. It may be called only after a
982C successful return from SLSODE. Detailed
983C instructions follow.
984C
985C Detailed instructions for using SINTDY
986C --------------------------------------
987C The form of the CALL is:
988C
989C CALL SINTDY (T, K, RWORK(21), NYH, DKY, IFLAG)
990C
991C The input parameters are:
992C
993C T Value of independent variable where answers are
994C desired (normally the same as the T last returned by
995C SLSODE). For valid results, T must lie between
996C TCUR - HU and TCUR. (See "Optional Outputs" above
997C for TCUR and HU.)
998C K Integer order of the derivative desired. K must
999C satisfy 0 <= K <= NQCUR, where NQCUR is the current
1000C order (see "Optional Outputs"). The capability
1001C corresponding to K = 0, i.e., computing y(t), is
1002C already provided by SLSODE directly. Since
1003C NQCUR >= 1, the first derivative dy/dt is always
1004C available with SINTDY.
1005C RWORK(21) The base address of the history array YH.
1006C NYH Column length of YH, equal to the initial value of NEQ.
1007C
1008C The output parameters are:
1009C
1010C DKY Real array of length NEQ containing the computed value
1011C of the Kth derivative of y(t).
1012C IFLAG Integer flag, returned as 0 if K and T were legal,
1013C -1 if K was illegal, and -2 if T was illegal.
1014C On an error return, a message is also written.
1015C
1016C
1017C Part 3. Common Blocks
1018C ----------------------
1019C
1020C If SLSODE is to be used in an overlay situation, the user must
1021C declare, in the primary overlay, the variables in:
1022C (1) the call sequence to SLSODE,
1023C (2) the internal COMMON block /SLS001/, of length 255
1024C (218 single precision words followed by 37 integer words).
1025C
1026C If SLSODE is used on a system in which the contents of internal
1027C COMMON blocks are not preserved between calls, the user should
1028C declare the above COMMON block in his main program to insure that
1029C its contents are preserved.
1030C
1031C If the solution of a given problem by SLSODE is to be interrupted
1032C and then later continued, as when restarting an interrupted run or
1033C alternating between two or more problems, the user should save,
1034C following the return from the last SLSODE call prior to the
1035C interruption, the contents of the call sequence variables and the
1036C internal COMMON block, and later restore these values before the
1037C next SLSODE call for that problem. In addition, if XSETUN and/or
1038C XSETF was called for non-default handling of error messages, then
1039C these calls must be repeated. To save and restore the COMMON
1040C block, use subroutine SSRCOM (see Part 2 above).
1041C
1042C
1043C Part 4. Optionally Replaceable Solver Routines
1044C -----------------------------------------------
1045C
1046C Below are descriptions of two routines in the SLSODE package which
1047C relate to the measurement of errors. Either routine can be
1048C replaced by a user-supplied version, if desired. However, since
1049C such a replacement may have a major impact on performance, it
1050C should be done only when absolutely necessary, and only with great
1051C caution. (Note: The means by which the package version of a
1052C routine is superseded by the user's version may be system-
1053C dependent.)
1054C
1055C SEWSET
1056C ------
1057C The following subroutine is called just before each internal
1058C integration step, and sets the array of error weights, EWT, as
1059C described under ITOL/RTOL/ATOL above:
1060C
1061C SUBROUTINE SEWSET (NEQ, ITOL, RTOL, ATOL, YCUR, EWT)
1062C
1063C where NEQ, ITOL, RTOL, and ATOL are as in the SLSODE call
1064C sequence, YCUR contains the current dependent variable vector,
1065C and EWT is the array of weights set by SEWSET.
1066C
1067C If the user supplies this subroutine, it must return in EWT(i)
1068C (i = 1,...,NEQ) a positive quantity suitable for comparing errors
1069C in Y(i) to. The EWT array returned by SEWSET is passed to the
1070C SVNORM routine (see below), and also used by SLSODE in the
1071C computation of the optional output IMXER, the diagonal Jacobian
1072C approximation, and the increments for difference quotient
1073C Jacobians.
1074C
1075C In the user-supplied version of SEWSET, it may be desirable to use
1076C the current values of derivatives of y. Derivatives up to order NQ
1077C are available from the history array YH, described above under
1078C optional outputs. In SEWSET, YH is identical to the YCUR array,
1079C extended to NQ + 1 columns with a column length of NYH and scale
1080C factors of H**j/factorial(j). On the first call for the problem,
1081C given by NST = 0, NQ is 1 and H is temporarily set to 1.0.
1082C NYH is the initial value of NEQ. The quantities NQ, H, and NST
1083C can be obtained by including in SEWSET the statements:
1084C REAL RLS
1085C COMMON /SLS001/ RLS(218),ILS(37)
1086C NQ = ILS(33)
1087C NST = ILS(34)
1088C H = RLS(212)
1089C Thus, for example, the current value of dy/dt can be obtained as
1090C YCUR(NYH+i)/H (i=1,...,NEQ) (and the division by H is unnecessary
1091C when NST = 0).
1092C
1093C SVNORM
1094C ------
1095C SVNORM is a real function routine which computes the weighted
1096C root-mean-square norm of a vector v:
1097C
1098C d = SVNORM (n, v, w)
1099C
1100C where:
1101C n = the length of the vector,
1102C v = real array of length n containing the vector,
1103C w = real array of length n containing weights,
1104C d = SQRT( (1/n) * sum(v(i)*w(i))**2 ).
1105C
1106C SVNORM is called with n = NEQ and with w(i) = 1.0/EWT(i), where
1107C EWT is as set by subroutine SEWSET.
1108C
1109C If the user supplies this function, it should return a nonnegative
1110C value of SVNORM suitable for use in the error control in SLSODE.
1111C None of the arguments should be altered by SVNORM. For example, a
1112C user-supplied SVNORM routine might:
1113C - Substitute a max-norm of (v(i)*w(i)) for the rms-norm, or
1114C - Ignore some components of v in the norm, with the effect of
1115C suppressing the error control on those components of Y.
1116C ---------------------------------------------------------------------
1117C***ROUTINES CALLED SEWSET, SINTDY, R1MACH, SSTODE, SVNORM, XERRWV
1118C***COMMON BLOCKS SLS001
1119C***REVISION HISTORY (YYYYMMDD)
1120C 19791129 DATE WRITTEN
1121C 19791213 Minor changes to declarations; DELP init. in STODE.
1122C 19800118 Treat NEQ as array; integer declarations added throughout;
1123C minor changes to prologue.
1124C 19800306 Corrected TESCO(1,NQP1) setting in CFODE.
1125C 19800519 Corrected access of YH on forced order reduction;
1126C numerous corrections to prologues and other comments.
1127C 19800617 In main driver, added loading of SQRT(UROUND) in RWORK;
1128C minor corrections to main prologue.
1129C 19800923 Added zero initialization of HU and NQU.
1130C 19801218 Revised XERRWV routine; minor corrections to main prologue.
1131C 19810401 Minor changes to comments and an error message.
1132C 19810814 Numerous revisions: replaced EWT by 1/EWT; used flags
1133C JCUR, ICF, IERPJ, IERSL between STODE and subordinates;
1134C added tuning parameters CCMAX, MAXCOR, MSBP, MXNCF;
1135C reorganized returns from STODE; reorganized type decls.;
1136C fixed message length in XERRWV; changed default LUNIT to 6;
1137C changed Common lengths; changed comments throughout.
1138C 19870330 Major update by ACH: corrected comments throughout;
1139C removed TRET from Common; rewrote EWSET with 4 loops;
1140C fixed t test in INTDY; added Cray directives in STODE;
1141C in STODE, fixed DELP init. and logic around PJAC call;
1142C combined routines to save/restore Common;
1143C passed LEVEL = 0 in error message calls (except run abort).
1144C 19890426 Modified prologue to SLATEC/LDOC format. (FNF)
1145C 19890501 Many improvements to prologue. (FNF)
1146C 19890503 A few final corrections to prologue. (FNF)
1147C 19890504 Minor cosmetic changes. (FNF)
1148C 19890510 Corrected description of Y in Arguments section. (FNF)
1149C 19890517 Minor corrections to prologue. (FNF)
1150C 19920514 Updated with prologue edited 891025 by G. Shaw for manual.
1151C 19920515 Converted source lines to upper case. (FNF)
1152C 19920603 Revised XERRWV calls using mixed upper-lower case. (ACH)
1153C 19920616 Revised prologue comment regarding CFT. (ACH)
1154C 19921116 Revised prologue comments regarding Common. (ACH).
1155C 19930326 Added comment about non-reentrancy. (FNF)
1156C 19930723 Changed R1MACH to RUMACH. (FNF)
1157C 19930801 Removed ILLIN and NTREP from Common (affects driver logic);
1158C minor changes to prologue and internal comments;
1159C changed Hollerith strings to quoted strings;
1160C changed internal comments to mixed case;
1161C replaced XERRWV with new version using character type;
1162C changed dummy dimensions from 1 to *. (ACH)
1163C 19930809 Changed to generic intrinsic names; changed names of
1164C subprograms and Common blocks to SLSODE etc. (ACH)
1165C 19930929 Eliminated use of REAL intrinsic; other minor changes. (ACH)
1166C 20010412 Removed all 'own' variables from Common block /SLS001/
1167C (affects declarations in 6 routines). (ACH)
1168C 20010509 Minor corrections to prologue. (ACH)
1169C 20031105 Restored 'own' variables to Common block /SLS001/, to
1170C enable interrupt/restart feature. (ACH)
1171C 20031112 Added SAVE statements for data-loaded constants.
1172C
1173C*** END PROLOGUE SLSODE
1174C
1175C*Internal Notes:
1176C
1177C Other Routines in the SLSODE Package.
1178C
1179C In addition to Subroutine SLSODE, the SLSODE package includes the
1180C following subroutines and function routines:
1181C SINTDY computes an interpolated value of the y vector at t = TOUT.
1182C SSTODE is the core integrator, which does one step of the
1183C integration and the associated error control.
1184C SCFODE sets all method coefficients and test constants.
1185C SPREPJ computes and preprocesses the Jacobian matrix J = df/dy
1186C and the Newton iteration matrix P = I - h*l0*J.
1187C SSOLSY manages solution of linear system in chord iteration.
1188C SEWSET sets the error weight vector EWT before each step.
1189C SVNORM computes the weighted R.M.S. norm of a vector.
1190C SSRCOM is a user-callable routine to save and restore
1191C the contents of the internal Common block.
1192C DGETRF AND DGETRS ARE ROUTINES FROM LAPACK FOR SOLVING FULL
1193C SYSTEMS OF LINEAR ALGEBRAIC EQUATIONS.
1194C DGBTRF AND DGBTRS ARE ROUTINES FROM LAPACK FOR SOLVING BANDED
1195C LINEAR SYSTEMS.
1196C R1MACH computes the unit roundoff in a machine-independent manner.
1197C XERRWV, XSETUN, XSETF, IXSAV, IUMACH handle the printing of all
1198C error messages and warnings. XERRWV is machine-dependent.
1199C Note: SVNORM, R1MACH, IXSAV, and IUMACH are function routines.
1200C All the others are subroutines.
1201C
1202C**End
1203C
1204C Declare externals.
1205 EXTERNAL sprepj, ssolsy
1206 REAL R1MACH, SVNORM
1207C
1208C Declare all other variables.
1209 INTEGER INIT, MXSTEP, MXHNIL, NHNIL, NSLAST, NYH,
1210 1 ialth, ipup, lmax, meo, nqnyh, nslp,
1211 1 icf, ierpj, iersl, jcur, jstart, kflag, l,
1212 2 lyh, lewt, lacor, lsavf, lwm, liwm, meth, miter,
1213 3 maxord, maxcor, msbp, mxncf, n, nq, nst, nfe, nje, nqu
1214 INTEGER I, I1, I2, IFLAG, IMXER, KGO, LF0,
1215 1 leniw, lenrw, lenwm, ml, mord, mu, mxhnl0, mxstp0
1216 REAL CONIT, CRATE, EL, ELCO, HOLD, RMAX, TESCO,
1217 1 ccmax, el0, h, hmin, hmxi, hu, rc, tn, uround
1218 REAL ATOLI, AYI, BIG, EWTI, H0, HMAX, HMX, RH, RTOLI,
1219 1 tcrit, tdist, tnext, tol, tolsf, tp, SIZE, sum, w0
1220 dimension mord(2)
1221 LOGICAL IHIT
1222 CHARACTER*80 MSG
1223 SAVE mord, mxstp0, mxhnl0
1224C-----------------------------------------------------------------------
1225C The following internal Common block contains
1226C (a) variables which are local to any subroutine but whose values must
1227C be preserved between calls to the routine ("own" variables), and
1228C (b) variables which are communicated between subroutines.
1229C The block SLS001 is declared in subroutines SLSODE, SINTDY, SSTODE,
1230C SPREPJ, and SSOLSY.
1231C Groups of variables are replaced by dummy arrays in the Common
1232C declarations in routines where those variables are not used.
1233C-----------------------------------------------------------------------
1234 COMMON /sls001/ conit, crate, el(13), elco(13,12),
1235 1 hold, rmax, tesco(3,12),
1236 1 ccmax, el0, h, hmin, hmxi, hu, rc, tn, uround,
1237 2 init, mxstep, mxhnil, nhnil, nslast, nyh,
1238 3 ialth, ipup, lmax, meo, nqnyh, nslp,
1239 3 icf, ierpj, iersl, jcur, jstart, kflag, l,
1240 4 lyh, lewt, lacor, lsavf, lwm, liwm, meth, miter,
1241 5 maxord, maxcor, msbp, mxncf, n, nq, nst, nfe, nje, nqu
1242C
1243 DATA mord(1),mord(2)/12,5/, mxstp0/500/, mxhnl0/10/
1244C-----------------------------------------------------------------------
1245C Block A.
1246C This code block is executed on every call.
1247C It tests ISTATE and ITASK for legality and branches appropriately.
1248C If ISTATE .GT. 1 but the flag INIT shows that initialization has
1249C not yet been done, an error return occurs.
1250C If ISTATE = 1 and TOUT = T, return immediately.
1251C-----------------------------------------------------------------------
1252C
1253C***FIRST EXECUTABLE STATEMENT SLSODE
1254 IF (istate .LT. 1 .OR. istate .GT. 3) GO TO 601
1255 IF (itask .LT. 1 .OR. itask .GT. 5) GO TO 602
1256 IF (istate .EQ. 1) GO TO 10
1257 IF (init .EQ. 0) GO TO 603
1258 IF (istate .EQ. 2) GO TO 200
1259 GO TO 20
1260 10 init = 0
1261 IF (tout .EQ. t) RETURN
1262C-----------------------------------------------------------------------
1263C Block B.
1264C The next code block is executed for the initial call (ISTATE = 1),
1265C or for a continuation call with parameter changes (ISTATE = 3).
1266C It contains checking of all inputs and various initializations.
1267C
1268C First check legality of the non-optional inputs NEQ, ITOL, IOPT,
1269C MF, ML, and MU.
1270C-----------------------------------------------------------------------
1271 20 IF (neq(1) .LE. 0) GO TO 604
1272 IF (istate .EQ. 1) GO TO 25
1273 IF (neq(1) .GT. n) GO TO 605
1274 25 n = neq(1)
1275 IF (itol .LT. 1 .OR. itol .GT. 4) GO TO 606
1276 IF (iopt .LT. 0 .OR. iopt .GT. 1) GO TO 607
1277 meth = mf/10
1278 miter = mf - 10*meth
1279 IF (meth .LT. 1 .OR. meth .GT. 2) GO TO 608
1280 IF (miter .LT. 0 .OR. miter .GT. 5) GO TO 608
1281 IF (miter .LE. 3) GO TO 30
1282 ml = iwork(1)
1283 mu = iwork(2)
1284 IF (ml .LT. 0 .OR. ml .GE. n) GO TO 609
1285 IF (mu .LT. 0 .OR. mu .GE. n) GO TO 610
1286 30 CONTINUE
1287C Next process and check the optional inputs. --------------------------
1288 IF (iopt .EQ. 1) GO TO 40
1289 maxord = mord(meth)
1290 mxstep = mxstp0
1291 mxhnil = mxhnl0
1292 IF (istate .EQ. 1) h0 = 0.0e0
1293 hmxi = 0.0e0
1294 hmin = 0.0e0
1295 GO TO 60
1296 40 maxord = iwork(5)
1297 IF (maxord .LT. 0) GO TO 611
1298 IF (maxord .EQ. 0) maxord = 100
1299 maxord = min(maxord,mord(meth))
1300 mxstep = iwork(6)
1301 IF (mxstep .LT. 0) GO TO 612
1302 IF (mxstep .EQ. 0) mxstep = mxstp0
1303 mxhnil = iwork(7)
1304 IF (mxhnil .LT. 0) GO TO 613
1305 IF (mxhnil .EQ. 0) mxhnil = mxhnl0
1306 IF (istate .NE. 1) GO TO 50
1307 h0 = rwork(5)
1308 IF ((tout - t)*h0 .LT. 0.0e0) GO TO 614
1309 50 hmax = rwork(6)
1310 IF (hmax .LT. 0.0e0) GO TO 615
1311 hmxi = 0.0e0
1312 IF (hmax .GT. 0.0e0) hmxi = 1.0e0/hmax
1313 hmin = rwork(7)
1314 IF (hmin .LT. 0.0e0) GO TO 616
1315C-----------------------------------------------------------------------
1316C Set work array pointers and check lengths LRW and LIW.
1317C Pointers to segments of RWORK and IWORK are named by prefixing L to
1318C the name of the segment. E.g., the segment YH starts at RWORK(LYH).
1319C Segments of RWORK (in order) are denoted YH, WM, EWT, SAVF, ACOR.
1320C-----------------------------------------------------------------------
1321 60 lyh = 21
1322 IF (istate .EQ. 1) nyh = n
1323 lwm = lyh + (maxord + 1)*nyh
1324 IF (miter .EQ. 0) lenwm = 0
1325 IF (miter .EQ. 1 .OR. miter .EQ. 2) lenwm = n*n + 2
1326 IF (miter .EQ. 3) lenwm = n + 2
1327 IF (miter .GE. 4) lenwm = (2*ml + mu + 1)*n + 2
1328 lewt = lwm + lenwm
1329 lsavf = lewt + n
1330 lacor = lsavf + n
1331 lenrw = lacor + n - 1
1332 iwork(17) = lenrw
1333 liwm = 1
1334 leniw = 20 + n
1335 IF (miter .EQ. 0 .OR. miter .EQ. 3) leniw = 20
1336 iwork(18) = leniw
1337 IF (lenrw .GT. lrw) GO TO 617
1338 IF (leniw .GT. liw) GO TO 618
1339C Check RTOL and ATOL for legality. ------------------------------------
1340 rtoli = rtol(1)
1341 atoli = atol(1)
1342 DO 70 i = 1,n
1343 IF (itol .GE. 3) rtoli = rtol(i)
1344 IF (itol .EQ. 2 .OR. itol .EQ. 4) atoli = atol(i)
1345 IF (rtoli .LT. 0.0e0) GO TO 619
1346 IF (atoli .LT. 0.0e0) GO TO 620
1347 70 CONTINUE
1348 IF (istate .EQ. 1) GO TO 100
1349C If ISTATE = 3, set flag to signal parameter changes to SSTODE. -------
1350 jstart = -1
1351 IF (nq .LE. maxord) GO TO 90
1352C MAXORD was reduced below NQ. Copy YH(*,MAXORD+2) into SAVF. ---------
1353 DO 80 i = 1,n
1354 80 rwork(i+lsavf-1) = rwork(i+lwm-1)
1355C Reload WM(1) = RWORK(LWM), since LWM may have changed. ---------------
1356 90 IF (miter .GT. 0) rwork(lwm) = sqrt(uround)
1357 IF (n .EQ. nyh) GO TO 200
1358C NEQ was reduced. Zero part of YH to avoid undefined references. -----
1359 i1 = lyh + l*nyh
1360 i2 = lyh + (maxord + 1)*nyh - 1
1361 IF (i1 .GT. i2) GO TO 200
1362 DO 95 i = i1,i2
1363 95 rwork(i) = 0.0e0
1364 GO TO 200
1365C-----------------------------------------------------------------------
1366C Block C.
1367C The next block is for the initial call only (ISTATE = 1).
1368C It contains all remaining initializations, the initial call to F,
1369C and the calculation of the initial step size.
1370C The error weights in EWT are inverted after being loaded.
1371C-----------------------------------------------------------------------
1372 100 uround = r1mach(4)
1373 tn = t
1374 IF (itask .NE. 4 .AND. itask .NE. 5) GO TO 110
1375 tcrit = rwork(1)
1376 IF ((tcrit - tout)*(tout - t) .LT. 0.0e0) GO TO 625
1377 IF (h0 .NE. 0.0e0 .AND. (t + h0 - tcrit)*h0 .GT. 0.0e0)
1378 1 h0 = tcrit - t
1379 110 jstart = 0
1380 IF (miter .GT. 0) rwork(lwm) = sqrt(uround)
1381 nhnil = 0
1382 nst = 0
1383 nje = 0
1384 nslast = 0
1385 hu = 0.0e0
1386 nqu = 0
1387 ccmax = 0.3e0
1388 maxcor = 3
1389 msbp = 20
1390 mxncf = 10
1391C Initial call to F. (LF0 points to YH(*,2).) -------------------------
1392 lf0 = lyh + nyh
1393 CALL f (neq, t, y, rwork(lf0))
1394 nfe = 1
1395C Load the initial value vector in YH. ---------------------------------
1396 DO 115 i = 1,n
1397 115 rwork(i+lyh-1) = y(i)
1398C Load and invert the EWT array. (H is temporarily set to 1.0.) -------
1399 nq = 1
1400 h = 1.0e0
1401 CALL sewset (n, itol, rtol, atol, rwork(lyh), rwork(lewt))
1402 DO 120 i = 1,n
1403 IF (rwork(i+lewt-1) .LE. 0.0e0) GO TO 621
1404 120 rwork(i+lewt-1) = 1.0e0/rwork(i+lewt-1)
1405C-----------------------------------------------------------------------
1406C The coding below computes the step size, H0, to be attempted on the
1407C first step, unless the user has supplied a value for this.
1408C First check that TOUT - T differs significantly from zero.
1409C A scalar tolerance quantity TOL is computed, as MAX(RTOL(I))
1410C if this is positive, or MAX(ATOL(I)/ABS(Y(I))) otherwise, adjusted
1411C so as to be between 100*UROUND and 1.0E-3.
1412C Then the computed value H0 is given by..
1413C NEQ
1414C H0**2 = TOL / ( w0**-2 + (1/NEQ) * SUM ( f(i)/ywt(i) )**2 )
1415C 1
1416C where w0 = MAX ( ABS(T), ABS(TOUT) ),
1417C f(i) = i-th component of initial value of f,
1418C ywt(i) = EWT(i)/TOL (a weight for y(i)).
1419C The sign of H0 is inferred from the initial values of TOUT and T.
1420C-----------------------------------------------------------------------
1421 IF (h0 .NE. 0.0e0) GO TO 180
1422 tdist = abs(tout - t)
1423 w0 = max(abs(t),abs(tout))
1424 IF (tdist .LT. 2.0e0*uround*w0) GO TO 622
1425 tol = rtol(1)
1426 IF (itol .LE. 2) GO TO 140
1427 DO 130 i = 1,n
1428 130 tol = max(tol,rtol(i))
1429 140 IF (tol .GT. 0.0e0) GO TO 160
1430 atoli = atol(1)
1431 DO 150 i = 1,n
1432 IF (itol .EQ. 2 .OR. itol .EQ. 4) atoli = atol(i)
1433 ayi = abs(y(i))
1434 IF (ayi .NE. 0.0e0) tol = max(tol,atoli/ayi)
1435 150 CONTINUE
1436 160 tol = max(tol,100.0e0*uround)
1437 tol = min(tol,0.001e0)
1438 sum = svnorm(n, rwork(lf0), rwork(lewt))
1439 sum = 1.0e0/(tol*w0*w0) + tol*sum**2
1440 h0 = 1.0e0/sqrt(sum)
1441 h0 = min(h0,tdist)
1442 h0 = sign(h0,tout-t)
1443C Adjust H0 if necessary to meet HMAX bound. ---------------------------
1444 180 rh = abs(h0)*hmxi
1445 IF (rh .GT. 1.0e0) h0 = h0/rh
1446C Load H with H0 and scale YH(*,2) by H0. ------------------------------
1447 h = h0
1448 DO 190 i = 1,n
1449 190 rwork(i+lf0-1) = h0*rwork(i+lf0-1)
1450 GO TO 270
1451C-----------------------------------------------------------------------
1452C Block D.
1453C The next code block is for continuation calls only (ISTATE = 2 or 3)
1454C and is to check stop conditions before taking a step.
1455C-----------------------------------------------------------------------
1456 200 nslast = nst
1457 GO TO (210, 250, 220, 230, 240), itask
1458 210 IF ((tn - tout)*h .LT. 0.0e0) GO TO 250
1459 CALL sintdy (tout, 0, rwork(lyh), nyh, y, iflag)
1460 IF (iflag .NE. 0) GO TO 627
1461 t = tout
1462 GO TO 420
1463 220 tp = tn - hu*(1.0e0 + 100.0e0*uround)
1464 IF ((tp - tout)*h .GT. 0.0e0) GO TO 623
1465 IF ((tn - tout)*h .LT. 0.0e0) GO TO 250
1466 GO TO 400
1467 230 tcrit = rwork(1)
1468 IF ((tn - tcrit)*h .GT. 0.0e0) GO TO 624
1469 IF ((tcrit - tout)*h .LT. 0.0e0) GO TO 625
1470 IF ((tn - tout)*h .LT. 0.0e0) GO TO 245
1471 CALL sintdy (tout, 0, rwork(lyh), nyh, y, iflag)
1472 IF (iflag .NE. 0) GO TO 627
1473 t = tout
1474 GO TO 420
1475 240 tcrit = rwork(1)
1476 IF ((tn - tcrit)*h .GT. 0.0e0) GO TO 624
1477 245 hmx = abs(tn) + abs(h)
1478 ihit = abs(tn - tcrit) .LE. 100.0e0*uround*hmx
1479 IF (ihit) GO TO 400
1480 tnext = tn + h*(1.0e0 + 4.0e0*uround)
1481 IF ((tnext - tcrit)*h .LE. 0.0e0) GO TO 250
1482 h = (tcrit - tn)*(1.0e0 - 4.0e0*uround)
1483 IF (istate .EQ. 2) jstart = -2
1484C-----------------------------------------------------------------------
1485C Block E.
1486C The next block is normally executed for all calls and contains
1487C the call to the one-step core integrator SSTODE.
1488C
1489C This is a looping point for the integration steps.
1490C
1491C First check for too many steps being taken, update EWT (if not at
1492C start of problem), check for too much accuracy being requested, and
1493C check for H below the roundoff level in T.
1494C-----------------------------------------------------------------------
1495 250 CONTINUE
1496 IF ((nst-nslast) .GE. mxstep) GO TO 500
1497 CALL sewset (n, itol, rtol, atol, rwork(lyh), rwork(lewt))
1498 DO 260 i = 1,n
1499 IF (rwork(i+lewt-1) .LE. 0.0e0) GO TO 510
1500 260 rwork(i+lewt-1) = 1.0e0/rwork(i+lewt-1)
1501 270 tolsf = uround*svnorm(n, rwork(lyh), rwork(lewt))
1502 IF (tolsf .LE. 1.0e0) GO TO 280
1503 tolsf = tolsf*2.0e0
1504 IF (nst .EQ. 0) GO TO 626
1505 GO TO 520
1506 280 IF ((tn + h) .NE. tn) GO TO 290
1507 nhnil = nhnil + 1
1508 IF (nhnil .GT. mxhnil) GO TO 290
1509 msg = 'SLSODE- Warning..internal T (=R1) and H (=R2) are'
1510 CALL xerrwv (msg, 50, 101, 0, 0, 0, 0, 0, 0.0e0, 0.0e0)
1511 msg=' such that in the machine, T + H = T on the next step '
1512 CALL xerrwv (msg, 60, 101, 0, 0, 0, 0, 0, 0.0e0, 0.0e0)
1513 msg = ' (H = step size). Solver will continue anyway'
1514 CALL xerrwv (msg, 50, 101, 0, 0, 0, 0, 2, tn, h)
1515 IF (nhnil .LT. mxhnil) GO TO 290
1516 msg = 'SLSODE- Above warning has been issued I1 times. '
1517 CALL xerrwv (msg, 50, 102, 0, 0, 0, 0, 0, 0.0e0, 0.0e0)
1518 msg = ' It will not be issued again for this problem'
1519 CALL xerrwv (msg, 50, 102, 0, 1, mxhnil, 0, 0, 0.0e0, 0.0e0)
1520 290 CONTINUE
1521C-----------------------------------------------------------------------
1522C CALL SSTODE(NEQ,Y,YH,NYH,YH,EWT,SAVF,ACOR,WM,IWM,F,JAC,SPREPJ,SSOLSY)
1523C-----------------------------------------------------------------------
1524 CALL sstode (neq, y, rwork(lyh), nyh, rwork(lyh), rwork(lewt),
1525 1 rwork(lsavf), rwork(lacor), rwork(lwm), iwork(liwm),
1526 2 f, jac, sprepj, ssolsy)
1527 kgo = 1 - kflag
1528 GO TO (300, 530, 540), kgo
1529C-----------------------------------------------------------------------
1530C Block F.
1531C The following block handles the case of a successful return from the
1532C core integrator (KFLAG = 0). Test for stop conditions.
1533C-----------------------------------------------------------------------
1534 300 init = 1
1535 GO TO (310, 400, 330, 340, 350), itask
1536C ITASK = 1. If TOUT has been reached, interpolate. -------------------
1537 310 IF ((tn - tout)*h .LT. 0.0e0) GO TO 250
1538 CALL sintdy (tout, 0, rwork(lyh), nyh, y, iflag)
1539 t = tout
1540 GO TO 420
1541C ITASK = 3. Jump to exit if TOUT was reached. ------------------------
1542 330 IF ((tn - tout)*h .GE. 0.0e0) GO TO 400
1543 GO TO 250
1544C ITASK = 4. See if TOUT or TCRIT was reached. Adjust H if necessary.
1545 340 IF ((tn - tout)*h .LT. 0.0e0) GO TO 345
1546 CALL sintdy (tout, 0, rwork(lyh), nyh, y, iflag)
1547 t = tout
1548 GO TO 420
1549 345 hmx = abs(tn) + abs(h)
1550 ihit = abs(tn - tcrit) .LE. 100.0e0*uround*hmx
1551 IF (ihit) GO TO 400
1552 tnext = tn + h*(1.0e0 + 4.0e0*uround)
1553 IF ((tnext - tcrit)*h .LE. 0.0e0) GO TO 250
1554 h = (tcrit - tn)*(1.0e0 - 4.0e0*uround)
1555 jstart = -2
1556 GO TO 250
1557C ITASK = 5. See if TCRIT was reached and jump to exit. ---------------
1558 350 hmx = abs(tn) + abs(h)
1559 ihit = abs(tn - tcrit) .LE. 100.0e0*uround*hmx
1560C-----------------------------------------------------------------------
1561C Block G.
1562C The following block handles all successful returns from SLSODE.
1563C If ITASK .NE. 1, Y is loaded from YH and T is set accordingly.
1564C ISTATE is set to 2, and the optional outputs are loaded into the
1565C work arrays before returning.
1566C-----------------------------------------------------------------------
1567 400 DO 410 i = 1,n
1568 410 y(i) = rwork(i+lyh-1)
1569 t = tn
1570 IF (itask .NE. 4 .AND. itask .NE. 5) GO TO 420
1571 IF (ihit) t = tcrit
1572 420 istate = 2
1573 rwork(11) = hu
1574 rwork(12) = h
1575 rwork(13) = tn
1576 iwork(11) = nst
1577 iwork(12) = nfe
1578 iwork(13) = nje
1579 iwork(14) = nqu
1580 iwork(15) = nq
1581 RETURN
1582C-----------------------------------------------------------------------
1583C Block H.
1584C The following block handles all unsuccessful returns other than
1585C those for illegal input. First the error message routine is called.
1586C If there was an error test or convergence test failure, IMXER is set.
1587C Then Y is loaded from YH and T is set to TN. The optional outputs
1588C are loaded into the work arrays before returning.
1589C-----------------------------------------------------------------------
1590C The maximum number of steps was taken before reaching TOUT. ----------
1591 500 msg = 'SLSODE- At current T (=R1), MXSTEP (=I1) steps '
1592 CALL xerrwv (msg, 50, 201, 0, 0, 0, 0, 0, 0.0e0, 0.0e0)
1593 msg = ' taken on this call before reaching TOUT '
1594 CALL xerrwv (msg, 50, 201, 0, 1, mxstep, 0, 1, tn, 0.0e0)
1595 istate = -1
1596 GO TO 580
1597C EWT(I) .LE. 0.0 for some I (not at start of problem). ----------------
1598 510 ewti = rwork(lewt+i-1)
1599 msg = .LE.'SLSODE- At T (=R1), EWT(I1) has become R2 0.'
1600 CALL xerrwv (msg, 50, 202, 0, 1, i, 0, 2, tn, ewti)
1601 istate = -6
1602 GO TO 580
1603C Too much accuracy requested for machine precision. -------------------
1604 520 msg = 'SLSODE- At T (=R1), too much accuracy requested '
1605 CALL xerrwv (msg, 50, 203, 0, 0, 0, 0, 0, 0.0e0, 0.0e0)
1606 msg = ' for precision of machine.. see TOLSF (=R2) '
1607 CALL xerrwv (msg, 50, 203, 0, 0, 0, 0, 2, tn, tolsf)
1608 rwork(14) = tolsf
1609 istate = -2
1610 GO TO 580
1611C KFLAG = -1. Error test failed repeatedly or with ABS(H) = HMIN. -----
1612 530 msg = 'SLSODE- At T(=R1) and step size H(=R2), the error'
1613 CALL xerrwv (msg, 50, 204, 0, 0, 0, 0, 0, 0.0e0, 0.0e0)
1614 msg = ' test failed repeatedly or with ABS(H) = HMIN'
1615 CALL xerrwv (msg, 50, 204, 0, 0, 0, 0, 2, tn, h)
1616 istate = -4
1617 GO TO 560
1618C KFLAG = -2. Convergence failed repeatedly or with ABS(H) = HMIN. ----
1619 540 msg = 'SLSODE- At T (=R1) and step size H (=R2), the '
1620 CALL xerrwv (msg, 50, 205, 0, 0, 0, 0, 0, 0.0e0, 0.0e0)
1621 msg = ' corrector convergence failed repeatedly '
1622 CALL xerrwv (msg, 50, 205, 0, 0, 0, 0, 0, 0.0e0, 0.0e0)
1623 msg = ' or with ABS(H) = HMIN '
1624 CALL xerrwv (msg, 30, 205, 0, 0, 0, 0, 2, tn, h)
1625 istate = -5
1626C Compute IMXER if relevant. -------------------------------------------
1627 560 big = 0.0e0
1628 imxer = 1
1629 DO 570 i = 1,n
1630 SIZE = abs(rwork(i+lacor-1)*rwork(i+lewt-1))
1631 IF (big .GE. size) GO TO 570
1632 big = SIZE
1633 imxer = i
1634 570 CONTINUE
1635 iwork(16) = imxer
1636C Set Y vector, T, and optional outputs. -------------------------------
1637 580 DO 590 i = 1,n
1638 590 y(i) = rwork(i+lyh-1)
1639 t = tn
1640 rwork(11) = hu
1641 rwork(12) = h
1642 rwork(13) = tn
1643 iwork(11) = nst
1644 iwork(12) = nfe
1645 iwork(13) = nje
1646 iwork(14) = nqu
1647 iwork(15) = nq
1648 RETURN
1649C-----------------------------------------------------------------------
1650C Block I.
1651C The following block handles all error returns due to illegal input
1652C (ISTATE = -3), as detected before calling the core integrator.
1653C First the error message routine is called. If the illegal input
1654C is a negative ISTATE, the run is aborted (apparent infinite loop).
1655C-----------------------------------------------------------------------
1656 601 msg = 'SLSODE- ISTATE (=I1) illegal '
1657 CALL xerrwv (msg, 30, 1, 0, 1, istate, 0, 0, 0.0e0, 0.0e0)
1658 IF (istate .LT. 0) GO TO 800
1659 GO TO 700
1660 602 msg = 'SLSODE- ITASK (=I1) illegal '
1661 CALL xerrwv (msg, 30, 2, 0, 1, itask, 0, 0, 0.0e0, 0.0e0)
1662 GO TO 700
1663 603 msg = .GT.'SLSODE- ISTATE 1 but SLSODE not initialized '
1664 CALL xerrwv (msg, 50, 3, 0, 0, 0, 0, 0, 0.0e0, 0.0e0)
1665 GO TO 700
1666 604 msg = .LT.'SLSODE- NEQ (=I1) 1 '
1667 CALL xerrwv (msg, 30, 4, 0, 1, neq(1), 0, 0, 0.0e0, 0.0e0)
1668 GO TO 700
1669 605 msg = 'SLSODE- ISTATE = 3 and NEQ increased (I1 to I2) '
1670 CALL xerrwv (msg, 50, 5, 0, 2, n, neq(1), 0, 0.0e0, 0.0e0)
1671 GO TO 700
1672 606 msg = 'SLSODE- ITOL (=I1) illegal '
1673 CALL xerrwv (msg, 30, 6, 0, 1, itol, 0, 0, 0.0e0, 0.0e0)
1674 GO TO 700
1675 607 msg = 'SLSODE- IOPT (=I1) illegal '
1676 CALL xerrwv (msg, 30, 7, 0, 1, iopt, 0, 0, 0.0e0, 0.0e0)
1677 GO TO 700
1678 608 msg = 'SLSODE- MF (=I1) illegal '
1679 CALL xerrwv (msg, 30, 8, 0, 1, mf, 0, 0, 0.0e0, 0.0e0)
1680 GO TO 700
1681 609 msg = .LT..GE.'SLSODE- ML (=I1) illegal.. 0 or NEQ (=I2)'
1682 CALL xerrwv (msg, 50, 9, 0, 2, ml, neq(1), 0, 0.0e0, 0.0e0)
1683 GO TO 700
1684 610 msg = .LT..GE.'SLSODE- MU (=I1) illegal.. 0 or NEQ (=I2)'
1685 CALL xerrwv (msg, 50, 10, 0, 2, mu, neq(1), 0, 0.0e0, 0.0e0)
1686 GO TO 700
1687 611 msg = .LT.'SLSODE- MAXORD (=I1) 0 '
1688 CALL xerrwv (msg, 30, 11, 0, 1, maxord, 0, 0, 0.0e0, 0.0e0)
1689 GO TO 700
1690 612 msg = .LT.'SLSODE- MXSTEP (=I1) 0 '
1691 CALL xerrwv (msg, 30, 12, 0, 1, mxstep, 0, 0, 0.0e0, 0.0e0)
1692 GO TO 700
1693 613 msg = .LT.'SLSODE- MXHNIL (=I1) 0 '
1694 CALL xerrwv (msg, 30, 13, 0, 1, mxhnil, 0, 0, 0.0e0, 0.0e0)
1695 GO TO 700
1696 614 msg = 'SLSODE- TOUT (=R1) behind T (=R2) '
1697 CALL xerrwv (msg, 40, 14, 0, 0, 0, 0, 2, tout, t)
1698 msg = ' Integration direction is given by H0 (=R1) '
1699 CALL xerrwv (msg, 50, 14, 0, 0, 0, 0, 1, h0, 0.0e0)
1700 GO TO 700
1701 615 msg = .LT.'SLSODE- HMAX (=R1) 0.0 '
1702 CALL xerrwv (msg, 30, 15, 0, 0, 0, 0, 1, hmax, 0.0e0)
1703 GO TO 700
1704 616 msg = .LT.'SLSODE- HMIN (=R1) 0.0 '
1705 CALL xerrwv (msg, 30, 16, 0, 0, 0, 0, 1, hmin, 0.0e0)
1706 GO TO 700
1707 617 CONTINUE
1708 msg='SLSODE- RWORK length needed, LENRW (=I1), exceeds LRW (=I2)'
1709 CALL xerrwv (msg, 60, 17, 0, 2, lenrw, lrw, 0, 0.0e0, 0.0e0)
1710 GO TO 700
1711 618 CONTINUE
1712 msg='SLSODE- IWORK length needed, LENIW (=I1), exceeds LIW (=I2)'
1713 CALL xerrwv (msg, 60, 18, 0, 2, leniw, liw, 0, 0.0e0, 0.0e0)
1714 GO TO 700
1715 619 msg = .LT.'SLSODE- RTOL(I1) is R1 0.0 '
1716 CALL xerrwv (msg, 40, 19, 0, 1, i, 0, 1, rtoli, 0.0e0)
1717 GO TO 700
1718 620 msg = .LT.'SLSODE- ATOL(I1) is R1 0.0 '
1719 CALL xerrwv (msg, 40, 20, 0, 1, i, 0, 1, atoli, 0.0e0)
1720 GO TO 700
1721 621 ewti = rwork(lewt+i-1)
1722 msg = .LE.'SLSODE- EWT(I1) is R1 0.0 '
1723 CALL xerrwv (msg, 40, 21, 0, 1, i, 0, 1, ewti, 0.0e0)
1724 GO TO 700
1725 622 CONTINUE
1726 msg='SLSODE- TOUT (=R1) too close to T(=R2) to start integration'
1727 CALL xerrwv (msg, 60, 22, 0, 0, 0, 0, 2, tout, t)
1728 GO TO 700
1729 623 CONTINUE
1730 msg='SLSODE- ITASK = I1 and TOUT (=R1) behind TCUR - HU (= R2) '
1731 CALL xerrwv (msg, 60, 23, 0, 1, itask, 0, 2, tout, tp)
1732 GO TO 700
1733 624 CONTINUE
1734 msg='SLSODE- ITASK = 4 OR 5 and TCRIT (=R1) behind TCUR (=R2) '
1735 CALL xerrwv (msg, 60, 24, 0, 0, 0, 0, 2, tcrit, tn)
1736 GO TO 700
1737 625 CONTINUE
1738 msg='SLSODE- ITASK = 4 or 5 and TCRIT (=R1) behind TOUT (=R2) '
1739 CALL xerrwv (msg, 60, 25, 0, 0, 0, 0, 2, tcrit, tout)
1740 GO TO 700
1741 626 msg = 'SLSODE- At start of problem, too much accuracy '
1742 CALL xerrwv (msg, 50, 26, 0, 0, 0, 0, 0, 0.0e0, 0.0e0)
1743 msg=' requested for precision of machine.. See TOLSF (=R1) '
1744 CALL xerrwv (msg, 60, 26, 0, 0, 0, 0, 1, tolsf, 0.0e0)
1745 rwork(14) = tolsf
1746 GO TO 700
1747 627 msg = 'SLSODE- Trouble in SINTDY. ITASK = I1, TOUT = R1'
1748 CALL xerrwv (msg, 50, 27, 0, 1, itask, 0, 1, tout, 0.0e0)
1749C
1750 700 istate = -3
1751 RETURN
1752C
1753 800 msg = 'SLSODE- Run aborted.. apparent infinite loop '
1754 CALL xerrwv (msg, 50, 303, 2, 0, 0, 0, 0, 0.0e0, 0.0e0)
1755 RETURN
1756C----------------------- END OF SUBROUTINE SLSODE ----------------------
1757 END
charNDArray max(char d, const charNDArray &m)
Definition: chNDArray.cc:230
charNDArray min(char d, const charNDArray &m)
Definition: chNDArray.cc:207
static T abs(T x)
Definition: pr-output.cc:1678
subroutine sewset(N, ITOL, RTOL, ATOL, YCUR, EWT)
Definition: sewset.f:2
subroutine sintdy(T, K, YH, NYH, DKY, IFLAG)
Definition: sintdy.f:2
subroutine slsode(F, NEQ, Y, T, TOUT, ITOL, RTOL, ATOL, ITASK, ISTATE, IOPT, RWORK, LRW, IWORK, LIW, JAC, MF)
Definition: slsode.f:3
subroutine sprepj(NEQ, Y, YH, NYH, EWT, FTEM, SAVF, WM, IWM, F, JAC)
Definition: sprepj.f:3
subroutine ssolsy(WM, IWM, X, TEM)
Definition: ssolsy.f:2
subroutine sstode(NEQ, Y, YH, NYH, YH1, EWT, SAVF, ACOR, WM, IWM, F, JAC, PJAC, SLVS)
Definition: sstode.f:3
subroutine xerrwv(MSG, NMES, NERR, LEVEL, NI, I1, I2, NR, R1, R2)
Definition: xerrwv.f:3