1 SUBROUTINE INTEGRATE
( TIN
, TOUT
)
3 IMPLICIT KPP_REAL
(A
-H
,O
-Z
)
4 INCLUDE
'KPP_ROOT_Parameters.h'
5 INCLUDE
'KPP_ROOT_Global.h'
12 PARAMETER ( LRW
=20+3*1500+16*NVAR
)
14 EXTERNAL FUNC_CHEM
, JAC_CHEM
24 C ---- NORMAL COMPUTATION ---
27 C ---- USE OPTIONAL INPUT ---
30 IWORK
(5) = MAXORD
! MAX ORD
33 RWORK
(6) = STEPMAX
! STEP MAX
34 RWORK
(7) = STEPMIN
! STEP MIN
35 RWORK
(5) = STEPMIN
! INITIAL STEP
37 C ----- SIGNAL FOR STIFF CASE, FULL JACOBIAN, INTERN (22) or SUPPLIED (21)
40 CALL atmlsodes
(FUNC_CHEM
, NVAR
, VAR
, TIN
, TOUT
, ITOL
, RTOL
, ATOL
,
41 ! ITASK
, ISTATE
, IOPT
, RWORK
, LRW
, IWORK
, LIW
,
45 print
*,'LSODES: Unsucessfull exit at T=',
46 & TIN
,' (ISTATE=',ISTATE
,')'
52 subroutine atmlsodes
(f
, neq
, y
, t
, tout
, itol
, RelTol
, AbsTol
,
53 1 itask
, istate
, iopt
, rwork
, lrw
, iwork
, liw
, jac
, mf
)
55 integer neq
, itol
, itask
, istate
, iopt
, lrw
, iwork
, liw
, mf
56 KPP_REAL y
, t
, tout
, RelTol
, AbsTol
, rwork
57 dimension neq
(1), y
(1), RelTol
(1), AbsTol
(1),
58 1 rwork
(lrw
), iwork
(liw
)
59 c-----------------------------------------------------------------------
60 c this is the march 30, 1987 version of
61 c lsodes.. livermore solver for ordinary differential equations
62 c with general sparse jacobian matrices.
63 c this version is in KPP_REAL.
65 c lsodes solves the initial value problem for stiff or nonstiff
66 c systems of first order ode-s,
67 c dy/dt = f(t,y) , or, in component form,
68 c dy(i)/dt = f(i) = f(i,t,y(1),y(2),...,y(neq)) (i = 1,...,neq).
69 c lsodes is a variant of the lsode package, and is intended for
70 c problems in which the jacobian matrix df/dy has an arbitrary
71 c sparse structure (when the problem is stiff).
73 c authors.. alan c. hindmarsh,
74 c computing and mathematics research division, l-316
75 c lawrence livermore national laboratory
76 c livermore, ca 94550.
78 c and andrew h. sherman
79 c j. s. nolen and associates
81 c-----------------------------------------------------------------------
83 c 1. alan c. hindmarsh, odepack, a systematized collection of ode
84 c solvers, in scientific computing, r. s. stepleman et al. (eds.),
85 c north-holland, amsterdam, 1983, pp. 55-64.
87 c 2. s. c. eisenstat, m. c. gursky, m. h. schultz, and a. h. sherman,
88 c yale sparse matrix package.. i. the symmetric codes,
89 c int. j. num. meth. eng., 18 (1982), pp. 1145-1151.
91 c 3. s. c. eisenstat, m. c. gursky, m. h. schultz, and a. h. sherman,
92 c yale sparse matrix package.. ii. the nonsymmetric codes,
93 c research report no. 114, dept. of computer sciences, yale
95 c-----------------------------------------------------------------------
98 c communication between the user and the lsodes package, for normal
99 c situations, is summarized here. this summary describes only a subset
100 c of the full set of options available. see the full description for
101 c details, including optional communication, nonstandard options,
102 c and instructions for special situations. see also the example
103 c problem (with program and output) following this summary.
105 c a. first provide a subroutine of the form..
106 c subroutine f (neq, t, y, ydot)
107 c dimension y(neq), ydot(neq)
108 c which supplies the vector function f by loading ydot(i) with f(i).
110 c b. next determine (or guess) whether or not the problem is stiff.
111 c stiffness occurs when the jacobian matrix df/dy has an eigenvalue
112 c whose real part is negative and large in magnitude, compared to the
113 c reciprocal of the t span of interest. if the problem is nonstiff,
114 c use a method flag mf = 10. if it is stiff, there are two standard
115 c for the method flag, mf = 121 and mf = 222. in both cases, lsodes
116 c requires the jacobian matrix in some form, and it treats this matrix
117 c in general sparse form, with sparsity structure determined internally.
118 c (for options where the user supplies the sparsity structure, see
119 c the full description of mf below.)
121 c c. if the problem is stiff, you are encouraged to supply the jacobian
122 c directly (mf = 121), but if this is not feasible, lsodes will
123 c compute it internally by difference quotients (mf = 222).
124 c if you are supplying the jacobian, provide a subroutine of the form..
125 c subroutine jac (neq, t, y, j, ian, jan, pdj)
126 c dimension y(1), ian(1), jan(1), pdj(1)
127 c here neq, t, y, and j are input arguments, and the jac routine is to
128 c load the array pdj (of length neq) with the j-th column of df/dy.
129 c i.e., load pdj(i) with df(i)/dy(j) for all relevant values of i.
130 c the arguments ian and jan should be ignored for normal situations.
131 c lsodes will CALL the jac routine with j = 1,2,...,neq.
132 c only nonzero elements need be loaded. usually, a crude approximation
133 c to df/dy, possibly with fewer nonzero elements, will suffice.
135 c d. write a main program which calls subroutine lsodes once for
136 c each point at which answers are desired. this should also provide
137 c for possible use of logical unit 6 for output of error messages
138 c by lsodes. on the first CALL to lsodes, supply arguments as follows..
139 c f = name of subroutine for right-hand side vector f.
140 c this name must be declared external in calling program.
141 c neq = number of first order ode-s.
142 c y = array of initial values, of length neq.
143 c t = the initial value of the independent variable.
144 c tout = first point where output is desired (.ne. t).
145 c itol = 1 or 2 according as AbsTol (below) is a scalar or array.
146 c RelTol = relative tolerance parameter (scalar).
147 c AbsTol = absolute tolerance parameter (scalar or array).
148 c the estimated local error in y(i) will be controlled so as
149 c to be roughly less (in magnitude) than
150 c ewt(i) = RelTol*abs(y(i)) + AbsTol if itol = 1, or
151 c ewt(i) = RelTol*abs(y(i)) + AbsTol(i) if itol = 2.
152 c thus the local error test passes if, in each component,
153 c either the absolute error is less than AbsTol (or AbsTol(i)),
154 c or the relative error is less than RelTol.
155 c use RelTol = 0.0 for pure absolute error control, and
156 c use AbsTol = 0.0 (or AbsTol(i) = 0.0) for pure relative error
157 c control. caution.. actual (global) errors may exceed these
158 c local tolerances, so choose them conservatively.
159 c itask = 1 for normal computation of output values of y at t = tout.
160 c istate = integer flag (input and output). set istate = 1.
161 c iopt = 0 to indicate no optional inputs used.
162 c rwork = real work array of length at least..
163 c 20 + 16*neq for mf = 10,
164 c 20 + (2 + 1./lenrat)*nnz + (11 + 9./lenrat)*neq
165 c for mf = 121 or 222,
167 c nnz = the number of nonzero elements in the sparse
168 c jacobian (if this is unknown, use an estimate), and
169 c lenrat = the real to integer wordlength ratio (usually 1 in
170 c single precision and 2 in KPP_REAL).
171 c in any case, the required size of rwork cannot generally
172 c be predicted in advance if mf = 121 or 222, and the value
173 c above is a rough estimate of a crude lower bound. some
174 c experimentation with this size may be necessary.
175 c (when known, the correct required length is an optional
176 c output, available in iwork(17).)
177 c lrw = declared length of rwork (in user-s dimension).
178 c iwork = integer work array of length at least 30.
179 c liw = declared length of iwork (in user-s dimension).
180 c jac = name of subroutine for jacobian matrix (mf = 121).
181 c if used, this name must be declared external in calling
182 c program. if not used, pass a dummy name.
183 c mf = method flag. standard values are..
184 c 10 for nonstiff (adams) method, no jacobian used.
185 c 121 for stiff (bdf) method, user-supplied sparse jacobian.
186 c 222 for stiff method, internally generated sparse jacobian.
187 c note that the main program must declare arrays y, rwork, iwork,
188 c and possibly AbsTol.
190 c e. the output from the first CALL (or any call) is..
191 c y = array of computed values of y(t) vector.
192 c t = corresponding value of independent variable (normally tout).
193 c istate = 2 if lsodes was successful, negative otherwise.
194 c -1 means excess work done on this CALL (perhaps wrong mf).
195 c -2 means excess accuracy requested (tolerances too small).
196 c -3 means illegal input detected (see printed message).
197 c -4 means repeated error test failures (check all inputs).
198 c -5 means repeated convergence failures (perhaps bad jacobian
199 c supplied or wrong choice of mf or tolerances).
200 c -6 means error weight became zero during problem. (solution
201 c component i vanished, and AbsTol or AbsTol(i) = 0.)
202 c -7 means a fatal error return flag came from the sparse
203 c solver cdrv by way of prjs or slss. should never happen.
204 c a return with istate = -1, -4, or -5 may result from using
205 c an inappropriate sparsity structure, one that is quite
206 c different from the initial structure. consider calling
207 c lsodes again with istate = 3 to force the structure to be
208 c reevaluated. see the full description of istate below.
210 c f. to continue the integration after a successful return, simply
211 c reset tout and CALL lsodes again. no other parameters need be reset.
213 c-----------------------------------------------------------------------
216 c the following is a simple example problem, with the coding
217 c needed for its solution by lsodes. the problem is from chemical
218 c kinetics, and consists of the following 12 rate equations..
220 c dy2/dt = rk1*y1 + rk11*rk14*y4 + rk19*rk14*y5
221 c - rk3*y2*y3 - rk15*y2*y12 - rk2*y2
222 c dy3/dt = rk2*y2 - rk5*y3 - rk3*y2*y3 - rk7*y10*y3
223 c + rk11*rk14*y4 + rk12*rk14*y6
224 c dy4/dt = rk3*y2*y3 - rk11*rk14*y4 - rk4*y4
225 c dy5/dt = rk15*y2*y12 - rk19*rk14*y5 - rk16*y5
226 c dy6/dt = rk7*y10*y3 - rk12*rk14*y6 - rk8*y6
227 c dy7/dt = rk17*y10*y12 - rk20*rk14*y7 - rk18*y7
228 c dy8/dt = rk9*y10 - rk13*rk14*y8 - rk10*y8
229 c dy9/dt = rk4*y4 + rk16*y5 + rk8*y6 + rk18*y7
230 c dy10/dt = rk5*y3 + rk12*rk14*y6 + rk20*rk14*y7
231 c + rk13*rk14*y8 - rk7*y10*y3 - rk17*y10*y12
232 c - rk6*y10 - rk9*y10
234 c dy12/dt = rk6*y10 + rk19*rk14*y5 + rk20*rk14*y7
235 c - rk15*y2*y12 - rk17*y10*y12
237 c with rk1 = rk5 = 0.1, rk4 = rk8 = rk16 = rk18 = 2.5,
238 c rk10 = 5.0, rk2 = rk6 = 10.0, rk14 = 30.0,
239 c rk3 = rk7 = rk9 = rk11 = rk12 = rk13 = rk19 = rk20 = 50.0,
240 c rk15 = rk17 = 100.0.
242 c the t interval is from 0 to 1000, and the initial conditions
243 c are y1 = 1, y2 = y3 = ... = y12 = 0. the problem is stiff.
245 c the following coding solves this problem with lsodes, using mf = 121
246 c and printing results at t = .1, 1., 10., 100., 1000. it uses
247 c itol = 1 and mixed relative/absolute tolerance controls.
248 c during the run and at the end, statistical quantities of interest
249 c are printed (see optional outputs in the full description below).
252 c KPP_REAL AbsTol, RelTol, rwork, t, tout, y
253 c dimension y(12), rwork(500), iwork(30)
254 c data lrw/500/, liw/30/
269 c CALL lsodes (fex, neq, y, t, tout, itol, RelTol, AbsTol,
270 c 1 itask, istate, iopt, rwork, lrw, iwork, liw, jex, mf)
271 c write(6,30)t,iwork(11),rwork(11),(y(i),i=1,neq)
272 c 30 format(//7h at t =,e11.3,4x,
273 c 1 12h no. steps =,i5,4x,12h last step =,e11.3/
274 c 2 13h y array = ,4e14.5/13x,4e14.5/13x,4e14.5)
275 c if (istate .lt. 0) go to 80
285 c nnzlu = iwork(25) + iwork(26) + neq
286 c write (6,70) lenrw,leniw,nst,nfe,nje,nlu,nnz,nnzlu
287 c 70 format(//22h required rwork size =,i4,15h iwork size =,i4/
288 c 1 12h no. steps =,i4,12h no. f-s =,i4,12h no. j-s =,i4,
289 c 2 13h no. lu-s =,i4/23h no. of nonzeros in j =,i5,
290 c 3 26h no. of nonzeros in lu =,i5)
292 c 80 write(6,90)istate
293 c 90 format(///22h error halt.. istate =,i3)
297 c subroutine fex (neq, t, y, ydot)
298 c KPP_REAL t, y, ydot
299 c KPP_REAL rk1, rk2, rk3, rk4, rk5, rk6, rk7, rk8, rk9,
300 c 1 rk10, rk11, rk12, rk13, rk14, rk15, rk16, rk17
301 c dimension y(12), ydot(12)
302 c data rk1/0.1d0/, rk2/10.0d0/, rk3/50.0d0/, rk4/2.5d0/, rk5/0.1d0/,
303 c 1 rk6/10.0d0/, rk7/50.0d0/, rk8/2.5d0/, rk9/50.0d0/, rk10/5.0d0/,
304 c 2 rk11/50.0d0/, rk12/50.0d0/, rk13/50.0d0/, rk14/30.0d0/,
305 c 3 rk15/100.0d0/, rk16/2.5d0/, rk17/100.0d0/, rk18/2.5d0/,
306 c 4 rk19/50.0d0/, rk20/50.0d0/
307 c ydot(1) = -rk1*y(1)
308 c ydot(2) = rk1*y(1) + rk11*rk14*y(4) + rk19*rk14*y(5)
309 c 1 - rk3*y(2)*y(3) - rk15*y(2)*y(12) - rk2*y(2)
310 c ydot(3) = rk2*y(2) - rk5*y(3) - rk3*y(2)*y(3) - rk7*y(10)*y(3)
311 c 1 + rk11*rk14*y(4) + rk12*rk14*y(6)
312 c ydot(4) = rk3*y(2)*y(3) - rk11*rk14*y(4) - rk4*y(4)
313 c ydot(5) = rk15*y(2)*y(12) - rk19*rk14*y(5) - rk16*y(5)
314 c ydot(6) = rk7*y(10)*y(3) - rk12*rk14*y(6) - rk8*y(6)
315 c ydot(7) = rk17*y(10)*y(12) - rk20*rk14*y(7) - rk18*y(7)
316 c ydot(8) = rk9*y(10) - rk13*rk14*y(8) - rk10*y(8)
317 c ydot(9) = rk4*y(4) + rk16*y(5) + rk8*y(6) + rk18*y(7)
318 c ydot(10) = rk5*y(3) + rk12*rk14*y(6) + rk20*rk14*y(7)
319 c 1 + rk13*rk14*y(8) - rk7*y(10)*y(3) - rk17*y(10)*y(12)
320 c 2 - rk6*y(10) - rk9*y(10)
321 c ydot(11) = rk10*y(8)
322 c ydot(12) = rk6*y(10) + rk19*rk14*y(5) + rk20*rk14*y(7)
323 c 1 - rk15*y(2)*y(12) - rk17*y(10)*y(12)
327 c subroutine jex (neq, t, y, j, ia, ja, pdj)
329 c KPP_REAL rk1, rk2, rk3, rk4, rk5, rk6, rk7, rk8, rk9,
330 c 1 rk10, rk11, rk12, rk13, rk14, rk15, rk16, rk17
331 c dimension y(1), ia(1), ja(1), pdj(1)
332 c data rk1/0.1d0/, rk2/10.0d0/, rk3/50.0d0/, rk4/2.5d0/, rk5/0.1d0/,
333 c 1 rk6/10.0d0/, rk7/50.0d0/, rk8/2.5d0/, rk9/50.0d0/, rk10/5.0d0/,
334 c 2 rk11/50.0d0/, rk12/50.0d0/, rk13/50.0d0/, rk14/30.0d0/,
335 c 3 rk15/100.0d0/, rk16/2.5d0/, rk17/100.0d0/, rk18/2.5d0/,
336 c 4 rk19/50.0d0/, rk20/50.0d0/
337 c go to (1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12), j
341 c 2 pdj(2) = -rk3*y(3) - rk15*y(12) - rk2
342 c pdj(3) = rk2 - rk3*y(3)
344 c pdj(5) = rk15*y(12)
345 c pdj(12) = -rk15*y(12)
347 c 3 pdj(2) = -rk3*y(2)
348 c pdj(3) = -rk5 - rk3*y(2) - rk7*y(10)
351 c pdj(10) = rk5 - rk7*y(10)
353 c 4 pdj(2) = rk11*rk14
355 c pdj(4) = -rk11*rk14 - rk4
358 c 5 pdj(2) = rk19*rk14
359 c pdj(5) = -rk19*rk14 - rk16
361 c pdj(12) = rk19*rk14
363 c 6 pdj(3) = rk12*rk14
364 c pdj(6) = -rk12*rk14 - rk8
366 c pdj(10) = rk12*rk14
368 c 7 pdj(7) = -rk20*rk14 - rk18
370 c pdj(10) = rk20*rk14
371 c pdj(12) = rk20*rk14
373 c 8 pdj(8) = -rk13*rk14 - rk10
374 c pdj(10) = rk13*rk14
377 c 10 pdj(3) = -rk7*y(3)
379 c pdj(7) = rk17*y(12)
381 c pdj(10) = -rk7*y(3) - rk17*y(12) - rk6 - rk9
382 c pdj(12) = rk6 - rk17*y(12)
384 c 12 pdj(2) = -rk15*y(2)
386 c pdj(7) = rk17*y(10)
387 c pdj(10) = -rk17*y(10)
388 c pdj(12) = -rk15*y(2) - rk17*y(10)
392 c the output of this program (on a cray-1 in single precision)
396 c at t = 1.000e-01 no. steps = 12 last step = 1.515e-02
397 c y array = 9.90050e-01 6.28228e-03 3.65313e-03 7.51934e-07
398 c 1.12167e-09 1.18458e-09 1.77291e-12 3.26476e-07
399 c 5.46720e-08 9.99500e-06 4.48483e-08 2.76398e-06
402 c at t = 1.000e+00 no. steps = 33 last step = 7.880e-02
403 c y array = 9.04837e-01 9.13105e-03 8.20622e-02 2.49177e-05
404 c 1.85055e-06 1.96797e-06 1.46157e-07 2.39557e-05
405 c 3.26306e-05 7.21621e-04 5.06433e-05 3.05010e-03
408 c at t = 1.000e+01 no. steps = 48 last step = 1.239e+00
409 c y array = 3.67876e-01 3.68958e-03 3.65133e-01 4.48325e-05
410 c 6.10798e-05 4.33148e-05 5.90211e-05 1.18449e-04
411 c 3.15235e-03 3.56531e-03 4.15520e-03 2.48741e-01
414 c at t = 1.000e+02 no. steps = 91 last step = 3.764e+00
415 c y array = 4.44981e-05 4.42666e-07 4.47273e-04 -3.53257e-11
416 c 2.81577e-08 -9.67741e-11 2.77615e-07 1.45322e-07
417 c 1.56230e-02 4.37394e-06 1.60104e-02 9.52246e-01
420 c at t = 1.000e+03 no. steps = 111 last step = 4.156e+02
421 c y array = -2.65492e-13 2.60539e-14 -8.59563e-12 6.29355e-14
422 c -1.78066e-13 5.71471e-13 -1.47561e-12 4.58078e-15
423 c 1.56314e-02 1.37878e-13 1.60184e-02 9.52719e-01
426 c required rwork size = 442 iwork size = 30
427 c no. steps = 111 no. f-s = 142 no. j-s = 2 no. lu-s = 20
428 c no. of nonzeros in j = 44 no. of nonzeros in lu = 50
429 c-----------------------------------------------------------------------
430 c full description of user interface to lsodes.
432 c the user interface to lsodes consists of the following parts.
434 c i. the CALL sequence to subroutine lsodes, which is a driver
435 c routine for the solver. this includes descriptions of both
436 c the CALL sequence arguments and of user-supplied routines.
437 c following these descriptions is a description of
438 c optional inputs available through the CALL sequence, and then
439 c a description of optional outputs (in the work arrays).
441 c ii. descriptions of other routines in the lsodes package that may be
442 c (optionally) called by the user. these provide the ability to
443 c alter error message handling, save and restore the internal
444 c common, and obtain specified derivatives of the solution y(t).
446 c iii. descriptions of common blocks to be declared in overlay
447 c or similar environments, or to be saved when doing an interrupt
448 c of the problem and continued solution later.
450 c iv. description of two routines in the lsodes package, either of
451 c which the user may replace with his own version, if desired.
452 c these relate to the measurement of errors.
454 c-----------------------------------------------------------------------
455 c part i. CALL sequence.
457 c the CALL sequence parameters used for input only are
458 c f, neq, tout, itol, RelTol, AbsTol, itask, iopt, lrw, liw, jac, mf,
459 c and those used for both input and output are
461 c the work arrays rwork and iwork are also used for conditional and
462 c optional inputs and optional outputs. (the term output here refers
463 c to the return from subroutine lsodes to the user-s calling program.)
465 c the legality of input parameters will be thoroughly checked on the
466 c initial CALL for the problem, but not checked thereafter unless a
467 c change in input parameters is flagged by istate = 3 on input.
469 c the descriptions of the CALL arguments are as follows.
471 c f = the name of the user-supplied subroutine defining the
472 c ode system. the system must be put in the first-order
473 c form dy/dt = f(t,y), where f is a vector-valued function
474 c of the scalar t and the vector y. subroutine f is to
475 c compute the function f. it is to have the form
476 c subroutine f (neq, t, y, ydot)
477 c dimension y(1), ydot(1)
478 c where neq, t, and y are input, and the array ydot = f(t,y)
479 c is output. y and ydot are arrays of length neq.
480 c (in the dimension statement above, 1 is a dummy
481 c dimension.. it can be replaced by any value.)
482 c subroutine f should not alter y(1),...,y(neq).
483 c f must be declared external in the calling program.
485 c subroutine f may access user-defined quantities in
486 c neq(2),... and/or in y(neq(1)+1),... if neq is an array
487 c (dimensioned in f) and/or y has length exceeding neq(1).
488 c see the descriptions of neq and y below.
490 c if quantities computed in the f routine are needed
491 c externally to lsodes, an extra CALL to f should be made
492 c for this purpose, for consistent and accurate results.
493 c if only the derivative dy/dt is needed, use intdy instead.
495 c neq = the size of the ode system (number of first order
496 c ordinary differential equations). used only for input.
497 c neq may be decreased, but not increased, during the problem.
498 c if neq is decreased (with istate = 3 on input), the
499 c remaining components of y should be left undisturbed, if
500 c these are to be accessed in f and/or jac.
502 c normally, neq is a scalar, and it is generally referred to
503 c as a scalar in this user interface description. however,
504 c neq may be an array, with neq(1) set to the system size.
505 c (the lsodes package accesses only neq(1).) in either case,
506 c this parameter is passed as the neq argument in all calls
507 c to f and jac. hence, if it is an array, locations
508 c neq(2),... may be used to store other integer data and pass
509 c it to f and/or jac. subroutines f and/or jac must include
510 c neq in a dimension statement in that case.
512 c y = a real array for the vector of dependent variables, of
513 c length neq or more. used for both input and output on the
514 c first CALL (istate = 1), and only for output on other calls.
515 c on the first call, y must contain the vector of initial
516 c values. on output, y contains the computed solution vector,
517 c evaluated at t. if desired, the y array may be used
518 c for other purposes between calls to the solver.
520 c this array is passed as the y argument in all calls to
521 c f and jac. hence its length may exceed neq, and locations
522 c y(neq+1),... may be used to store other real data and
523 c pass it to f and/or jac. (the lsodes package accesses only
526 c t = the independent variable. on input, t is used only on the
527 c first call, as the initial point of the integration.
528 c on output, after each call, t is the value at which a
529 c computed solution y is evaluated (usually the same as tout).
530 c on an error return, t is the farthest point reached.
532 c tout = the next value of t at which a computed solution is desired.
533 c used only for input.
535 c when starting the problem (istate = 1), tout may be equal
536 c to t for one call, then should .ne. t for the next call.
537 c for the initial t, an input value of tout .ne. t is used
538 c in order to determine the direction of the integration
539 c (i.e. the algebraic sign of the step sizes) and the rough
540 c scale of the problem. integration in either direction
541 c (forward or backward in t) is permitted.
543 c if itask = 2 or 5 (one-step modes), tout is ignored after
544 c the first CALL (i.e. the first CALL with tout .ne. t).
545 c otherwise, tout is required on every call.
547 c if itask = 1, 3, or 4, the values of tout need not be
548 c monotone, but a value of tout which backs up is limited
549 c to the current internal t interval, whose endpoints are
550 c tcur - hu and tcur (see optional outputs, below, for
553 c itol = an indicator for the type of error control. see
554 c description below under AbsTol. used only for input.
556 c RelTol = a relative error tolerance parameter, either a scalar or
557 c an array of length neq. see description below under AbsTol.
560 c AbsTol = an absolute error tolerance parameter, either a scalar or
561 c an array of length neq. input only.
563 c the input parameters itol, RelTol, and AbsTol determine
564 c the error control performed by the solver. the solver will
565 c control the vector e = (e(i)) of estimated local errors
566 c in y, according to an inequality of the form
567 c rms-norm of ( e(i)/ewt(i) ) .le. 1,
568 c where ewt(i) = RelTol(i)*abs(y(i)) + AbsTol(i),
569 c and the rms-norm (root-mean-square norm) here is
570 c rms-norm(v) = sqrt(sum v(i)**2 / neq). here ewt = (ewt(i))
571 c is a vector of weights which must always be positive, and
572 c the values of RelTol and AbsTol should all be non-negative.
573 c the following table gives the types (scalar/array) of
574 c RelTol and AbsTol, and the corresponding form of ewt(i).
576 c itol RelTol AbsTol ewt(i)
577 c 1 scalar scalar RelTol*abs(y(i)) + AbsTol
578 c 2 scalar array RelTol*abs(y(i)) + AbsTol(i)
579 c 3 array scalar RelTol(i)*abs(y(i)) + AbsTol
580 c 4 array array RelTol(i)*abs(y(i)) + AbsTol(i)
582 c when either of these parameters is a scalar, it need not
583 c be dimensioned in the user-s calling program.
585 c if none of the above choices (with itol, RelTol, and AbsTol
586 c fixed throughout the problem) is suitable, more general
587 c error controls can be obtained by substituting
588 c user-supplied routines for the setting of ewt and/or for
589 c the norm calculation. see part iv below.
591 c if global errors are to be estimated by making a repeated
592 c run on the same problem with smaller tolerances, then all
593 c components of RelTol and AbsTol (i.e. of ewt) should be scaled
596 c itask = an index specifying the task to be performed.
597 c input only. itask has the following values and meanings.
598 c 1 means normal computation of output values of y(t) at
599 c t = tout (by overshooting and interpolating).
600 c 2 means take one step only and return.
601 c 3 means stop at the first internal mesh point at or
602 c beyond t = tout and return.
603 c 4 means normal computation of output values of y(t) at
604 c t = tout but without overshooting t = tcrit.
605 c tcrit must be input as rwork(1). tcrit may be equal to
606 c or beyond tout, but not behind it in the direction of
607 c integration. this option is useful if the problem
608 c has a singularity at or beyond t = tcrit.
609 c 5 means take one step, without passing tcrit, and return.
610 c tcrit must be input as rwork(1).
612 c note.. if itask = 4 or 5 and the solver reaches tcrit
613 c (within roundoff), it will return t = tcrit (exactly) to
614 c indicate this (unless itask = 4 and tout comes before tcrit,
615 c in which case answers at t = tout are returned first).
617 c istate = an index used for input and output to specify the
618 c the state of the calculation.
620 c on input, the values of istate are as follows.
621 c 1 means this is the first CALL for the problem
622 c (initializations will be done). see note below.
623 c 2 means this is not the first call, and the calculation
624 c is to continue normally, with no change in any input
625 c parameters except possibly tout and itask.
626 c (if itol, RelTol, and/or AbsTol are changed between calls
627 c with istate = 2, the new values will be used but not
628 c tested for legality.)
629 c 3 means this is not the first call, and the
630 c calculation is to continue normally, but with
631 c a change in input parameters other than
632 c tout and itask. changes are allowed in
633 c neq, itol, RelTol, AbsTol, iopt, lrw, liw, mf,
634 c the conditional inputs ia and ja,
635 c and any of the optional inputs except h0.
636 c in particular, if miter = 1 or 2, a CALL with istate = 3
637 c will cause the sparsity structure of the problem to be
638 c recomputed (or reread from ia and ja if moss = 0).
639 c note.. a preliminary CALL with tout = t is not counted
640 c as a first CALL here, as no initialization or checking of
641 c input is done. (such a CALL is sometimes useful for the
642 c purpose of outputting the initial conditions.)
643 c thus the first CALL for which tout .ne. t requires
644 c istate = 1 on input.
646 c on output, istate has the following values and meanings.
647 c 1 means nothing was done, as tout was equal to t with
648 c istate = 1 on input. (however, an internal counter was
649 c set to detect and prevent repeated calls of this type.)
650 c 2 means the integration was performed successfully.
651 c -1 means an excessive amount of work (more than mxstep
652 c steps) was done on this call, before completing the
653 c requested task, but the integration was otherwise
654 c successful as far as t. (mxstep is an optional input
655 c and is normally 500.) to continue, the user may
656 c simply reset istate to a value .gt. 1 and CALL again
657 c (the excess work step counter will be reset to 0).
658 c in addition, the user may increase mxstep to avoid
659 c this error return (see below on optional inputs).
660 c -2 means too much accuracy was requested for the precision
661 c of the machine being used. this was detected before
662 c completing the requested task, but the integration
663 c was successful as far as t. to continue, the tolerance
664 c parameters must be reset, and istate must be set
665 c to 3. the optional output tolsf may be used for this
666 c purpose. (note.. if this condition is detected before
667 c taking any steps, then an illegal input return
668 c (istate = -3) occurs instead.)
669 c -3 means illegal input was detected, before taking any
670 c integration steps. see written message for details.
671 c note.. if the solver detects an infinite loop of calls
672 c to the solver with illegal input, it will cause
674 c -4 means there were repeated error test failures on
675 c one attempted step, before completing the requested
676 c task, but the integration was successful as far as t.
677 c the problem may have a singularity, or the input
678 c may be inappropriate.
679 c -5 means there were repeated convergence test failures on
680 c one attempted step, before completing the requested
681 c task, but the integration was successful as far as t.
682 c this may be caused by an inaccurate jacobian matrix,
683 c if one is being used.
684 c -6 means ewt(i) became zero for some i during the
685 c integration. pure relative error control (AbsTol(i)=0.0)
686 c was requested on a variable which has now vanished.
687 c the integration was successful as far as t.
688 c -7 means a fatal error return flag came from the sparse
689 c solver cdrv by way of prjs or slss (numerical
690 c factorization or backsolve). this should never happen.
691 c the integration was successful as far as t.
693 c note.. an error return with istate = -1, -4, or -5 and with
694 c miter = 1 or 2 may mean that the sparsity structure of the
695 c problem has changed significantly since it was last
696 c determined (or input). in that case, one can attempt to
697 c complete the integration by setting istate = 3 on the next
698 c call, so that a new structure determination is done.
700 c note.. since the normal output value of istate is 2,
701 c it does not need to be reset for normal continuation.
702 c also, since a negative input value of istate will be
703 c regarded as illegal, a negative output value requires the
704 c user to change it, and possibly other inputs, before
705 c calling the solver again.
707 c iopt = an integer flag to specify whether or not any optional
708 c inputs are being used on this call. input only.
709 c the optional inputs are listed separately below.
710 c iopt = 0 means no optional inputs are being used.
711 c default values will be used in all cases.
712 c iopt = 1 means one or more optional inputs are being used.
714 c rwork = a work array used for a mixture of real (KPP_REAL)
715 c and integer work space.
716 c the length of rwork (in real words) must be at least
717 c 20 + nyh*(maxord + 1) + 3*neq + lwm where
718 c nyh = the initial value of neq,
719 c maxord = 12 (if meth = 1) or 5 (if meth = 2) (unless a
720 c smaller value is given as an optional input),
721 c lwm = 0 if miter = 0,
722 c lwm = 2*nnz + 2*neq + (nnz+9*neq)/lenrat if miter = 1,
723 c lwm = 2*nnz + 2*neq + (nnz+10*neq)/lenrat if miter = 2,
724 c lwm = neq + 2 if miter = 3.
725 c in the above formulas,
726 c nnz = number of nonzero elements in the jacobian matrix.
727 c lenrat = the real to integer wordlength ratio (usually 1 in
728 c single precision and 2 in KPP_REAL).
729 c (see the mf description for meth and miter.)
730 c thus if maxord has its default value and neq is constant,
731 c the minimum length of rwork is..
732 c 20 + 16*neq for mf = 10,
733 c 20 + 16*neq + lwm for mf = 11, 111, 211, 12, 112, 212,
734 c 22 + 17*neq for mf = 13,
735 c 20 + 9*neq for mf = 20,
736 c 20 + 9*neq + lwm for mf = 21, 121, 221, 22, 122, 222,
737 c 22 + 10*neq for mf = 23.
738 c if miter = 1 or 2, the above formula for lwm is only a
739 c crude lower bound. the required length of rwork cannot
740 c be readily predicted in general, as it depends on the
741 c sparsity structure of the problem. some experimentation
744 c the first 20 words of rwork are reserved for conditional
745 c and optional inputs and optional outputs.
747 c the following word in rwork is a conditional input..
748 c rwork(1) = tcrit = critical value of t which the solver
749 c is not to overshoot. required if itask is
750 c 4 or 5, and ignored otherwise. (see itask.)
752 c lrw = the length of the array rwork, as declared by the user.
753 c (this will be checked by the solver.)
755 c iwork = an integer work array. the length of iwork must be at least
756 c 31 + neq + nnz if moss = 0 and miter = 1 or 2, or
758 c (nnz is the number of nonzero elements in df/dy.)
760 c in lsodes, iwork is used only for conditional and
761 c optional inputs and optional outputs.
763 c the following two blocks of words in iwork are conditional
764 c inputs, required if moss = 0 and miter = 1 or 2, but not
765 c otherwise (see the description of mf for moss).
766 c iwork(30+j) = ia(j) (j=1,...,neq+1)
767 c iwork(31+neq+k) = ja(k) (k=1,...,nnz)
768 c the two arrays ia and ja describe the sparsity structure
769 c to be assumed for the jacobian matrix. ja contains the row
770 c indices where nonzero elements occur, reading in columnwise
771 c order, and ia contains the starting locations in ja of the
772 c descriptions of columns 1,...,neq, in that order, with
773 c ia(1) = 1. thus, for each column index j = 1,...,neq, the
774 c values of the row index i in column j where a nonzero
775 c element may occur are given by
776 c i = ja(k), where ia(j) .le. k .lt. ia(j+1).
777 c if nnz is the total number of nonzero locations assumed,
778 c then the length of the ja array is nnz, and ia(neq+1) must
779 c be nnz + 1. duplicate entries are not allowed.
781 c liw = the length of the array iwork, as declared by the user.
782 c (this will be checked by the solver.)
784 c note.. the work arrays must not be altered between calls to lsodes
785 c for the same problem, except possibly for the conditional and
786 c optional inputs, and except for the last 3*neq words of rwork.
787 c the latter space is used for internal scratch space, and so is
788 c available for use by the user outside lsodes between calls, if
789 c desired (but not for use by f or jac).
791 c jac = name of user-supplied routine (miter = 1 or moss = 1) to
792 c compute the jacobian matrix, df/dy, as a function of
793 c the scalar t and the vector y. it is to have the form
794 c subroutine jac (neq, t, y, j, ian, jan, pdj)
795 c dimension y(1), ian(1), jan(1), pdj(1)
796 c where neq, t, y, j, ian, and jan are input, and the array
797 c pdj, of length neq, is to be loaded with column j
798 c of the jacobian on output. thus df(i)/dy(j) is to be
799 c loaded into pdj(i) for all relevant values of i.
800 c here t and y have the same meaning as in subroutine f,
801 c and j is a column index (1 to neq). ian and jan are
802 c undefined in calls to jac for structure determination
803 c (moss = 1). otherwise, ian and jan are structure
804 c descriptors, as defined under optional outputs below, and
805 c so can be used to determine the relevant row indices i, if
806 c desired. (in the dimension statement above, 1 is a
807 c dummy dimension.. it can be replaced by any value.)
808 c jac need not provide df/dy exactly. a crude
809 c approximation (possibly with greater sparsity) will do.
810 c in any case, pdj is preset to zero by the solver,
811 c so that only the nonzero elements need be loaded by jac.
812 c calls to jac are made with j = 1,...,neq, in that order, and
813 c each such set of calls is preceded by a CALL to f with the
814 c same arguments neq, t, and y. thus to gain some efficiency,
815 c intermediate quantities shared by both calculations may be
816 c saved in a user common block by f and not recomputed by jac,
817 c if desired. jac must not alter its input arguments.
818 c jac must be declared external in the calling program.
819 c subroutine jac may access user-defined quantities in
820 c neq(2),... and y(neq(1)+1),... if neq is an array
821 c (dimensioned in jac) and y has length exceeding neq(1).
822 c see the descriptions of neq and y above.
824 c mf = the method flag. used only for input.
825 c mf has three decimal digits-- moss, meth, miter--
826 c mf = 100*moss + 10*meth + miter.
827 c moss indicates the method to be used to obtain the sparsity
828 c structure of the jacobian matrix if miter = 1 or 2..
829 c moss = 0 means the user has supplied ia and ja
830 c (see descriptions under iwork above).
831 c moss = 1 means the user has supplied jac (see below)
832 c and the structure will be obtained from neq
833 c initial calls to jac.
834 c moss = 2 means the structure will be obtained from neq+1
835 c initial calls to f.
836 c meth indicates the basic linear multistep method..
837 c meth = 1 means the implicit adams method.
838 c meth = 2 means the method based on backward
839 c differentiation formulas (bdf-s).
840 c miter indicates the corrector iteration method..
841 c miter = 0 means functional iteration (no jacobian matrix
843 c miter = 1 means chord iteration with a user-supplied
844 c sparse jacobian, given by subroutine jac.
845 c miter = 2 means chord iteration with an internally
846 c generated (difference quotient) sparse jacobian
847 c (using ngp extra calls to f per df/dy value,
848 c where ngp is an optional output described below.)
849 c miter = 3 means chord iteration with an internally
850 c generated diagonal jacobian approximation.
851 c (using 1 extra CALL to f per df/dy evaluation).
852 c if miter = 1 or moss = 1, the user must supply a subroutine
853 c jac (the name is arbitrary) as described above under jac.
854 c otherwise, a dummy argument can be used.
856 c the standard choices for mf are..
857 c mf = 10 for a nonstiff problem,
858 c mf = 21 or 22 for a stiff problem with ia/ja supplied
859 c (21 if jac is supplied, 22 if not),
860 c mf = 121 for a stiff problem with jac supplied,
862 c mf = 222 for a stiff problem with neither ia/ja nor
864 c the sparseness structure can be changed during the
865 c problem by making a CALL to lsodes with istate = 3.
866 c-----------------------------------------------------------------------
869 c the following is a list of the optional inputs provided for in the
870 c CALL sequence. (see also part ii.) for each such input variable,
871 c this table lists its name as used in this documentation, its
872 c location in the CALL sequence, its meaning, and the default value.
873 c the use of any of these inputs requires iopt = 1, and in that
874 c case all of these inputs are examined. a value of zero for any
875 c of these optional inputs will cause the default value to be used.
876 c thus to use a subset of the optional inputs, simply preload
877 c locations 5 to 10 in rwork and iwork to 0.0 and 0 respectively, and
878 c then set those of interest to nonzero values.
880 c name location meaning and default value
882 c h0 rwork(5) the step size to be attempted on the first step.
883 c the default value is determined by the solver.
885 c hmax rwork(6) the maximum absolute step size allowed.
886 c the default value is infinite.
888 c hmin rwork(7) the minimum absolute step size allowed.
889 c the default value is 0. (this lower bound is not
890 c enforced on the final step before reaching tcrit
891 c when itask = 4 or 5.)
893 c seth rwork(8) the element threshhold for sparsity determination
894 c when moss = 1 or 2. if the absolute value of
895 c an estimated jacobian element is .le. seth, it
896 c will be assumed to be absent in the structure.
897 c the default value of seth is 0.
899 c maxord iwork(5) the maximum order to be allowed. the default
900 c value is 12 if meth = 1, and 5 if meth = 2.
901 c if maxord exceeds the default value, it will
902 c be reduced to the default value.
903 c if maxord is changed during the problem, it may
904 c cause the current order to be reduced.
906 c mxstep iwork(6) maximum number of (internally defined) steps
907 c allowed during one CALL to the solver.
908 c the default value is 500.
910 c mxhnil iwork(7) maximum number of messages printed (per problem)
911 c warning that t + h = t on a step (h = step size).
912 c this must be positive to result in a non-default
913 c value. the default value is 10.
914 c-----------------------------------------------------------------------
917 c as optional additional output from lsodes, the variables listed
918 c below are quantities related to the performance of lsodes
919 c which are available to the user. these are communicated by way of
920 c the work arrays, but also have internal mnemonic names as shown.
921 c except where stated otherwise, all of these outputs are defined
922 c on any successful return from lsodes, and on any return with
923 c istate = -1, -2, -4, -5, or -6. on an illegal input return
924 c (istate = -3), they will be unchanged from their existing values
925 c (if any), except possibly for tolsf, lenrw, and leniw.
926 c on any error return, outputs relevant to the error will be defined,
929 c name location meaning
931 c hu rwork(11) the step size in t last used (successfully).
933 c hcur rwork(12) the step size to be attempted on the next step.
935 c tcur rwork(13) the current value of the independent variable
936 c which the solver has actually reached, i.e. the
937 c current internal mesh point in t. on output, tcur
938 c will always be at least as far as the argument
939 c t, but may be farther (if interpolation was done).
941 c tolsf rwork(14) a tolerance scale factor, greater than 1.0,
942 c computed when a request for too much accuracy was
943 c detected (istate = -3 if detected at the start of
944 c the problem, istate = -2 otherwise). if itol is
945 c left unaltered but RelTol and AbsTol are uniformly
946 c scaled up by a factor of tolsf for the next call,
947 c then the solver is deemed likely to succeed.
948 c (the user may also ignore tolsf and alter the
949 c tolerance parameters in any other way appropriate.)
951 c nst iwork(11) the number of steps taken for the problem so far.
953 c nfe iwork(12) the number of f evaluations for the problem so far,
954 c excluding those for structure determination
957 c nje iwork(13) the number of jacobian evaluations for the problem
958 c so far, excluding those for structure determination
961 c nqu iwork(14) the method order last used (successfully).
963 c nqcur iwork(15) the order to be attempted on the next step.
965 c imxer iwork(16) the index of the component of largest magnitude in
966 c the weighted local error vector ( e(i)/ewt(i) ),
967 c on an error return with istate = -4 or -5.
969 c lenrw iwork(17) the length of rwork actually required.
970 c this is defined on normal returns and on an illegal
971 c input return for insufficient storage.
973 c leniw iwork(18) the length of iwork actually required.
974 c this is defined on normal returns and on an illegal
975 c input return for insufficient storage.
977 c nnz iwork(19) the number of nonzero elements in the jacobian
978 c matrix, including the diagonal (miter = 1 or 2).
979 c (this may differ from that given by ia(neq+1)-1
980 c if moss = 0, because of added diagonal entries.)
982 c ngp iwork(20) the number of groups of column indices, used in
983 c difference quotient jacobian aproximations if
984 c miter = 2. this is also the number of extra f
985 c evaluations needed for each jacobian evaluation.
987 c nlu iwork(21) the number of sparse lu decompositions for the
990 c lyh iwork(22) the base address in rwork of the history array yh,
991 c described below in this list.
993 c ipian iwork(23) the base address of the structure descriptor array
994 c ian, described below in this list.
996 c ipjan iwork(24) the base address of the structure descriptor array
997 c jan, described below in this list.
999 c nzl iwork(25) the number of nonzero elements in the strict lower
1000 c triangle of the lu factorization used in the chord
1001 c iteration (miter = 1 or 2).
1003 c nzu iwork(26) the number of nonzero elements in the strict upper
1004 c triangle of the lu factorization used in the chord
1005 c iteration (miter = 1 or 2).
1006 c the total number of nonzeros in the factorization
1007 c is therefore nzl + nzu + neq.
1009 c the following four arrays are segments of the rwork array which
1010 c may also be of interest to the user as optional outputs.
1011 c for each array, the table below gives its internal name,
1012 c its base address, and its description.
1013 c for yh and acor, the base addresses are in rwork (a real array).
1014 c the integer arrays ian and jan are to be obtained by declaring an
1015 c integer array iwk and identifying iwk(1) with rwork(21), using either
1016 c an equivalence statement or a subroutine call. then the base
1017 c addresses ipian (of ian) and ipjan (of jan) in iwk are to be obtained
1018 c as optional outputs iwork(23) and iwork(24), respectively.
1019 c thus ian(1) is iwk(ipian), etc.
1021 c name base address description
1023 c ian ipian (in iwk) structure descriptor array of size neq + 1.
1024 c jan ipjan (in iwk) structure descriptor array of size nnz.
1025 c (see above) ian and jan together describe the sparsity
1026 c structure of the jacobian matrix, as used by
1027 c lsodes when miter = 1 or 2.
1028 c jan contains the row indices of the nonzero
1029 c locations, reading in columnwise order, and
1030 c ian contains the starting locations in jan of
1031 c the descriptions of columns 1,...,neq, in
1032 c that order, with ian(1) = 1. thus for each
1033 c j = 1,...,neq, the row indices i of the
1034 c nonzero locations in column j are
1035 c i = jan(k), ian(j) .le. k .lt. ian(j+1).
1036 c note that ian(neq+1) = nnz + 1.
1037 c (if moss = 0, ian/jan may differ from the
1038 c input ia/ja because of a different ordering
1039 c in each column, and added diagonal entries.)
1041 c yh lyh the nordsieck history array, of size nyh by
1042 c (optional (nqcur + 1), where nyh is the initial value
1043 c output) of neq. for j = 0,1,...,nqcur, column j+1
1044 c of yh contains hcur**j/factorial(j) times
1045 c the j-th derivative of the interpolating
1046 c polynomial currently representing the solution,
1047 c evaluated at t = tcur. the base address lyh
1048 c is another optional output, listed above.
1050 c acor lenrw-neq+1 array of size neq used for the accumulated
1051 c corrections on each step, scaled on output
1052 c to represent the estimated local error in y
1053 c on the last step. this is the vector e in
1054 c the description of the error control. it is
1055 c defined only on a successful return from
1058 c-----------------------------------------------------------------------
1059 c part ii. other routines callable.
1061 c the following are optional calls which the user may make to
1062 c gain additional capabilities in conjunction with lsodes.
1063 c (the routines xsetun and xsetf are designed to conform to the
1064 c slatec error handling package.)
1066 c form of CALL function
1067 c CALL xsetun(lun) set the logical unit number, lun, for
1068 c output of messages from lsodes, if
1069 c the default is not desired.
1070 c the default value of lun is 6.
1072 c CALL xsetf(mflag) set a flag to control the printing of
1073 c messages by lsodes.
1074 c mflag = 0 means do not print. (danger..
1075 c this risks losing valuable information.)
1076 c mflag = 1 means print (the default).
1078 c either of the above calls may be made at
1079 c any time and will take effect immediately.
1081 c CALL srcms(rsav,isav,job) saves and restores the contents of
1082 c the internal common blocks used by
1083 c lsodes (see part iii below).
1084 c rsav must be a real array of length 224
1085 c or more, and isav must be an integer
1086 c array of length 75 or more.
1087 c job=1 means save common into rsav/isav.
1088 c job=2 means restore common from rsav/isav.
1089 c srcms is useful if one is
1090 c interrupting a run and restarting
1091 c later, or alternating between two or
1092 c more problems solved with lsodes.
1094 c CALL intdy(,,,,,) provide derivatives of y, of various
1095 c (see below) orders, at a specified point t, if
1096 c desired. it may be called only after
1097 c a successful return from lsodes.
1099 c the detailed instructions for using intdy are as follows.
1100 c the form of the CALL is..
1103 c CALL intdy (t, k, rwork(lyh), nyh, dky, iflag)
1105 c the input parameters are..
1107 c t = value of independent variable where answers are desired
1108 c (normally the same as the t last returned by lsodes).
1109 c for valid results, t must lie between tcur - hu and tcur.
1110 c (see optional outputs for tcur and hu.)
1111 c k = integer order of the derivative desired. k must satisfy
1112 c 0 .le. k .le. nqcur, where nqcur is the current order
1113 c (see optional outputs). the capability corresponding
1114 c to k = 0, i.e. computing y(t), is already provided
1115 c by lsodes directly. since nqcur .ge. 1, the first
1116 c derivative dy/dt is always available with intdy.
1117 c lyh = the base address of the history array yh, obtained
1118 c as an optional output as shown above.
1119 c nyh = column length of yh, equal to the initial value of neq.
1121 c the output parameters are..
1123 c dky = a real array of length neq containing the computed value
1124 c of the k-th derivative of y(t).
1125 c iflag = integer flag, returned as 0 if k and t were legal,
1126 c -1 if k was illegal, and -2 if t was illegal.
1127 c on an error return, a message is also written.
1128 c-----------------------------------------------------------------------
1129 c part iii. common blocks.
1131 c if lsodes is to be used in an overlay situation, the user
1132 c must declare, in the primary overlay, the variables in..
1133 c (1) the CALL sequence to lsodes,
1134 c (2) the three internal common blocks
1135 c /ls0001/ of length 257 (218 KPP_REAL words
1136 c followed by 39 integer words),
1137 c /lss001/ of length 40 ( 6 KPP_REAL words
1138 c followed by 34 integer words),
1139 c /eh0001/ of length 2 (integer words).
1141 c if lsodes is used on a system in which the contents of internal
1142 c common blocks are not preserved between calls, the user should
1143 c declare the above three common blocks in his main program to insure
1144 c that their contents are preserved.
1146 c if the solution of a given problem by lsodes is to be interrupted
1147 c and then later continued, such as when restarting an interrupted run
1148 c or alternating between two or more problems, the user should save,
1149 c following the return from the last lsodes CALL prior to the
1150 c interruption, the contents of the CALL sequence variables and the
1151 c internal common blocks, and later restore these values before the
1152 c next lsodes CALL for that problem. to save and restore the common
1153 c blocks, use subroutine srcms (see part ii above).
1155 c-----------------------------------------------------------------------
1156 c part iv. optionally replaceable solver routines.
1158 c below are descriptions of two routines in the lsodes package which
1159 c relate to the measurement of errors. either routine can be
1160 c replaced by a user-supplied version, if desired. however, since such
1161 c a replacement may have a major impact on performance, it should be
1162 c done only when absolutely necessary, and only with great caution.
1163 c (note.. the means by which the package version of a routine is
1164 c superseded by the user-s version may be system-dependent.)
1167 c the following subroutine is called just before each internal
1168 c integration step, and sets the array of error weights, ewt, as
1169 c described under itol/RelTol/AbsTol above..
1170 c subroutine ewset (neq, itol, RelTol, AbsTol, ycur, ewt)
1171 c where neq, itol, RelTol, and AbsTol are as in the lsodes CALL sequence,
1172 c ycur contains the current dependent variable vector, and
1173 c ewt is the array of weights set by ewset.
1175 c if the user supplies this subroutine, it must return in ewt(i)
1176 c (i = 1,...,neq) a positive quantity suitable for comparing errors
1177 c in y(i) to. the ewt array returned by ewset is passed to the
1178 c vnorm routine (see below), and also used by lsodes in the computation
1179 c of the optional output imxer, the diagonal jacobian approximation,
1180 c and the increments for difference quotient jacobians.
1182 c in the user-supplied version of ewset, it may be desirable to use
1183 c the current values of derivatives of y. derivatives up to order nq
1184 c are available from the history array yh, described above under
1185 c optional outputs. in ewset, yh is identical to the ycur array,
1186 c extended to nq + 1 columns with a column length of nyh and scale
1187 c factors of h**j/factorial(j). on the first CALL for the problem,
1188 c given by nst = 0, nq is 1 and h is temporarily set to 1.0.
1189 c the quantities nq, nyh, h, and nst can be obtained by including
1190 c in ewset the statements..
1192 c common /ls0001/ rls(218),ils(39)
1197 c thus, for example, the current value of dy/dt can be obtained as
1198 c ycur(nyh+i)/h (i=1,...,neq) (and the division by h is
1199 c unnecessary when nst = 0).
1202 c the following is a real function routine which computes the weighted
1203 c root-mean-square norm of a vector v..
1204 c d = vnorm (n, v, w)
1206 c n = the length of the vector,
1207 c v = real array of length n containing the vector,
1208 c w = real array of length n containing weights,
1209 c d = sqrt( (1/n) * sum(v(i)*w(i))**2 ).
1210 c vnorm is called with n = neq and with w(i) = 1.0/ewt(i), where
1211 c ewt is as set by subroutine ewset.
1213 c if the user supplies this function, it should return a non-negative
1214 c value of vnorm suitable for use in the error control in lsodes.
1215 c none of the arguments should be altered by vnorm.
1216 c for example, a user-supplied vnorm routine might..
1217 c -substitute a max-norm of (v(i)*w(i)) for the rms-norm, or
1218 c -ignore some components of v in the norm, with the effect of
1219 c suppressing the error control on those components of y.
1220 c-----------------------------------------------------------------------
1221 c-----------------------------------------------------------------------
1222 c other routines in the lsodes package.
1224 c in addition to subroutine lsodes, the lsodes package includes the
1225 c following subroutines and function routines..
1226 c iprep acts as an iterface between lsodes and prep, and also does
1227 c adjusting of work space pointers and work arrays.
1228 c prep is called by iprep to compute sparsity and do sparse matrix
1229 c preprocessing if miter = 1 or 2.
1230 c jgroup is called by prep to compute groups of jacobian column
1231 c indices for use when miter = 2.
1232 c adjlr adjusts the length of required sparse matrix work space.
1233 c it is called by prep.
1234 c cntnzu is called by prep and counts the nonzero elements in the
1235 c strict upper triangle of j + j-transpose, where j = df/dy.
1236 c intdy computes an interpolated value of the y vector at t = tout.
1237 c stode is the core integrator, which does one step of the
1238 c integration and the associated error control.
1239 c cfode sets all method coefficients and test constants.
1240 c prjs computes and preprocesses the jacobian matrix j = df/dy
1241 c and the newton iteration matrix p = i - h*l0*j.
1242 c slss manages solution of linear system in chord iteration.
1243 c ewset sets the error weight vector ewt before each step.
1244 c vnorm computes the weighted r.m.s. norm of a vector.
1245 c srcms is a user-callable routine to save and restore
1246 c the contents of the internal common blocks.
1247 c odrv constructs a reordering of the rows and columns of
1248 c a matrix by the minimum degree algorithm. odrv is a
1249 c driver routine which calls subroutines md, mdi, mdm,
1250 c mdp, mdu, and sro. see ref. 2 for details. (the odrv
1251 c module has been modified since ref. 2, however.)
1252 c cdrv performs reordering, symbolic factorization, numerical
1253 c factorization, or linear system solution operations,
1254 c depending on a path argument ipath. cdrv is a
1255 c driver routine which calls subroutines nroc, nsfc,
1256 c nnfc, nnsc, and nntc. see ref. 3 for details.
1257 c lsodes uses cdrv to solve linear systems in which the
1258 c coefficient matrix is p = i - con*j, where i is the
1259 c identity, con is a scalar, and j is an approximation to
1260 c the jacobian df/dy. because cdrv deals with rowwise
1261 c sparsity descriptions, cdrv works with p-transpose, not p.
1262 c d1mach computes the unit roundoff in a machine-independent manner.
1263 c xerrwv, xsetun, and xsetf handle the printing of all error
1264 c messages and warnings. xerrwv is machine-dependent.
1265 c note.. vnorm and d1mach are function routines.
1266 c all the others are subroutines.
1268 c the intrinsic and external routines used by lsodes are..
1269 c dabs, DMAX1, dmin1, dfloat, max0, min0, mod, DSIGN, DSQRT, and write.
1271 c a block data subprogram is also included with the package,
1272 c for loading some of the variables in internal common.
1274 c-----------------------------------------------------------------------
1275 c the following card is for optimized compilation on lll compilers.
1277 c-----------------------------------------------------------------------
1279 integer illin
, init
, lyh
, lewt
, lacor
, lsavf
, lwm
, liwm
,
1280 1 mxstep
, mxhnil
, nhnil
, ntrep
, nslast
, nyh
, iowns
1281 integer icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
1282 1 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
1283 integer iplost
, iesp
, istatc
, iys
, iba
, ibian
, ibjan
, ibjgp
,
1284 1 ipian
, ipjan
, ipjgp
, ipigp
, ipr
, ipc
, ipic
, ipisp
, iprsp
, ipa
,
1285 2 lenyh
, lenyhm
, lenwk
, lreq
, lrat
, lrest
, lwmin
, moss
, msbj
,
1286 3 nslj
, ngp
, nlu
, nnz
, nsp
, nzl
, nzu
1287 integer i
, i1
, i2
, iflag
, imax
, imul
, imxer
, ipflag
, ipgo
, irem
,
1288 1 j
, kgo
, lenrat
, lenyht
, leniw
, lenrw
, lf0
, lia
, lja
,
1289 2 lrtem
, lwtem
, lyhd
, lyhn
, mf1
, mord
, mxhnl0
, mxstp0
, ncolm
1291 1 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
1292 KPP_REAL con0
, conmin
, ccmxj
, psmall
, rbig
, seth
1293 KPP_REAL AbsToli
, ayi
, big
, ewti
, h0
, hmax
, hmx
, rh
, RelToli
,
1294 1 tcrit
, tdist
, tnext
, tol
, tolsf
, tp
, size
, sum
, w0
,
1298 c-----------------------------------------------------------------------
1299 c the following two internal common blocks contain
1300 c (a) variables which are local to any subroutine but whose values must
1301 c be preserved between calls to the routine (own variables), and
1302 c (b) variables which are communicated between subroutines.
1303 c the structure of each block is as follows.. all real variables are
1304 c listed first, followed by all integers. within each type, the
1305 c variables are grouped with those local to subroutine lsodes first,
1306 c then those local to subroutine stode or subroutine prjs
1307 c (no other routines have own variables), and finally those used
1308 c for communication. the block ls0001 is declared in subroutines
1309 c lsodes, iprep, prep, intdy, stode, prjs, and slss. the block lss001
1310 c is declared in subroutines lsodes, iprep, prep, prjs, and slss.
1311 c groups of variables are replaced by dummy arrays in the common
1312 c declarations in routines where those variables are not used.
1313 c-----------------------------------------------------------------------
1314 common /ls0001
/ rowns
(209),
1315 1 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
,
1316 2 illin
, init
, lyh
, lewt
, lacor
, lsavf
, lwm
, liwm
,
1317 3 mxstep
, mxhnil
, nhnil
, ntrep
, nslast
, nyh
, iowns
(6),
1318 4 icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
1319 5 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
1321 common /lss001
/ con0
, conmin
, ccmxj
, psmall
, rbig
, seth
,
1322 1 iplost
, iesp
, istatc
, iys
, iba
, ibian
, ibjan
, ibjgp
,
1323 2 ipian
, ipjan
, ipjgp
, ipigp
, ipr
, ipc
, ipic
, ipisp
, iprsp
, ipa
,
1324 3 lenyh
, lenyhm
, lenwk
, lreq
, lrat
, lrest
, lwmin
, moss
, msbj
,
1325 4 nslj
, ngp
, nlu
, nnz
, nsp
, nzl
, nzu
1327 data mord
(1),mord
(2)/12,5/, mxstp0
/500/, mxhnl0
/10/
1328 c-----------------------------------------------------------------------
1329 c in the data statement below, set lenrat equal to the ratio of
1330 c the wordlength for a real number to that for an integer. usually,
1331 c lenrat = 1 for single precision and 2 for KPP_REAL. if the
1332 c true ratio is not an integer, use the next smaller integer (.ge. 1).
1333 c-----------------------------------------------------------------------
1335 c-----------------------------------------------------------------------
1337 c this code block is executed on every call.
1338 c it tests istate and itask for legality and branches appropriately.
1339 c if istate .gt. 1 but the flag init shows that initialization has
1340 c not yet been done, an error return occurs.
1341 c if istate = 1 and tout = t, jump to block g and return immediately.
1342 c-----------------------------------------------------------------------
1343 if (istate
.lt
. 1 .or
. istate
.gt
. 3) go to 601
1344 if (itask
.lt
. 1 .or
. itask
.gt
. 5) go to 602
1345 if (istate
.eq
. 1) go to 10
1346 if (init
.eq
. 0) go to 603
1347 if (istate
.eq
. 2) go to 200
1350 if (tout
.eq
. t
) go to 430
1352 c-----------------------------------------------------------------------
1354 c the next code block is executed for the initial CALL (istate = 1),
1355 c or for a continuation CALL with parameter changes (istate = 3).
1356 c it contains checking of all inputs and various initializations.
1357 c if istate = 1, the final setting of work space pointers, the matrix
1358 c preprocessing, and other initializations are done in block c.
1360 c first check legality of the non-optional inputs neq, itol, iopt,
1362 c-----------------------------------------------------------------------
1363 if (neq
(1) .le
. 0) go to 604
1364 if (istate
.eq
. 1) go to 25
1365 if (neq
(1) .gt
. n
) go to 605
1367 if (itol
.lt
. 1 .or
. itol
.gt
. 4) go to 606
1368 if (iopt
.lt
. 0 .or
. iopt
.gt
. 1) go to 607
1372 miter
= mf1
- 10*meth
1373 if (moss
.lt
. 0 .or
. moss
.gt
. 2) go to 608
1374 if (meth
.lt
. 1 .or
. meth
.gt
. 2) go to 608
1375 if (miter
.lt
. 0 .or
. miter
.gt
. 3) go to 608
1376 if (miter
.eq
. 0 .or
. miter
.eq
. 3) moss
= 0
1377 c next process and check the optional inputs. --------------------------
1378 if (iopt
.eq
. 1) go to 40
1382 if (istate
.eq
. 1) h0
= 0.0d0
1387 40 maxord
= iwork
(5)
1388 if (maxord
.lt
. 0) go to 611
1389 if (maxord
.eq
. 0) maxord
= 100
1390 maxord
= min0
(maxord
,mord
(meth
))
1392 if (mxstep
.lt
. 0) go to 612
1393 if (mxstep
.eq
. 0) mxstep
= mxstp0
1395 if (mxhnil
.lt
. 0) go to 613
1396 if (mxhnil
.eq
. 0) mxhnil
= mxhnl0
1397 if (istate
.ne
. 1) go to 50
1399 if ((tout
- t
)*h0
.lt
. 0.0d0
) go to 614
1401 if (hmax
.lt
. 0.0d0
) go to 615
1403 if (hmax
.gt
. 0.0d0
) hmxi
= 1.0d0
/hmax
1405 if (hmin
.lt
. 0.0d0
) go to 616
1407 if (seth
.lt
. 0.0d0
) go to 609
1408 c check RelTol and AbsTol for legality. ------------------------------------
1409 60 RelToli
= RelTol
(1)
1412 if (itol
.ge
. 3) RelToli
= RelTol
(i
)
1413 if (itol
.eq
. 2 .or
. itol
.eq
. 4) AbsToli
= AbsTol
(i
)
1414 if (RelToli
.lt
. 0.0d0
) go to 619
1415 if (AbsToli
.lt
. 0.0d0
) go to 620
1417 c-----------------------------------------------------------------------
1418 c compute required work array lengths, as far as possible, and test
1419 c these against lrw and liw. then set tentative pointers for work
1420 c arrays. pointers to rwork/iwork segments are named by prefixing l to
1421 c the name of the segment. e.g., the segment yh starts at rwork(lyh).
1422 c segments of rwork (in order) are denoted wm, yh, savf, ewt, acor.
1423 c if miter = 1 or 2, the required length of the matrix work space wm
1424 c is not yet known, and so a crude minimum value is used for the
1425 c initial tests of lrw and liw, and yh is temporarily stored as far
1426 c to the right in rwork as possible, to leave the maximum amount
1427 c of space for wm for matrix preprocessing. thus if miter = 1 or 2
1428 c and moss .ne. 2, some of the segments of rwork are temporarily
1429 c omitted, as they are not needed in the preprocessing. these
1430 c omitted segments are.. acor if istate = 1, ewt and acor if istate = 3
1431 c and moss = 1, and savf, ewt, and acor if istate = 3 and moss = 0.
1432 c-----------------------------------------------------------------------
1434 if (istate
.eq
. 1) nyh
= n
1436 if (miter
.eq
. 1) lwmin
= 4*n
+ 10*n
/lrat
1437 if (miter
.eq
. 2) lwmin
= 4*n
+ 11*n
/lrat
1438 if (miter
.eq
. 3) lwmin
= n
+ 2
1439 lenyh
= (maxord
+1)*nyh
1441 lenrw
= 20 + lwmin
+ lrest
1444 if (moss
.eq
. 0 .and
. miter
.ne
. 0 .and
. miter
.ne
. 3)
1445 1 leniw
= leniw
+ n
+ 1
1447 if (lenrw
.gt
. lrw
) go to 617
1448 if (leniw
.gt
. liw
) go to 618
1450 if (moss
.eq
. 0 .and
. miter
.ne
. 0 .and
. miter
.ne
. 3)
1451 1 leniw
= leniw
+ iwork
(lia
+n
) - 1
1453 if (leniw
.gt
. liw
) go to 618
1458 if (istate
.eq
. 1) nq
= 1
1459 ncolm
= min0
(nq
+1,maxord
+2)
1462 if (miter
.eq
. 1 .or
. miter
.eq
. 2) lenyht
= lenyhm
1464 if (istate
.eq
. 3) imul
= moss
1465 if (moss
.eq
. 2) imul
= 3
1466 lrtem
= lenyht
+ imul*n
1468 if (miter
.eq
. 1 .or
. miter
.eq
. 2) lwtem
= lrw
- 20 - lrtem
1471 lsavf
= lyhn
+ lenyht
1475 if (istate
.eq
. 1) go to 100
1476 c-----------------------------------------------------------------------
1477 c istate = 3. move yh to its new location.
1478 c note that only the part of yh needed for the next step, namely
1479 c min(nq+1,maxord+2) columns, is actually moved.
1480 c a temporary error weight array ewt is loaded if moss = 2.
1481 c sparse matrix processing is done in iprep/prep if miter = 1 or 2.
1482 c if maxord was reduced below nq, then the pointers are finally set
1483 c so that savf is identical to yh(*,maxord+2).
1484 c-----------------------------------------------------------------------
1486 imax
= lyhn
- 1 + lenyhm
1487 c move yh. branch for move right, no move, or move left. --------------
1489 70 do 72 i
= lyhn
,imax
1491 72 rwork
(j
) = rwork
(j
+lyhd
)
1493 74 do 76 i
= lyhn
,imax
1494 76 rwork
(i
) = rwork
(i
+lyhd
)
1497 if (miter
.eq
. 0 .or
. miter
.eq
. 3) go to 92
1498 if (moss
.ne
. 2) go to 85
1499 c temporarily load ewt if miter = 1 or 2 and moss = 2. -----------------
1500 CALL ewset
(n
, itol
, RelTol
, AbsTol
, rwork
(lyh
), rwork
(lewt
))
1502 if (rwork
(i
+lewt
-1) .le
. 0.0d0
) go to 621
1503 82 rwork
(i
+lewt
-1) = 1.0d0
/rwork
(i
+lewt
-1)
1505 c iprep and prep do sparse matrix preprocessing if miter = 1 or 2. -----
1506 lsavf
= min0
(lsavf
,lrw
)
1507 lewt
= min0
(lewt
,lrw
)
1508 lacor
= min0
(lacor
,lrw
)
1509 CALL iprep
(neq
, y
, rwork
, iwork
(lia
), iwork
(lja
), ipflag
, f
, jac
)
1510 lenrw
= lwm
- 1 + lenwk
+ lrest
1512 if (ipflag
.ne
. -1) iwork
(23) = ipian
1513 if (ipflag
.ne
. -1) iwork
(24) = ipjan
1515 go to (90, 628, 629, 630, 631, 632, 633), ipgo
1517 if (lenrw
.gt
. lrw
) go to 617
1518 c set flag to signal parameter changes to stode. -----------------------
1520 if (n
.eq
. nyh
) go to 200
1521 c neq was reduced. zero part of yh to avoid undefined references. -----
1523 i2
= lyh
+ (maxord
+ 1)*nyh
- 1
1524 if (i1
.gt
. i2
) go to 200
1528 c-----------------------------------------------------------------------
1530 c the next block is for the initial CALL only (istate = 1).
1531 c it contains all remaining initializations, the initial CALL to f,
1532 c the sparse matrix preprocessing (miter = 1 or 2), and the
1533 c calculation of the initial step size.
1534 c the error weights in ewt are inverted after being loaded.
1535 c-----------------------------------------------------------------------
1546 c load the initial value vector in yh. ---------------------------------
1548 105 rwork
(i
+lyh
-1) = y
(i
)
1549 c initial CALL to f. (lf0 points to yh(*,2).) -------------------------
1551 CALL f
(neq
, t
, y
, rwork
(lf0
))
1553 c load and invert the ewt array. (h is temporarily set to 1.0.) -------
1554 CALL ewset
(n
, itol
, RelTol
, AbsTol
, rwork
(lyh
), rwork
(lewt
))
1556 if (rwork
(i
+lewt
-1) .le
. 0.0d0
) go to 621
1557 110 rwork
(i
+lewt
-1) = 1.0d0
/rwork
(i
+lewt
-1)
1558 if (miter
.eq
. 0 .or
. miter
.eq
. 3) go to 120
1559 c iprep and prep do sparse matrix preprocessing if miter = 1 or 2. -----
1560 lacor
= min0
(lacor
,lrw
)
1561 CALL iprep
(neq
, y
, rwork
, iwork
(lia
), iwork
(lja
), ipflag
, f
, jac
)
1562 lenrw
= lwm
- 1 + lenwk
+ lrest
1564 if (ipflag
.ne
. -1) iwork
(23) = ipian
1565 if (ipflag
.ne
. -1) iwork
(24) = ipjan
1567 go to (115, 628, 629, 630, 631, 632, 633), ipgo
1569 if (lenrw
.gt
. lrw
) go to 617
1570 c check tcrit for legality (itask = 4 or 5). ---------------------------
1572 if (itask
.ne
. 4 .and
. itask
.ne
. 5) go to 125
1574 if ((tcrit
- tout
)*(tout
- t
) .lt
. 0.0d0
) go to 625
1575 if (h0
.ne
. 0.0d0
.and
. (t
+ h0
- tcrit
)*h0
.gt
. 0.0d0
)
1577 c initialize all remaining parameters. ---------------------------------
1578 125 uround
= d1mach
(4)
1580 if (miter
.ne
. 0) rwork
(lwm
) = DSQRT
(uround
)
1584 psmall
= 1000.0d0*uround
1585 rbig
= 0.01d0
/psmall
1596 c-----------------------------------------------------------------------
1597 c the coding below computes the step size, h0, to be attempted on the
1598 c first step, unless the user has supplied a value for this.
1599 c first check that tout - t differs significantly from zero.
1600 c a scalar tolerance quantity tol is computed, as max(RelTol(i))
1601 c if this is positive, or max(AbsTol(i)/abs(y(i))) otherwise, adjusted
1602 c so as to be between 100*uround and 1.0e-3.
1603 c then the computed value h0 is given by..
1605 c h0**2 = tol / ( w0**-2 + (1/neq) * sum ( f(i)/ywt(i) )**2 )
1607 c where w0 = max ( abs(t), abs(tout) ),
1608 c f(i) = i-th component of initial value of f,
1609 c ywt(i) = ewt(i)/tol (a weight for y(i)).
1610 c the sign of h0 is inferred from the initial values of tout and t.
1611 c-----------------------------------------------------------------------
1613 if (h0
.ne
. 0.0d0
) go to 180
1614 tdist
= dabs
(tout
- t
)
1615 w0
= DMAX1
(dabs
(t
),dabs
(tout
))
1616 if (tdist
.lt
. 2.0d0*uround*w0
) go to 622
1618 if (itol
.le
. 2) go to 140
1620 130 tol
= DMAX1
(tol
,RelTol
(i
))
1621 140 if (tol
.gt
. 0.0d0
) go to 160
1624 if (itol
.eq
. 2 .or
. itol
.eq
. 4) AbsToli
= AbsTol
(i
)
1626 if (ayi
.ne
. 0.0d0
) tol
= DMAX1
(tol
,AbsToli
/ayi
)
1628 160 tol
= DMAX1
(tol
,100.0d0*uround
)
1629 tol
= dmin1
(tol
,0.001d0
)
1630 sum
= vnorm
(n
, rwork
(lf0
), rwork
(lewt
))
1631 sum
= 1.0d0
/(tol*w0*w0
) + tol*sum**2
1632 h0
= 1.0d0
/DSQRT
(sum
)
1633 h0
= dmin1
(h0
,tdist
)
1634 h0
= DSIGN
(h0
,tout
-t
)
1635 c adjust h0 if necessary to meet hmax bound. ---------------------------
1636 180 rh
= dabs
(h0
)*hmxi
1637 if (rh
.gt
. 1.0d0
) h0
= h0
/rh
1638 c load h with h0 and scale yh(*,2) by h0. ------------------------------
1641 190 rwork
(i
+lf0
-1) = h0*rwork
(i
+lf0
-1)
1643 c-----------------------------------------------------------------------
1645 c the next code block is for continuation calls only (istate = 2 or 3)
1646 c and is to check stop conditions before taking a step.
1647 c-----------------------------------------------------------------------
1649 go to (210, 250, 220, 230, 240), itask
1650 210 if ((tn
- tout
)*h
.lt
. 0.0d0
) go to 250
1651 CALL intdy
(tout
, 0, rwork
(lyh
), nyh
, y
, iflag
)
1652 if (iflag
.ne
. 0) go to 627
1655 220 tp
= tn
- hu*
(1.0d0
+ 100.0d0*uround
)
1656 if ((tp
- tout
)*h
.gt
. 0.0d0
) go to 623
1657 if ((tn
- tout
)*h
.lt
. 0.0d0
) go to 250
1659 230 tcrit
= rwork
(1)
1660 if ((tn
- tcrit
)*h
.gt
. 0.0d0
) go to 624
1661 if ((tcrit
- tout
)*h
.lt
. 0.0d0
) go to 625
1662 if ((tn
- tout
)*h
.lt
. 0.0d0
) go to 245
1663 CALL intdy
(tout
, 0, rwork
(lyh
), nyh
, y
, iflag
)
1664 if (iflag
.ne
. 0) go to 627
1667 240 tcrit
= rwork
(1)
1668 if ((tn
- tcrit
)*h
.gt
. 0.0d0
) go to 624
1669 245 hmx
= dabs
(tn
) + dabs
(h
)
1670 ihit
= dabs
(tn
- tcrit
) .le
. 100.0d0*uround*hmx
1672 tnext
= tn
+ h*
(1.0d0
+ 4.0d0*uround
)
1673 if ((tnext
- tcrit
)*h
.le
. 0.0d0
) go to 250
1674 h
= (tcrit
- tn
)*(1.0d0
- 4.0d0*uround
)
1675 if (istate
.eq
. 2) jstart
= -2
1676 c-----------------------------------------------------------------------
1678 c the next block is normally executed for all calls and contains
1679 c the CALL to the one-step core integrator stode.
1681 c this is a looping point for the integration steps.
1683 c first check for too many steps being taken, update ewt (if not at
1684 c start of problem), check for too much accuracy being requested, and
1685 c check for h below the roundoff level in t.
1686 c-----------------------------------------------------------------------
1688 if ((nst
-nslast
) .ge
. mxstep
) go to 500
1689 CALL ewset
(n
, itol
, RelTol
, AbsTol
, rwork
(lyh
), rwork
(lewt
))
1691 if (rwork
(i
+lewt
-1) .le
. 0.0d0
) go to 510
1692 260 rwork
(i
+lewt
-1) = 1.0d0
/rwork
(i
+lewt
-1)
1693 270 tolsf
= uround*vnorm
(n
, rwork
(lyh
), rwork
(lewt
))
1694 if (tolsf
.le
. 1.0d0
) go to 280
1696 if (nst
.eq
. 0) go to 626
1698 280 if ((tn
+ h
) .ne
. tn
) go to 290
1700 if (nhnil
.gt
. mxhnil
) go to 290
1701 CALL xerrwv
(50hlsodes
-- warning
..internal t
(=r1
) and h
(=r2
) are
,
1702 1 50, 101, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1704 1 60h such that in the machine
, t
+ h
= t on the next step
,
1705 1 60, 101, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1706 CALL xerrwv
(50h
(h
= step size
). solver will
continue anyway
,
1707 1 50, 101, 0, 0, 0, 0, 2, tn
, h
)
1708 if (nhnil
.lt
. mxhnil
) go to 290
1709 CALL xerrwv
(50hlsodes
-- above warning has been issued i1 times
. ,
1710 1 50, 102, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1711 CALL xerrwv
(50h it will not be issued again
for this problem
,
1712 1 50, 102, 0, 1, mxhnil
, 0, 0, 0.0d0
, 0.0d0
)
1714 c-----------------------------------------------------------------------
1715 c CALL stode(neq,y,yh,nyh,yh,ewt,savf,acor,wm,wm,f,jac,prjs,slss)
1716 c-----------------------------------------------------------------------
1717 CALL stode
(neq
, y
, rwork
(lyh
), nyh
, rwork
(lyh
), rwork
(lewt
),
1718 1 rwork
(lsavf
), rwork
(lacor
), rwork
(lwm
), rwork
(lwm
),
1719 2 f
, jac
, prjs
, slss
)
1721 go to (300, 530, 540, 550), kgo
1722 c-----------------------------------------------------------------------
1724 c the following block handles the case of a successful return from the
1725 c core integrator (kflag = 0). test for stop conditions.
1726 c-----------------------------------------------------------------------
1728 go to (310, 400, 330, 340, 350), itask
1729 c itask = 1. if tout has been reached, interpolate. -------------------
1730 310 if ((tn
- tout
)*h
.lt
. 0.0d0
) go to 250
1731 CALL intdy
(tout
, 0, rwork
(lyh
), nyh
, y
, iflag
)
1734 c itask = 3. jump to exit if tout was reached. ------------------------
1735 330 if ((tn
- tout
)*h
.ge
. 0.0d0
) go to 400
1737 c itask = 4. see if tout or tcrit was reached. adjust h if necessary.
1738 340 if ((tn
- tout
)*h
.lt
. 0.0d0
) go to 345
1739 CALL intdy
(tout
, 0, rwork
(lyh
), nyh
, y
, iflag
)
1742 345 hmx
= dabs
(tn
) + dabs
(h
)
1743 ihit
= dabs
(tn
- tcrit
) .le
. 100.0d0*uround*hmx
1745 tnext
= tn
+ h*
(1.0d0
+ 4.0d0*uround
)
1746 if ((tnext
- tcrit
)*h
.le
. 0.0d0
) go to 250
1747 h
= (tcrit
- tn
)*(1.0d0
- 4.0d0*uround
)
1750 c itask = 5. see if tcrit was reached and jump to exit. ---------------
1751 350 hmx
= dabs
(tn
) + dabs
(h
)
1752 ihit
= dabs
(tn
- tcrit
) .le
. 100.0d0*uround*hmx
1753 c-----------------------------------------------------------------------
1755 c the following block handles all successful returns from lsodes.
1756 c if itask .ne. 1, y is loaded from yh and t is set accordingly.
1757 c istate is set to 2, the illegal input counter is zeroed, and the
1758 c optional outputs are loaded into the work arrays before returning.
1759 c if istate = 1 and tout = t, there is a return with no action taken,
1760 c except that if this has happened repeatedly, the run is terminated.
1761 c-----------------------------------------------------------------------
1763 410 y
(i
) = rwork
(i
+lyh
-1)
1765 if (itask
.ne
. 4 .and
. itask
.ne
. 5) go to 420
1784 430 ntrep
= ntrep
+ 1
1785 if (ntrep
.lt
. 5) return
1787 1 60hlsodes
-- repeated calls with istate
= 1 and tout
= t
(=r1
) ,
1788 1 60, 301, 0, 0, 0, 0, 1, t
, 0.0d0
)
1790 c-----------------------------------------------------------------------
1792 c the following block handles all unsuccessful returns other than
1793 c those for illegal input. first the error message routine is called.
1794 c if there was an error test or convergence test failure, imxer is set.
1795 c then y is loaded from yh, t is set to tn, and the illegal input
1796 c counter illin is set to 0. the optional outputs are loaded into
1797 c the work arrays before returning.
1798 c-----------------------------------------------------------------------
1799 c the maximum number of steps was taken before reaching tout. ----------
1800 500 CALL xerrwv
(50hlsodes
-- at current t
(=r1
), mxstep
(=i1
) steps
,
1801 1 50, 201, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1802 CALL xerrwv
(50h taken on this
CALL before reaching tout
,
1803 1 50, 201, 0, 1, mxstep
, 0, 1, tn
, 0.0d0
)
1806 c ewt(i) .le. 0.0 for some i (not at start of problem). ----------------
1807 510 ewti
= rwork
(lewt
+i
-1)
1808 CALL xerrwv
(50hlsodes
-- at t
(=r1
), ewt
(i1
) has become r2
.le
. 0.,
1809 1 50, 202, 0, 1, i
, 0, 2, tn
, ewti
)
1812 c too much accuracy requested for machine precision. -------------------
1813 520 CALL xerrwv
(50hlsodes
-- at t
(=r1
), too much accuracy requested
,
1814 1 50, 203, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1815 CALL xerrwv
(50h
for precision of machine
.. see tolsf
(=r2
) ,
1816 1 50, 203, 0, 0, 0, 0, 2, tn
, tolsf
)
1820 c kflag = -1. error test failed repeatedly or with abs(h) = hmin. -----
1821 530 CALL xerrwv
(50hlsodes
-- at t
(=r1
) and step size h
(=r2
), the error
,
1822 1 50, 204, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1823 CALL xerrwv
(50h test failed repeatedly or with abs
(h
) = hmin
,
1824 1 50, 204, 0, 0, 0, 0, 2, tn
, h
)
1827 c kflag = -2. convergence failed repeatedly or with abs(h) = hmin. ----
1828 540 CALL xerrwv
(50hlsodes
-- at t
(=r1
) and step size h
(=r2
), the
,
1829 1 50, 205, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1830 CALL xerrwv
(50h corrector convergence failed repeatedly
,
1831 1 50, 205, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1832 CALL xerrwv
(30h or with abs
(h
) = hmin
,
1833 1 30, 205, 0, 0, 0, 0, 2, tn
, h
)
1836 c kflag = -3. fatal error flag returned by prjs or slss (cdrv). -------
1837 550 CALL xerrwv
(50hlsodes
-- at t
(=r1
) and step size h
(=r2
), a fatal
,
1838 1 50, 207, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1839 CALL xerrwv
(50h error flag was returned by cdrv
(by way of
,
1840 1 50, 207, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1841 CALL xerrwv
(30h
subroutine prjs or slss
),
1842 1 30, 207, 0, 0, 0, 0, 2, tn
, h
)
1845 c compute imxer if relevant. -------------------------------------------
1849 size
= dabs
(rwork
(i
+lacor
-1)*rwork
(i
+lewt
-1))
1850 if (big
.ge
. size
) go to 570
1855 c set y vector, t, illin, and optional outputs. ------------------------
1857 590 y
(i
) = rwork
(i
+lyh
-1)
1874 c-----------------------------------------------------------------------
1876 c the following block handles all error returns due to illegal input
1877 c (istate = -3), as detected before calling the core integrator.
1878 c first the error message routine is called. then if there have been
1879 c 5 consecutive such returns just before this CALL to the solver,
1880 c the run is halted.
1881 c-----------------------------------------------------------------------
1882 601 CALL xerrwv
(30hlsodes
-- istate
(=i1
) illegal
,
1883 1 30, 1, 0, 1, istate
, 0, 0, 0.0d0
, 0.0d0
)
1885 602 CALL xerrwv
(30hlsodes
-- itask
(=i1
) illegal
,
1886 1 30, 2, 0, 1, itask
, 0, 0, 0.0d0
, 0.0d0
)
1888 603 CALL xerrwv
(50hlsodes
-- istate
.gt
. 1 but lsodes not initialized
,
1889 1 50, 3, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1891 604 CALL xerrwv
(30hlsodes
-- neq
(=i1
) .lt
. 1 ,
1892 1 30, 4, 0, 1, neq
(1), 0, 0, 0.0d0
, 0.0d0
)
1894 605 CALL xerrwv
(50hlsodes
-- istate
= 3 and neq increased
(i1
to i2
) ,
1895 1 50, 5, 0, 2, n
, neq
(1), 0, 0.0d0
, 0.0d0
)
1897 606 CALL xerrwv
(30hlsodes
-- itol
(=i1
) illegal
,
1898 1 30, 6, 0, 1, itol
, 0, 0, 0.0d0
, 0.0d0
)
1900 607 CALL xerrwv
(30hlsodes
-- iopt
(=i1
) illegal
,
1901 1 30, 7, 0, 1, iopt
, 0, 0, 0.0d0
, 0.0d0
)
1903 608 CALL xerrwv
(30hlsodes
-- mf
(=i1
) illegal
,
1904 1 30, 8, 0, 1, mf
, 0, 0, 0.0d0
, 0.0d0
)
1906 609 CALL xerrwv
(30hlsodes
-- seth
(=r1
) .lt
. 0.0 ,
1907 1 30, 9, 0, 0, 0, 0, 1, seth
, 0.0d0
)
1909 611 CALL xerrwv
(30hlsodes
-- maxord
(=i1
) .lt
. 0 ,
1910 1 30, 11, 0, 1, maxord
, 0, 0, 0.0d0
, 0.0d0
)
1912 612 CALL xerrwv
(30hlsodes
-- mxstep
(=i1
) .lt
. 0 ,
1913 1 30, 12, 0, 1, mxstep
, 0, 0, 0.0d0
, 0.0d0
)
1915 613 CALL xerrwv
(30hlsodes
-- mxhnil
(=i1
) .lt
. 0 ,
1916 1 30, 13, 0, 1, mxhnil
, 0, 0, 0.0d0
, 0.0d0
)
1918 614 CALL xerrwv
(40hlsodes
-- tout
(=r1
) behind t
(=r2
) ,
1919 1 40, 14, 0, 0, 0, 0, 2, tout
, t
)
1920 CALL xerrwv
(50h integration direction is given by h0
(=r1
) ,
1921 1 50, 14, 0, 0, 0, 0, 1, h0
, 0.0d0
)
1923 615 CALL xerrwv
(30hlsodes
-- hmax
(=r1
) .lt
. 0.0 ,
1924 1 30, 15, 0, 0, 0, 0, 1, hmax
, 0.0d0
)
1926 616 CALL xerrwv
(30hlsodes
-- hmin
(=r1
) .lt
. 0.0 ,
1927 1 30, 16, 0, 0, 0, 0, 1, hmin
, 0.0d0
)
1929 617 CALL xerrwv
(50hlsodes
-- rwork length is insufficient
to proceed
. ,
1930 1 50, 17, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1932 1 60h length needed is
.ge
. lenrw
(=i1
), exceeds lrw
(=i2
),
1933 1 60, 17, 0, 2, lenrw
, lrw
, 0, 0.0d0
, 0.0d0
)
1935 618 CALL xerrwv
(50hlsodes
-- iwork length is insufficient
to proceed
. ,
1936 1 50, 18, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1938 1 60h length needed is
.ge
. leniw
(=i1
), exceeds liw
(=i2
),
1939 1 60, 18, 0, 2, leniw
, liw
, 0, 0.0d0
, 0.0d0
)
1941 619 CALL xerrwv
(40hlsodes
-- RelTol
(i1
) is r1
.lt
. 0.0 ,
1942 1 40, 19, 0, 1, i
, 0, 1, RelToli
, 0.0d0
)
1944 620 CALL xerrwv
(40hlsodes
-- AbsTol
(i1
) is r1
.lt
. 0.0 ,
1945 1 40, 20, 0, 1, i
, 0, 1, AbsToli
, 0.0d0
)
1947 621 ewti
= rwork
(lewt
+i
-1)
1948 CALL xerrwv
(40hlsodes
-- ewt
(i1
) is r1
.le
. 0.0 ,
1949 1 40, 21, 0, 1, i
, 0, 1, ewti
, 0.0d0
)
1952 1 60hlsodes
-- tout
(=r1
) too close
to t
(=r2
) to start integration
,
1953 1 60, 22, 0, 0, 0, 0, 2, tout
, t
)
1956 1 60hlsodes
-- itask
= i1 and tout
(=r1
) behind tcur
- hu
(= r2
) ,
1957 1 60, 23, 0, 1, itask
, 0, 2, tout
, tp
)
1960 1 60hlsodes
-- itask
= 4 or
5 and tcrit
(=r1
) behind tcur
(=r2
) ,
1961 1 60, 24, 0, 0, 0, 0, 2, tcrit
, tn
)
1964 1 60hlsodes
-- itask
= 4 or
5 and tcrit
(=r1
) behind tout
(=r2
) ,
1965 1 60, 25, 0, 0, 0, 0, 2, tcrit
, tout
)
1967 626 CALL xerrwv
(50hlsodes
-- at start of problem
, too much accuracy
,
1968 1 50, 26, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1970 1 60h requested
for precision of machine
.. see tolsf
(=r1
) ,
1971 1 60, 26, 0, 0, 0, 0, 1, tolsf
, 0.0d0
)
1974 627 CALL xerrwv
(50hlsodes
-- trouble from intdy
. itask
= i1
, tout
= r1
,
1975 1 50, 27, 0, 1, itask
, 0, 1, tout
, 0.0d0
)
1978 1 60hlsodes
-- rwork length insufficient
(for subroutine prep
). ,
1979 1 60, 28, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1981 1 60h length needed is
.ge
. lenrw
(=i1
), exceeds lrw
(=i2
),
1982 1 60, 28, 0, 2, lenrw
, lrw
, 0, 0.0d0
, 0.0d0
)
1985 1 60hlsodes
-- rwork length insufficient
(for subroutine jgroup
). ,
1986 1 60, 29, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1988 1 60h length needed is
.ge
. lenrw
(=i1
), exceeds lrw
(=i2
),
1989 1 60, 29, 0, 2, lenrw
, lrw
, 0, 0.0d0
, 0.0d0
)
1992 1 60hlsodes
-- rwork length insufficient
(for subroutine odrv
). ,
1993 1 60, 30, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
1995 1 60h length needed is
.ge
. lenrw
(=i1
), exceeds lrw
(=i2
),
1996 1 60, 30, 0, 2, lenrw
, lrw
, 0, 0.0d0
, 0.0d0
)
1999 1 60hlsodes
-- error from odrv in yale sparse matrix package
,
2000 1 60, 31, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
2004 1 60h at t
(=r1
), odrv returned error flag
= i1*neq
+ i2
. ,
2005 1 60, 31, 0, 2, imul
, irem
, 1, tn
, 0.0d0
)
2008 1 60hlsodes
-- rwork length insufficient
(for subroutine cdrv
). ,
2009 1 60, 32, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
2011 1 60h length needed is
.ge
. lenrw
(=i1
), exceeds lrw
(=i2
),
2012 1 60, 32, 0, 2, lenrw
, lrw
, 0, 0.0d0
, 0.0d0
)
2015 1 60hlsodes
-- error from cdrv in yale sparse matrix package
,
2016 1 60, 33, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
2020 1 60h at t
(=r1
), cdrv returned error flag
= i1*neq
+ i2
. ,
2021 1 60, 33, 0, 2, imul
, irem
, 1, tn
, 0.0d0
)
2022 if (imul
.eq
. 2) CALL xerrwv
(
2023 1 60h duplicate entry in sparsity structure descriptors
,
2024 1 60, 33, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
2025 if (imul
.eq
. 3 .or
. imul
.eq
. 6) CALL xerrwv
(
2026 1 60h insufficient storage
for nsfc
(called by cdrv
) ,
2027 1 60, 33, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
2029 700 if (illin
.eq
. 5) go to 710
2033 710 CALL xerrwv
(50hlsodes
-- repeated occurrences of illegal input
,
2034 1 50, 302, 0, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
2036 800 CALL xerrwv
(50hlsodes
-- run aborted
.. apparent infinite loop
,
2037 1 50, 303, 2, 0, 0, 0, 0, 0.0d0
, 0.0d0
)
2039 c----------------------- end of subroutine lsodes ----------------------
2041 subroutine iprep
(neq
, y
, rwork
, ia
, ja
, ipflag
, f
, jac
)
2044 integer neq
, ia
, ja
, ipflag
2045 integer illin
, init
, lyh
, lewt
, lacor
, lsavf
, lwm
, liwm
,
2046 1 mxstep
, mxhnil
, nhnil
, ntrep
, nslast
, nyh
, iowns
2047 integer icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
2048 1 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
2049 integer iplost
, iesp
, istatc
, iys
, iba
, ibian
, ibjan
, ibjgp
,
2050 1 ipian
, ipjan
, ipjgp
, ipigp
, ipr
, ipc
, ipic
, ipisp
, iprsp
, ipa
,
2051 2 lenyh
, lenyhm
, lenwk
, lreq
, lrat
, lrest
, lwmin
, moss
, msbj
,
2052 3 nslj
, ngp
, nlu
, nnz
, nsp
, nzl
, nzu
2053 integer i
, imax
, lewtn
, lyhd
, lyhn
2056 1 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
2058 dimension neq
(1), y
(1), rwork
(1), ia
(1), ja
(1)
2059 common /ls0001
/ rowns
(209),
2060 1 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
,
2061 2 illin
, init
, lyh
, lewt
, lacor
, lsavf
, lwm
, liwm
,
2062 3 mxstep
, mxhnil
, nhnil
, ntrep
, nslast
, nyh
, iowns
(6),
2063 4 icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
2064 5 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
2065 common /lss001
/ rlss
(6),
2066 1 iplost
, iesp
, istatc
, iys
, iba
, ibian
, ibjan
, ibjgp
,
2067 2 ipian
, ipjan
, ipjgp
, ipigp
, ipr
, ipc
, ipic
, ipisp
, iprsp
, ipa
,
2068 3 lenyh
, lenyhm
, lenwk
, lreq
, lrat
, lrest
, lwmin
, moss
, msbj
,
2069 4 nslj
, ngp
, nlu
, nnz
, nsp
, nzl
, nzu
2070 c-----------------------------------------------------------------------
2071 c this routine serves as an interface between the driver and
2072 c subroutine prep. it is called only if miter is 1 or 2.
2073 c tasks performed here are..
2075 c * reset the required wm segment length lenwk,
2076 c * move yh back to its final location (following wm in rwork),
2077 c * reset pointers for yh, savf, ewt, and acor, and
2078 c * move ewt to its new position if istate = 1.
2079 c ipflag is an output error indication flag. ipflag = 0 if there was
2080 c no trouble, and ipflag is the value of the prep error flag ipper
2081 c if there was trouble in subroutine prep.
2082 c-----------------------------------------------------------------------
2084 c CALL prep to do matrix preprocessing operations. ---------------------
2085 c CALL prep (neq, y, rwork(lyh), rwork(lsavf), rwork(lewt),
2086 c 1 rwork(lacor), ia, ja, rwork(lwm), rwork(lwm), ipflag, f, jac)
2087 CALL prep
(neq
, y
, rwork
(lyh
), rwork
(lsavf
), rwork
(lewt
),
2088 1 rwork
(lacor
), ia
, ja
, rwork
(lwm
), rwork
(lwm
), ipflag
, f
, jac
)
2089 lenwk
= max0
(lreq
,lwmin
)
2090 if (ipflag
.lt
. 0) return
2091 c if prep was successful, move yh to end of required space for wm. -----
2093 if (lyhn
.gt
. lyh
) return
2095 if (lyhd
.eq
. 0) go to 20
2096 imax
= lyhn
- 1 + lenyhm
2098 10 rwork
(i
) = rwork
(i
+lyhd
)
2100 c reset pointers for savf, ewt, and acor. ------------------------------
2101 20 lsavf
= lyh
+ lenyh
2104 if (istatc
.eq
. 3) go to 40
2105 c if istate = 1, move ewt (left) to its new position. ------------------
2106 if (lewtn
.gt
. lewt
) return
2108 30 rwork
(i
+lewtn
-1) = rwork
(i
+lewt
-1)
2111 c----------------------- end of subroutine iprep -----------------------
2113 subroutine slss
(wk
, iwk
, x
, tem
)
2116 integer iownd
, iowns
,
2117 1 icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
2118 2 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
2119 integer iplost
, iesp
, istatc
, iys
, iba
, ibian
, ibjan
, ibjgp
,
2120 1 ipian
, ipjan
, ipjgp
, ipigp
, ipr
, ipc
, ipic
, ipisp
, iprsp
, ipa
,
2121 2 lenyh
, lenyhm
, lenwk
, lreq
, lrat
, lrest
, lwmin
, moss
, msbj
,
2122 3 nslj
, ngp
, nlu
, nnz
, nsp
, nzl
, nzu
2126 1 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
2128 KPP_REAL di
, hl0
, phl0
, r
2129 dimension wk
(*), iwk
(*), x
(*), tem
(*)
2130 common /ls0001
/ rowns
(209),
2131 2 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
,
2132 3 iownd
(14), iowns
(6),
2133 4 icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
2134 5 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
2135 common /lss001
/ rlss
(6),
2136 1 iplost
, iesp
, istatc
, iys
, iba
, ibian
, ibjan
, ibjgp
,
2137 2 ipian
, ipjan
, ipjgp
, ipigp
, ipr
, ipc
, ipic
, ipisp
, iprsp
, ipa
,
2138 3 lenyh
, lenyhm
, lenwk
, lreq
, lrat
, lrest
, lwmin
, moss
, msbj
,
2139 4 nslj
, ngp
, nlu
, nnz
, nsp
, nzl
, nzu
2140 c-----------------------------------------------------------------------
2141 c this routine manages the solution of the linear system arising from
2142 c a chord iteration. it is called if miter .ne. 0.
2143 c if miter is 1 or 2, it calls cdrv to accomplish this.
2144 c if miter = 3 it updates the coefficient h*el0 in the diagonal
2145 c matrix, and then computes the solution.
2146 c communication with slss uses the following variables..
2147 c wk = real work space containing the inverse diagonal matrix if
2148 c miter = 3 and the lu decomposition of the matrix otherwise.
2149 c storage of matrix elements starts at wk(3).
2150 c wk also contains the following matrix-related data..
2151 c wk(1) = sqrt(uround) (not used here),
2152 c wk(2) = hl0, the previous value of h*el0, used if miter = 3.
2153 c iwk = integer work space for matrix-related data, assumed to
2154 c be equivalenced to wk. in addition, wk(iprsp) and iwk(ipisp)
2155 c are assumed to have identical locations.
2156 c x = the right-hand side vector on input, and the solution vector
2157 c on output, of length n.
2158 c tem = vector of work space of length n, not used in this version.
2159 c iersl = output flag (in common).
2160 c iersl = 0 if no trouble occurred.
2161 c iersl = -1 if cdrv returned an error flag (miter = 1 or 2).
2162 c this should never occur and is considered fatal.
2163 c iersl = 1 if a singular matrix arose with miter = 3.
2164 c this routine also uses other variables in common.
2165 c-----------------------------------------------------------------------
2167 go to (100, 100, 300), miter
2168 100 CALL cdrv
(n
,iwk
(ipr
),iwk
(ipc
),iwk
(ipic
),iwk
(ipian
),iwk
(ipjan
),
2169 1 wk
(ipa
),x
,x
,nsp
,iwk
(ipisp
),wk
(iprsp
),iesp
,4,iersl
)
2170 if (iersl
.ne
. 0) iersl
= -1
2176 if (hl0
.eq
. phl0
) go to 330
2179 di
= 1.0d0
- r*
(1.0d0
- 1.0d0
/wk
(i
+2))
2180 if (dabs
(di
) .eq
. 0.0d0
) go to 390
2181 320 wk
(i
+2) = 1.0d0
/di
2183 340 x
(i
) = wk
(i
+2)*x
(i
)
2188 c----------------------- end of subroutine slss ------------------------
2190 subroutine intdy
(t
, k
, yh
, nyh
, dky
, iflag
)
2192 integer k
, nyh
, iflag
2193 integer iownd
, iowns
,
2194 1 icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
2195 2 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
2196 integer i
, ic
, j
, jb
, jb2
, jj
, jj1
, jp1
2199 1 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
2200 KPP_REAL c
, r
, s
, tp
2201 dimension yh
(nyh
,1), dky
(1)
2202 common /ls0001
/ rowns
(209),
2203 2 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
,
2204 3 iownd
(14), iowns
(6),
2205 4 icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
2206 5 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
2207 c-----------------------------------------------------------------------
2208 c intdy computes interpolated values of the k-th derivative of the
2209 c dependent variable vector y, and stores it in dky. this routine
2210 c is called within the package with k = 0 and t = tout, but may
2211 c also be called by the user for any k up to the current order.
2212 c (see detailed instructions in the usage documentation.)
2213 c-----------------------------------------------------------------------
2214 c the computed values in dky are gotten by interpolation using the
2215 c nordsieck history array yh. this array corresponds uniquely to a
2216 c vector-valued polynomial of degree nqcur or less, and dky is set
2217 c to the k-th derivative of this polynomial at t.
2218 c the formula for dky is..
2220 c dky(i) = sum c(j,k) * (t - tn)**(j-k) * h**(-j) * yh(i,j+1)
2222 c where c(j,k) = j*(j-1)*...*(j-k+1), q = nqcur, tn = tcur, h = hcur.
2223 c the quantities nq = nqcur, l = nq+1, n = neq, tn, and h are
2224 c communicated by common. the above sum is done in reverse order.
2225 c iflag is returned negative if either k or t is out of bounds.
2226 c-----------------------------------------------------------------------
2228 if (k
.lt
. 0 .or
. k
.gt
. nq
) go to 80
2229 tp
= tn
- hu
- 100.0d0*uround*
(tn
+ hu
)
2230 if ((t
-tp
)*(t
-tn
) .gt
. 0.0d0
) go to 90
2234 if (k
.eq
. 0) go to 15
2240 20 dky
(i
) = c*yh
(i
,l
)
2241 if (k
.eq
. nq
) go to 55
2247 if (k
.eq
. 0) go to 35
2253 40 dky
(i
) = c*yh
(i
,jp1
) + s*dky
(i
)
2255 if (k
.eq
. 0) return
2258 60 dky
(i
) = r*dky
(i
)
2261 80 CALL xerrwv
(30hintdy
-- k
(=i1
) illegal
,
2262 1 30, 51, 0, 1, k
, 0, 0, 0.0d0
, 0.0d0
)
2265 90 CALL xerrwv
(30hintdy
-- t
(=r1
) illegal
,
2266 1 30, 52, 0, 0, 0, 0, 1, t
, 0.0d0
)
2268 1 60h t not in interval tcur
- hu
(= r1
) to tcur
(=r2
) ,
2269 1 60, 52, 0, 0, 0, 0, 2, tp
, tn
)
2272 c----------------------- end of subroutine intdy -----------------------
2274 subroutine prjs
(neq
,y
,yh
,nyh
,ewt
,ftem
,savf
,wk
,iwk
,f
,jac
)
2277 integer neq
, nyh
, iwk
2278 integer iownd
, iowns
,
2279 1 icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
2280 2 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
2281 integer iplost
, iesp
, istatc
, iys
, iba
, ibian
, ibjan
, ibjgp
,
2282 1 ipian
, ipjan
, ipjgp
, ipigp
, ipr
, ipc
, ipic
, ipisp
, iprsp
, ipa
,
2283 2 lenyh
, lenyhm
, lenwk
, lreq
, lrat
, lrest
, lwmin
, moss
, msbj
,
2284 3 nslj
, ngp
, nlu
, nnz
, nsp
, nzl
, nzu
2285 integer i
, imul
, j
, jj
, jok
, jmax
, jmin
, k
, kmax
, kmin
, ng
2288 1 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
2289 KPP_REAL con0
, conmin
, ccmxj
, psmall
, rbig
, seth
2290 KPP_REAL con
, di
, fac
, hl0
, pij
, r
, r0
, rcon
, rcont
,
2292 dimension neq
(*), iwk
(*)
2293 KPP_REAL y
(*), yh
(nyh
,*), ewt
(*), ftem
(*), savf
(*), wk
(*)
2294 common /ls0001
/ rowns
(209),
2295 2 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
,
2296 3 iownd
(14), iowns
(6),
2297 4 icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
2298 5 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
2299 common /lss001
/ con0
, conmin
, ccmxj
, psmall
, rbig
, seth
,
2300 1 iplost
, iesp
, istatc
, iys
, iba
, ibian
, ibjan
, ibjgp
,
2301 2 ipian
, ipjan
, ipjgp
, ipigp
, ipr
, ipc
, ipic
, ipisp
, iprsp
, ipa
,
2302 3 lenyh
, lenyhm
, lenwk
, lreq
, lrat
, lrest
, lwmin
, moss
, msbj
,
2303 4 nslj
, ngp
, nlu
, nnz
, nsp
, nzl
, nzu
2304 c-----------------------------------------------------------------------
2305 c prjs is called to compute and process the matrix
2306 c p = i - h*el(1)*j , where j is an approximation to the jacobian.
2307 c j is computed by columns, either by the user-supplied routine jac
2308 c if miter = 1, or by finite differencing if miter = 2.
2309 c if miter = 3, a diagonal approximation to j is used.
2310 c if miter = 1 or 2, and if the existing value of the jacobian
2311 c (as contained in p) is considered acceptable, then a new value of
2312 c p is reconstructed from the old value. in any case, when miter
2313 c is 1 or 2, the p matrix is subjected to lu decomposition in cdrv.
2314 c p and its lu decomposition are stored (separately) in wk.
2316 c in addition to variables described previously, communication
2317 c with prjs uses the following..
2318 c y = array containing predicted values on entry.
2319 c ftem = work array of length n (acor in stode).
2320 c savf = array containing f evaluated at predicted y.
2321 c wk = real work space for matrices. on output it contains the
2322 c inverse diagonal matrix if miter = 3, and p and its sparse
2323 c lu decomposition if miter is 1 or 2.
2324 c storage of matrix elements starts at wk(3).
2325 c wk also contains the following matrix-related data..
2326 c wk(1) = sqrt(uround), used in numerical jacobian increments.
2327 c wk(2) = h*el0, saved for later use if miter = 3.
2328 c iwk = integer work space for matrix-related data, assumed to
2329 c be equivalenced to wk. in addition, wk(iprsp) and iwk(ipisp)
2330 c are assumed to have identical locations.
2331 c el0 = el(1) (input).
2332 c ierpj = output error flag (in common).
2334 c = 1 if zero pivot found in cdrv.
2335 c = 2 if a singular matrix arose with miter = 3.
2336 c = -1 if insufficient storage for cdrv (should not occur here).
2337 c = -2 if other error found in cdrv (should not occur here).
2338 c jcur = output flag = 1 to indicate that the jacobian matrix
2339 c (or approximation) is now current.
2340 c this routine also uses other variables in common.
2341 c-----------------------------------------------------------------------
2344 if (miter
.eq
. 3) go to 300
2345 c see whether j should be reevaluated (jok = 0) or not (jok = 1). ------
2347 if (nst
.eq
. 0 .or
. nst
.ge
. nslj
+msbj
) jok
= 0
2348 if (icf
.eq
. 1 .and
. dabs
(rc
- 1.0d0
) .lt
. ccmxj
) jok
= 0
2349 if (icf
.eq
. 2) jok
= 0
2350 if (jok
.eq
. 1) go to 250
2352 c miter = 1 or 2, and the jacobian is to be reevaluated. ---------------
2358 go to (100, 200), miter
2360 c if miter = 1, call jac_chem, multiply by scalar, and add identity. --------
2363 call jac_chem
(neq
, tn
, y
, JJJ
, j
, iwk
(ipian
), iwk
(ipjan
))
2365 kmax
= iwk
(ipian
+j
) - 1
2368 C call jac_chem (neq, tn, y, ftem, j, iwk(ipian), iwk(ipjan))
2372 do 120 k
= kmin
, kmax
2374 wk
(iba
+k
) = ftem
(i
)*con
2375 if (i
.eq
. j
) wk
(iba
+k
) = wk
(iba
+k
) + 1.0d0
2381 c if miter = 2, make ngp calls to f to approximate j and p. ------------
2383 fac
= vnorm
(n
, savf
, ewt
)
2384 r0
= 1000.0d0
* dabs
(h
) * uround
* dfloat
(n
) * fac
2385 if (r0
.eq
. 0.0d0
) r0
= 1.0d0
2389 jmax
= iwk
(ipigp
+ng
) - 1
2390 do 210 j
= jmin
,jmax
2392 r
= DMAX1
(srur*dabs
(y
(jj
)),r0
/ewt
(jj
))
2393 210 y
(jj
) = y
(jj
) + r
2394 CALL f
(neq
, tn
, y
, ftem
)
2395 do 230 j
= jmin
,jmax
2398 r
= DMAX1
(srur*dabs
(y
(jj
)),r0
/ewt
(jj
))
2401 kmax
=iwk
(ibian
+jj
+1) - 1
2402 do 220 k
= kmin
,kmax
2404 wk
(iba
+k
) = (ftem
(i
) - savf
(i
))*fac
2405 if (i
.eq
. jj
) wk
(iba
+k
) = wk
(iba
+k
) + 1.0d0
2413 c if jok = 1, reconstruct new p from old p. ----------------------------
2416 rcont
= dabs
(con
)/conmin
2417 if (rcont
.gt
. rbig
.and
. iplost
.eq
. 1) go to 20
2420 kmax
= iwk
(ipian
+j
) - 1
2421 do 270 k
= kmin
,kmax
2424 if (i
.ne
. j
) go to 260
2426 if (dabs
(pij
) .ge
. psmall
) go to 260
2428 conmin
= dmin1
(dabs
(con0
),conmin
)
2430 if (i
.eq
. j
) pij
= pij
+ 1.0d0
2436 c do numerical factorization of p matrix. ------------------------------
2442 CALL cdrv
(n
,iwk
(ipr
),iwk
(ipc
),iwk
(ipic
),iwk
(ipian
),iwk
(ipjan
),
2443 1 wk
(ipa
),ftem
,ftem
,nsp
,iwk
(ipisp
),wk
(iprsp
),iesp
,2,iys
)
2444 if (iys
.eq
. 0) return
2447 if (imul
.eq
. 8) ierpj
= 1
2448 if (imul
.eq
. 10) ierpj
= -1
2451 c if miter = 3, construct a diagonal approximation to j and p. ---------
2459 310 y
(i
) = y
(i
) + r*
(h*savf
(i
) - yh
(i
,2))
2460 CALL f
(neq
, tn
, y
, wk
(3))
2463 r0
= h*savf
(i
) - yh
(i
,2)
2464 di
= 0.1d0*r0
- h*
(wk
(i
+2) - savf
(i
))
2466 if (dabs
(r0
) .lt
. uround
/ewt
(i
)) go to 320
2467 if (dabs
(di
) .eq
. 0.0d0
) go to 330
2468 wk
(i
+2) = 0.1d0*r0
/di
2473 c----------------------- end of subroutine prjs ------------------------
2475 subroutine stode
(neq
, y
, yh
, nyh
, yh1
, ewt
, savf
, acor
,
2476 1 wm
, iwm
, f
, jac
, pjac
, slvs
)
2478 external f
, jac
, pjac
, slvs
2479 integer neq
, nyh
, iwm
2480 integer iownd
, ialth
, ipup
, lmax
, meo
, nqnyh
, nslp
,
2481 1 icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
2482 2 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
2483 integer i
, i1
, iredo
, iret
, j
, jb
, m
, ncf
, newq
2484 KPP_REAL y
, yh
, yh1
, ewt
, savf
, acor
, wm
2485 KPP_REAL conit
, crate
, el
, elco
, hold
, rmax
, tesco
,
2486 2 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
2487 KPP_REAL dcon
, ddn
, del
, delp
, dsm
, dup
, exdn
, exsm
, exup
,
2488 1 r
, rh
, rhdn
, rhsm
, rhup
, told
, vnorm
2489 dimension neq
(*), y
(*), yh
(nyh
,*), yh1
(*), ewt
(*), savf
(*),
2490 1 acor
(*), wm
(*), iwm
(*)
2491 common /ls0001
/ conit
, crate
, el
(13), elco
(13,12),
2492 1 hold
, rmax
, tesco
(3,12),
2493 2 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
, iownd
(14),
2494 3 ialth
, ipup
, lmax
, meo
, nqnyh
, nslp
,
2495 4 icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
2496 5 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
2497 c-----------------------------------------------------------------------
2498 c stode performs one step of the integration of an initial value
2499 c problem for a system of ordinary differential equations.
2500 c note.. stode is independent of the value of the iteration method
2501 c indicator miter, when this is .ne. 0, and hence is independent
2502 c of the type of chord method used, or the jacobian structure.
2503 c communication with stode is done with the following variables..
2505 c neq = integer array containing problem size in neq(1), and
2506 c passed as the neq argument in all calls to f and jac.
2507 c y = an array of length .ge. n used as the y argument in
2508 c all calls to f and jac.
2509 c yh = an nyh by lmax array containing the dependent variables
2510 c and their approximate scaled derivatives, where
2511 c lmax = maxord + 1. yh(i,j+1) contains the approximate
2512 c j-th derivative of y(i), scaled by h**j/factorial(j)
2513 c (j = 0,1,...,nq). on entry for the first step, the first
2514 c two columns of yh must be set from the initial values.
2515 c nyh = a constant integer .ge. n, the first dimension of yh.
2516 c yh1 = a one-dimensional array occupying the same space as yh.
2517 c ewt = an array of length n containing multiplicative weights
2518 c for local error measurements. local errors in y(i) are
2519 c compared to 1.0/ewt(i) in various error tests.
2520 c savf = an array of working storage, of length n.
2521 c also used for input of yh(*,maxord+2) when jstart = -1
2522 c and maxord .lt. the current order nq.
2523 c acor = a work array of length n, used for the accumulated
2524 c corrections. on a successful return, acor(i) contains
2525 c the estimated one-step local error in y(i).
2526 c wm,iwm = real and integer work arrays associated with matrix
2527 c operations in chord iteration (miter .ne. 0).
2528 c pjac = name of routine to evaluate and preprocess jacobian matrix
2529 c and p = i - h*el0*jac, if a chord method is being used.
2530 c slvs = name of routine to solve linear system in chord iteration.
2531 c ccmax = maximum relative change in h*el0 before pjac is called.
2532 c h = the step size to be attempted on the next step.
2533 c h is altered by the error control algorithm during the
2534 c problem. h can be either positive or negative, but its
2535 c sign must remain constant throughout the problem.
2536 c hmin = the minimum absolute value of the step size h to be used.
2537 c hmxi = inverse of the maximum absolute value of h to be used.
2538 c hmxi = 0.0 is allowed and corresponds to an infinite hmax.
2539 c hmin and hmxi may be changed at any time, but will not
2540 c take effect until the next change of h is considered.
2541 c tn = the independent variable. tn is updated on each step taken.
2542 c jstart = an integer used for input only, with the following
2543 c values and meanings..
2544 c 0 perform the first step.
2545 c .gt.0 take a new step continuing from the last.
2546 c -1 take the next step with a new value of h, maxord,
2547 c n, meth, miter, and/or matrix parameters.
2548 c -2 take the next step with a new value of h,
2549 c but with other inputs unchanged.
2550 c on return, jstart is set to 1 to facilitate continuation.
2551 c kflag = a completion code with the following meanings..
2552 c 0 the step was succesful.
2553 c -1 the requested error could not be achieved.
2554 c -2 corrector convergence could not be achieved.
2555 c -3 fatal error in pjac or slvs.
2556 c a return with kflag = -1 or -2 means either
2557 c abs(h) = hmin or 10 consecutive failures occurred.
2558 c on a return with kflag negative, the values of tn and
2559 c the yh array are as of the beginning of the last
2560 c step, and h is the last step size attempted.
2561 c maxord = the maximum order of integration method to be allowed.
2562 c maxcor = the maximum number of corrector iterations allowed.
2563 c msbp = maximum number of steps between pjac calls (miter .gt. 0).
2564 c mxncf = maximum number of convergence failures allowed.
2565 c meth/miter = the method flags. see description in driver.
2566 c n = the number of first-order differential equations.
2567 c-----------------------------------------------------------------------
2576 if (jstart
.gt
. 0) go to 200
2577 if (jstart
.eq
. -1) go to 100
2578 if (jstart
.eq
. -2) go to 160
2579 c-----------------------------------------------------------------------
2580 c on the first call, the order is set to 1, and other variables are
2581 c initialized. rmax is the maximum ratio by which h can be increased
2582 c in a single step. it is initially 1.e4 to compensate for the small
2583 c initial h, but then is normally equal to 10. if a failure
2584 c occurs (in corrector convergence or error test), rmax is set at 2
2585 c for the next increase.
2586 c-----------------------------------------------------------------------
2601 c-----------------------------------------------------------------------
2602 c the following block handles preliminaries needed when jstart = -1.
2603 c ipup is set to miter to force a matrix update.
2604 c if an order increase is about to be considered (ialth = 1),
2605 c ialth is reset to 2 to postpone consideration one more step.
2606 c if the caller has changed meth, cfode is called to reset
2607 c the coefficients of the method.
2608 c if the caller has changed maxord to a value less than the current
2609 c order nq, nq is reduced to maxord, and a new h chosen accordingly.
2610 c if h is to be changed, yh must be rescaled.
2611 c if h or meth is being changed, ialth is reset to l = nq + 1
2612 c to prevent further changes in h for that many steps.
2613 c-----------------------------------------------------------------------
2616 if (ialth
.eq
. 1) ialth
= 2
2617 if (meth
.eq
. meo
) go to 110
2618 CALL cfode
(meth
, elco
, tesco
)
2620 if (nq
.gt
. maxord
) go to 120
2624 110 if (nq
.le
. maxord
) go to 160
2628 125 el
(i
) = elco
(i
,nq
)
2632 conit
= 0.5d0
/dfloat
(nq
+2)
2633 ddn
= vnorm
(n
, savf
, ewt
)/tesco
(1,l
)
2634 exdn
= 1.0d0
/dfloat
(l
)
2635 rhdn
= 1.0d0
/(1.3d0*ddn**exdn
+ 0.0000013d0
)
2636 rh
= dmin1
(rhdn
,1.0d0
)
2638 if (h
.eq
. hold
) go to 170
2639 rh
= dmin1
(rh
,dabs
(h
/hold
))
2642 c-----------------------------------------------------------------------
2643 c cfode is called to get all the integration coefficients for the
2644 c current meth. then the el vector and related constants are reset
2645 c whenever the order nq is changed, or at the start of the problem.
2646 c-----------------------------------------------------------------------
2647 140 CALL cfode
(meth
, elco
, tesco
)
2649 155 el
(i
) = elco
(i
,nq
)
2653 conit
= 0.5d0
/dfloat
(nq
+2)
2654 go to (160, 170, 200), iret
2655 c-----------------------------------------------------------------------
2656 c if h is being changed, the h ratio rh is checked against
2657 c rmax, hmin, and hmxi, and the yh array rescaled. ialth is set to
2658 c l = nq + 1 to prevent a change of h for that many steps, unless
2659 c forced by a convergence or error test failure.
2660 c-----------------------------------------------------------------------
2661 160 if (h
.eq
. hold
) go to 200
2666 170 rh
= DMAX1
(rh
,hmin
/dabs
(h
))
2667 175 rh
= dmin1
(rh
,rmax
)
2668 rh
= rh
/DMAX1
(1.0d0
,dabs
(h
)*hmxi*rh
)
2673 180 yh
(i
,j
) = yh
(i
,j
)*r
2677 if (iredo
.eq
. 0) go to 690
2678 c-----------------------------------------------------------------------
2679 c this section computes the predicted values by effectively
2680 c multiplying the yh array by the pascal triangle matrix.
2681 c rc is the ratio of new to old values of the coefficient h*el(1).
2682 c when rc differs from 1 by more than ccmax, ipup is set to miter
2683 c to force pjac to be called, if a jacobian is involved.
2684 c in any case, pjac is called at least every msbp steps.
2685 c-----------------------------------------------------------------------
2686 200 if (dabs
(rc
-1.0d0
) .gt
. ccmax
) ipup
= miter
2687 if (nst
.ge
. nslp
+msbp
) ipup
= miter
2694 210 yh1
(i
) = yh1
(i
) + yh1
(i
+nyh
)
2696 c-----------------------------------------------------------------------
2697 c up to maxcor corrector iterations are taken. a convergence test is
2698 c made on the r.m.s. norm of each correction, weighted by the error
2699 c weight vector ewt. the sum of the corrections is accumulated in the
2700 c vector acor(i). the yh array is not altered in the corrector loop.
2701 c-----------------------------------------------------------------------
2705 CALL f
(neq
, tn
, y
, savf
)
2707 if (ipup
.le
. 0) go to 250
2708 c-----------------------------------------------------------------------
2709 c if indicated, the matrix p = i - h*el(1)*j is reevaluated and
2710 c preprocessed before starting the corrector iteration. ipup is set
2711 c to 0 as an indicator that this has been done.
2712 c-----------------------------------------------------------------------
2713 CALL pjac
(neq
, y
, yh
, nyh
, ewt
, acor
, savf
, wm
, iwm
, f
, jac
)
2718 if (ierpj
.ne
. 0) go to 430
2721 270 if (miter
.ne
. 0) go to 350
2722 c-----------------------------------------------------------------------
2723 c in the case of functional iteration, update y directly from
2724 c the result of the last function evaluation.
2725 c-----------------------------------------------------------------------
2727 savf
(i
) = h*savf
(i
) - yh
(i
,2)
2728 290 y
(i
) = savf
(i
) - acor
(i
)
2729 del
= vnorm
(n
, y
, ewt
)
2731 y
(i
) = yh
(i
,1) + el
(1)*savf
(i
)
2732 300 acor
(i
) = savf
(i
)
2734 c-----------------------------------------------------------------------
2735 c in the case of the chord method, compute the corrector error,
2736 c and solve the linear system with that as right-hand side and
2737 c p as coefficient matrix.
2738 c-----------------------------------------------------------------------
2740 360 y
(i
) = h*savf
(i
) - (yh
(i
,2) + acor
(i
))
2741 CALL slvs
(wm
, iwm
, y
, savf
)
2742 if (iersl
.lt
. 0) go to 430
2743 if (iersl
.gt
. 0) go to 410
2744 del
= vnorm
(n
, y
, ewt
)
2746 acor
(i
) = acor
(i
) + y
(i
)
2747 380 y
(i
) = yh
(i
,1) + el
(1)*acor
(i
)
2748 c-----------------------------------------------------------------------
2749 c test for convergence. if m.gt.0, an estimate of the convergence
2750 c rate constant is stored in crate, and this is used in the test.
2751 c-----------------------------------------------------------------------
2752 400 if (m
.ne
. 0) crate
= DMAX1
(0.2d0*crate
,del
/delp
)
2753 dcon
= del*dmin1
(1.0d0
,1.5d0*crate
)/(tesco
(2,nq
)*conit
)
2754 if (dcon
.le
. 1.0d0
) go to 450
2756 if (m
.eq
. maxcor
) go to 410
2757 if (m
.ge
. 2 .and
. del
.gt
. 2.0d0*delp
) go to 410
2759 CALL f
(neq
, tn
, y
, savf
)
2762 c-----------------------------------------------------------------------
2763 c the corrector iteration failed to converge.
2764 c if miter .ne. 0 and the jacobian is out of date, pjac is called for
2765 c the next try. otherwise the yh array is retracted to its values
2766 c before prediction, and h is reduced, if possible. if h cannot be
2767 c reduced or mxncf failures have occurred, exit with kflag = -2.
2768 c-----------------------------------------------------------------------
2769 410 if (miter
.eq
. 0 .or
. jcur
.eq
. 1) go to 430
2782 440 yh1
(i
) = yh1
(i
) - yh1
(i
+nyh
)
2784 if (ierpj
.lt
. 0 .or
. iersl
.lt
. 0) go to 680
2785 if (dabs
(h
) .le
. hmin*1
.00001d0
) go to 670
2786 if (ncf
.eq
. mxncf
) go to 670
2791 c-----------------------------------------------------------------------
2792 c the corrector has converged. jcur is set to 0
2793 c to signal that the jacobian involved may need updating later.
2794 c the local error test is made and control passes to statement 500
2796 c-----------------------------------------------------------------------
2798 if (m
.eq
. 0) dsm
= del
/tesco
(2,nq
)
2799 if (m
.gt
. 0) dsm
= vnorm
(n
, acor
, ewt
)/tesco
(2,nq
)
2800 if (dsm
.gt
. 1.0d0
) go to 500
2801 c-----------------------------------------------------------------------
2802 c after a successful step, update the yh array.
2803 c consider changing h if ialth = 1. otherwise decrease ialth by 1.
2804 c if ialth is then 1 and nq .lt. maxord, then acor is saved for
2805 c use in a possible order increase on the next step.
2806 c if a change in h is considered, an increase or decrease in order
2807 c by one is considered also. a change in h is made only if it is by a
2808 c factor of at least 1.1. if not, ialth is set to 3 to prevent
2809 c testing for that many steps.
2810 c-----------------------------------------------------------------------
2818 470 yh
(i
,j
) = yh
(i
,j
) + el
(j
)*acor
(i
)
2820 if (ialth
.eq
. 0) go to 520
2821 if (ialth
.gt
. 1) go to 700
2822 if (l
.eq
. lmax
) go to 700
2824 490 yh
(i
,lmax
) = acor
(i
)
2826 c-----------------------------------------------------------------------
2827 c the error test failed. kflag keeps track of multiple failures.
2828 c restore tn and the yh array to their previous values, and prepare
2829 c to try the step again. compute the optimum step size for this or
2830 c one lower order. after 2 or more failures, h is forced to decrease
2831 c by a factor of 0.2 or less.
2832 c-----------------------------------------------------------------------
2833 500 kflag
= kflag
- 1
2840 510 yh1
(i
) = yh1
(i
) - yh1
(i
+nyh
)
2843 if (dabs
(h
) .le
. hmin*1
.00001d0
) go to 660
2844 if (kflag
.le
. -3) go to 640
2848 c-----------------------------------------------------------------------
2849 c regardless of the success or failure of the step, factors
2850 c rhdn, rhsm, and rhup are computed, by which h could be multiplied
2851 c at order nq - 1, order nq, or order nq + 1, respectively.
2852 c in the case of failure, rhup = 0.0 to avoid an order increase.
2853 c the largest of these is determined and the new order chosen
2854 c accordingly. if the order is to be increased, we compute one
2855 c additional scaled derivative.
2856 c-----------------------------------------------------------------------
2858 if (l
.eq
. lmax
) go to 540
2860 530 savf
(i
) = acor
(i
) - yh
(i
,lmax
)
2861 dup
= vnorm
(n
, savf
, ewt
)/tesco
(3,nq
)
2862 exup
= 1.0d0
/dfloat
(l
+1)
2863 rhup
= 1.0d0
/(1.4d0*dup**exup
+ 0.0000014d0
)
2864 540 exsm
= 1.0d0
/dfloat
(l
)
2865 rhsm
= 1.0d0
/(1.2d0*dsm**exsm
+ 0.0000012d0
)
2867 if (nq
.eq
. 1) go to 560
2868 ddn
= vnorm
(n
, yh
(1,l
), ewt
)/tesco
(1,nq
)
2869 exdn
= 1.0d0
/dfloat
(nq
)
2870 rhdn
= 1.0d0
/(1.3d0*ddn**exdn
+ 0.0000013d0
)
2871 560 if (rhsm
.ge
. rhup
) go to 570
2872 if (rhup
.gt
. rhdn
) go to 590
2874 570 if (rhsm
.lt
. rhdn
) go to 580
2880 if (kflag
.lt
. 0 .and
. rh
.gt
. 1.0d0
) rh
= 1.0d0
2884 if (rh
.lt
. 1.1d0
) go to 610
2887 600 yh
(i
,newq
+1) = acor
(i
)*r
2891 620 if ((kflag
.eq
. 0) .and
. (rh
.lt
. 1.1d0
)) go to 610
2892 if (kflag
.le
. -2) rh
= dmin1
(rh
,0.2d0
)
2893 c-----------------------------------------------------------------------
2894 c if there is a change of order, reset nq, l, and the coefficients.
2895 c in any case h is reset according to rh and the yh array is rescaled.
2896 c then exit from 690 if the step was ok, or redo the step otherwise.
2897 c-----------------------------------------------------------------------
2898 if (newq
.eq
. nq
) go to 170
2903 c-----------------------------------------------------------------------
2904 c control reaches this section if 3 or more failures have occured.
2905 c if 10 failures have occurred, exit with kflag = -1.
2906 c it is assumed that the derivatives that have accumulated in the
2907 c yh array have errors of the wrong order. hence the first
2908 c derivative is recomputed, and the order is set to 1. then
2909 c h is reduced by a factor of 10, and the step is retried,
2910 c until it succeeds or h reaches hmin.
2911 c-----------------------------------------------------------------------
2912 640 if (kflag
.eq
. -10) go to 660
2914 rh
= DMAX1
(hmin
/dabs
(h
),rh
)
2918 CALL f
(neq
, tn
, y
, savf
)
2921 650 yh
(i
,2) = h*savf
(i
)
2924 if (nq
.eq
. 1) go to 200
2929 c-----------------------------------------------------------------------
2930 c all returns are made through this section. h is saved in hold
2931 c to allow the caller to change h on the next step.
2932 c-----------------------------------------------------------------------
2940 700 r
= 1.0d0
/tesco
(2,nqu
)
2942 710 acor
(i
) = acor
(i
)*r
2946 c----------------------- end of subroutine stode -----------------------
2948 subroutine xerrwv
(msg
, nmes
, nerr
, level
, ni
, i1
, i2
, nr
, r1
, r2
)
2949 integer msg
, nmes
, nerr
, level
, ni
, i1
, i2
, nr
,
2950 1 i
, lun
, lunit
, mesflg
, ncpw
, nch
, nwds
2953 c-----------------------------------------------------------------------
2954 c subroutines xerrwv, xsetf, and xsetun, as given here, constitute
2955 c a simplified version of the slatec error handling package.
2956 c written by a. c. hindmarsh at llnl. version of march 30, 1987.
2957 c this version is in KPP_REAL.
2959 c all arguments are input arguments.
2961 c msg = the message (hollerith literal or integer array).
2962 c nmes = the length of msg (number of characters).
2963 c nerr = the error number (not used).
2964 c level = the error level..
2965 c 0 or 1 means recoverable (control returns to caller).
2966 c 2 means fatal (run is aborted--see note below).
2967 c ni = number of integers (0, 1, or 2) to be printed with message.
2968 c i1,i2 = integers to be printed, depending on ni.
2969 c nr = number of reals (0, 1, or 2) to be printed with message.
2970 c r1,r2 = reals to be printed, depending on nr.
2972 c note.. this routine is machine-dependent and specialized for use
2973 c in limited context, in the following ways..
2974 c 1. the number of hollerith characters stored per word, denoted
2975 c by ncpw below, is a data-loaded constant.
2976 c 2. the value of nmes is assumed to be at most 60.
2977 c (multi-line messages are generated by repeated calls.)
2978 c 3. if level = 2, control passes to the statement stop
2979 c to abort the run. this statement may be machine-dependent.
2980 c 4. r1 and r2 are assumed to be in KPP_REAL and are printed
2982 c 5. the common block /eh0001/ below is data-loaded (a machine-
2983 c dependent feature) with default values.
2984 c this block is needed for proper retention of parameters used by
2985 c this routine which the user can reset by calling xsetf or xsetun.
2986 c the variables in this block are as follows..
2987 c mesflg = print control flag..
2988 c 1 means print all messages (the default).
2989 c 0 means no printing.
2990 c lunit = logical unit number for messages.
2991 c the default is 6 (machine-dependent).
2992 c-----------------------------------------------------------------------
2993 c the following are instructions for installing this routine
2994 c in different machine environments.
2996 c to change the default output unit, change the data statement
2997 c in the block data subprogram below.
2999 c for a different number of characters per word, change the
3000 c data statement setting ncpw below, and format 10. alternatives for
3001 c various computers are shown in comment cards.
3003 c for a different run-abort command, change the statement following
3004 c statement 100 at the end.
3005 c-----------------------------------------------------------------------
3006 common /eh0001
/ mesflg
, lunit
3007 c-----------------------------------------------------------------------
3008 c the following data-loaded value of ncpw is valid for the cdc-6600
3009 c and cdc-7600 computers.
3011 c the following is valid for the cray-1 computer.
3013 c the following is valid for the burroughs 6700 and 7800 computers.
3015 c the following is valid for the pdp-10 computer.
3017 c the following is valid for the vax computer with 4 bytes per integer,
3018 c and for the ibm-360, ibm-370, ibm-303x, and ibm-43xx computers.
3020 c the following is valid for the pdp-11, or vax with 2-byte integers.
3022 c-----------------------------------------------------------------------
3023 if (mesflg
.eq
. 0) go to 100
3024 c get logical unit number. ---------------------------------------------
3026 c get number of words in message. --------------------------------------
3029 if (nch
.ne
. nwds*ncpw
) nwds
= nwds
+ 1
3030 c write the message. ---------------------------------------------------
3031 write (lun
, 10) (msg
(i
),i
=1,nwds
)
3032 c-----------------------------------------------------------------------
3033 c the following format statement is to have the form
3034 c 10 format(1x,mmann)
3035 c where nn = ncpw and mm is the smallest integer .ge. 60/ncpw.
3036 c the following is valid for ncpw = 10.
3037 c 10 format(1x,6a10)
3038 c the following is valid for ncpw = 8.
3040 c the following is valid for ncpw = 6.
3041 c 10 format(1x,10a6)
3042 c the following is valid for ncpw = 5.
3043 c 10 format(1x,12a5)
3044 c the following is valid for ncpw = 4.
3046 c the following is valid for ncpw = 2.
3047 c 10 format(1x,30a2)
3048 c-----------------------------------------------------------------------
3049 if (ni
.eq
. 1) write (lun
, 20) i1
3050 20 format(6x
,23hin above message
, i1
=,i10
)
3051 if (ni
.eq
. 2) write (lun
, 30) i1
,i2
3052 30 format(6x
,23hin above message
, i1
=,i10
,3x
,4hi2
=,i10
)
3053 if (nr
.eq
. 1) write (lun
, 40) r1
3054 40 format(6x
,23hin above message
, r1
=,d21
.13
)
3055 if (nr
.eq
. 2) write (lun
, 50) r1
,r2
3056 50 format(6x
,15hin above
, r1
=,d21
.13
,3x
,4hr2
=,d21
.13
)
3057 c abort the run if level = 2. ------------------------------------------
3058 100 if (level
.ne
. 2) return
3060 c----------------------- end of subroutine xerrwv ----------------------
3062 KPP_REAL
function vnorm
(n
, v
, w
)
3064 c-----------------------------------------------------------------------
3065 c this function routine computes the weighted root-mean-square norm
3066 c of the vector of length n contained in the array v, with weights
3067 c contained in the array w of length n..
3068 c vnorm = sqrt( (1/n) * sum( v(i)*w(i) )**2 )
3069 c-----------------------------------------------------------------------
3072 dimension v
(n
), w
(n
)
3075 10 sum
= sum
+ (v
(i
)*w
(i
))**2
3076 vnorm
= DSQRT
(sum
/dfloat
(n
))
3078 c----------------------- end of function vnorm -------------------------
3080 subroutine ewset
(n
, itol
, RelTol
, AbsTol
, ycur
, ewt
)
3082 c-----------------------------------------------------------------------
3083 c this subroutine sets the error weight vector ewt according to
3084 c ewt(i) = RelTol(i)*abs(ycur(i)) + AbsTol(i), i = 1,...,n,
3085 c with the subscript on RelTol and/or AbsTol possibly replaced by 1 above,
3086 c depending on the value of itol.
3087 c-----------------------------------------------------------------------
3090 KPP_REAL RelTol
, AbsTol
, ycur
, ewt
3091 dimension RelTol
(1), AbsTol
(1), ycur
(n
), ewt
(n
)
3093 go to (10, 20, 30, 40), itol
3096 15 ewt
(i
) = RelTol
(1)*dabs
(ycur
(i
)) + AbsTol
(1)
3100 25 ewt
(i
) = RelTol
(1)*dabs
(ycur
(i
)) + AbsTol
(i
)
3104 35 ewt
(i
) = RelTol
(i
)*dabs
(ycur
(i
)) + AbsTol
(1)
3108 45 ewt
(i
) = RelTol
(i
)*dabs
(ycur
(i
)) + AbsTol
(i
)
3110 c----------------------- end of subroutine ewset -----------------------
3112 subroutine cfode
(meth
, elco
, tesco
)
3115 integer i
, ib
, nq
, nqm1
, nqp1
3116 KPP_REAL elco
, tesco
3117 KPP_REAL agamq
, fnq
, fnqm1
, pc
, pint
, ragq
,
3118 1 rqfac
, rq1fac
, tsign
, xpin
3119 dimension elco
(13,12), tesco
(3,12)
3120 c-----------------------------------------------------------------------
3121 c cfode is called by the integrator routine to set coefficients
3122 c needed there. the coefficients for the current method, as
3123 c given by the value of meth, are set for all orders and saved.
3124 c the maximum order assumed here is 12 if meth = 1 and 5 if meth = 2.
3125 c (a smaller value of the maximum order is also allowed.)
3126 c cfode is called once at the beginning of the problem,
3127 c and is not called again unless and until meth is changed.
3129 c the elco array contains the basic method coefficients.
3130 c the coefficients el(i), 1 .le. i .le. nq+1, for the method of
3131 c order nq are stored in elco(i,nq). they are given by a genetrating
3133 c l(x) = el(1) + el(2)*x + ... + el(nq+1)*x**nq.
3134 c for the implicit adams methods, l(x) is given by
3135 c dl/dx = (x+1)*(x+2)*...*(x+nq-1)/factorial(nq-1), l(-1) = 0.
3136 c for the bdf methods, l(x) is given by
3137 c l(x) = (x+1)*(x+2)* ... *(x+nq)/k,
3138 c where k = factorial(nq)*(1 + 1/2 + ... + 1/nq).
3140 c the tesco array contains test constants used for the
3141 c local error test and the selection of step size and/or order.
3142 c at order nq, tesco(k,nq) is used for the selection of step
3143 c size at order nq - 1 if k = 1, at order nq if k = 2, and at order
3145 c-----------------------------------------------------------------------
3148 go to (100, 200), meth
3150 100 elco
(1,1) = 1.0d0
3159 c-----------------------------------------------------------------------
3160 c the pc array will contain the coefficients of the polynomial
3161 c p(x) = (x+1)*(x+2)*...*(x+nq-1).
3162 c initially, p(x) = 1.
3163 c-----------------------------------------------------------------------
3165 rqfac
= rqfac
/dfloat
(nq
)
3167 fnqm1
= dfloat
(nqm1
)
3169 c form coefficients of p(x)*(x+nq-1). ----------------------------------
3173 110 pc
(i
) = pc
(i
-1) + fnqm1*pc
(i
)
3175 c compute integral, -1 to 0, of p(x) and x*p(x). -----------------------
3181 pint
= pint
+ tsign*pc
(i
)/dfloat
(i
)
3182 120 xpin
= xpin
+ tsign*pc
(i
)/dfloat
(i
+1)
3183 c store coefficients in elco and tesco. --------------------------------
3184 elco
(1,nq
) = pint*rq1fac
3187 130 elco
(i
+1,nq
) = rq1fac*pc
(i
)/dfloat
(i
)
3191 if (nq
.lt
. 12) tesco
(1,nqp1
) = ragq*rqfac
/dfloat
(nqp1
)
3192 tesco
(3,nqm1
) = ragq
3199 c-----------------------------------------------------------------------
3200 c the pc array will contain the coefficients of the polynomial
3201 c p(x) = (x+1)*(x+2)*...*(x+nq).
3202 c initially, p(x) = 1.
3203 c-----------------------------------------------------------------------
3206 c form coefficients of p(x)*(x+nq). ------------------------------------
3210 210 pc
(i
) = pc
(i
-1) + fnq*pc
(i
)
3212 c store coefficients in elco and tesco. --------------------------------
3214 220 elco
(i
,nq
) = pc
(i
)/pc
(2)
3216 tesco
(1,nq
) = rq1fac
3217 tesco
(2,nq
) = dfloat
(nqp1
)/elco
(1,nq
)
3218 tesco
(3,nq
) = dfloat
(nq
+2)/elco
(1,nq
)
3222 c----------------------- end of subroutine cfode -----------------------
3225 * (n
, r
,c
,ic
, ia
,ja
,a
, b
, z
, nsp
,isp
,rsp
,esp
, path
, flag
)
3227 c*** subroutine cdrv
3228 c*** driver for subroutines for solving sparse nonsymmetric systems of
3229 c linear equations (compressed pointer storage)
3233 c class abbreviations are--
3234 c n - integer variable
3236 c v - supplies a value to the driver
3237 c r - returns a result from the driver
3238 c i - used internally by the driver
3244 c the nonzero entries of the coefficient matrix m are stored
3245 c row-by-row in the array a. to identify the individual nonzero
3246 c entries in each row, we need to know in which column each entry
3247 c lies. the column indices which correspond to the nonzero entries
3248 c of m are stored in the array ja. i.e., if a(k) = m(i,j), then
3249 c ja(k) = j. in addition, we need to know where each row starts and
3250 c how long it is. the index positions in ja and a where the rows of
3251 c m begin are stored in the array ia. i.e., if m(i,j) is the first
3252 c nonzero entry (stored) in the i-th row and a(k) = m(i,j), then
3253 c ia(i) = k. moreover, the index in ja and a of the first location
3254 c following the last element in the last row is stored in ia(n+1).
3255 c thus, the number of entries in the i-th row is given by
3256 c ia(i+1) - ia(i), the nonzero entries of the i-th row are stored
3258 c a(ia(i)), a(ia(i)+1), ..., a(ia(i+1)-1),
3259 c and the corresponding column indices are stored consecutively in
3260 c ja(ia(i)), ja(ia(i)+1), ..., ja(ia(i+1)-1).
3261 c for example, the 5 by 5 matrix
3264 c m = ( 0. 4. 5. 6. 0.)
3267 c would be stored as
3268 c - 1 2 3 4 5 6 7 8 9
3269 c ---+--------------------------
3271 c ja - 1 3 2 2 3 4 4 4 5
3272 c a - 1. 2. 3. 4. 5. 6. 7. 8. 9. .
3274 c nv - n - number of variables/equations.
3275 c fva - a - nonzero entries of the coefficient matrix m, stored
3277 c - size = number of nonzero entries in m.
3278 c nva - ia - pointers to delimit the rows in a.
3280 c nva - ja - column numbers corresponding to the elements of a.
3281 c - size = size of a.
3282 c fva - b - right-hand side b. b and z can the same array.
3284 c fra - z - solution x. b and z can be the same array.
3287 c the rows and columns of the original matrix m can be
3288 c reordered (e.g., to reduce fillin or ensure numerical stability)
3289 c before calling the driver. if no reordering is done, then set
3290 c r(i) = c(i) = ic(i) = i for i=1,...,n. the solution z is returned
3291 c in the original order.
3292 c if the columns have been reordered (i.e., c(i).ne.i for some
3293 c i), then the driver will CALL a subroutine (nroc) which rearranges
3294 c each row of ja and a, leaving the rows in the original order, but
3295 c placing the elements of each row in increasing order with respect
3296 c to the new ordering. if path.ne.1, then nroc is assumed to have
3297 c been called already.
3299 c nva - r - ordering of the rows of m.
3301 c nva - c - ordering of the columns of m.
3303 c nva - ic - inverse of the ordering of the columns of m. i.e.,
3304 c - ic(c(i)) = i for i=1,...,n.
3307 c the solution of the system of linear equations is divided into
3309 c nsfc -- the matrix m is processed symbolically to determine where
3310 c fillin will occur during the numeric factorization.
3311 c nnfc -- the matrix m is factored numerically into the product ldu
3312 c of a unit lower triangular matrix l, a diagonal matrix
3313 c d, and a unit upper triangular matrix u, and the system
3315 c nnsc -- the linear system mx = b is solved using the ldu
3316 c or factorization from nnfc.
3317 c nntc -- the transposed linear system mt x = b is solved using
3318 c the ldu factorization from nnf.
3319 c for several systems whose coefficient matrices have the same
3320 c nonzero structure, nsfc need be done only once (for the first
3321 c system). then nnfc is done once for each additional system. for
3322 c several systems with the same coefficient matrix, nsfc and nnfc
3323 c need be done only once (for the first system). then nnsc or nntc
3324 c is done once for each additional right-hand side.
3326 c nv - path - path specification. values and their meanings are --
3327 c - 1 perform nroc, nsfc, and nnfc.
3328 c - 2 perform nnfc only (nsfc is assumed to have been
3329 c - done in a manner compatible with the storage
3330 c - allocation used in the driver).
3331 c - 3 perform nnsc only (nsfc and nnfc are assumed to
3332 c - have been done in a manner compatible with the
3333 c - storage allocation used in the driver).
3334 c - 4 perform nntc only (nsfc and nnfc are assumed to
3335 c - have been done in a manner compatible with the
3336 c - storage allocation used in the driver).
3337 c - 5 perform nroc and nsfc.
3339 c various errors are detected by the driver and the individual
3342 c nr - flag - error flag. values and their meanings are --
3343 c - 0 no errors detected
3344 c - n+k null row in a -- row = k
3345 c - 2n+k duplicate entry in a -- row = k
3346 c - 3n+k insufficient storage in nsfc -- row = k
3347 c - 4n+1 insufficient storage in nnfc
3348 c - 5n+k null pivot -- row = k
3349 c - 6n+k insufficient storage in nsfc -- row = k
3350 c - 7n+1 insufficient storage in nnfc
3351 c - 8n+k zero pivot -- row = k
3352 c - 10n+1 insufficient storage in cdrv
3353 c - 11n+1 illegal path specification
3355 c working storage is needed for the factored form of the matrix
3356 c m plus various temporary vectors. the arrays isp and rsp should be
3357 c equivalenced. integer storage is allocated from the beginning of
3358 c isp and real storage from the end of rsp.
3360 c nv - nsp - declared dimension of rsp. nsp generally must
3361 c - be larger than 8n+2 + 2k (where k = (number of
3362 c - nonzero entries in m)).
3363 c nvira - isp - integer working storage divided up into various arrays
3364 c - needed by the subroutines. isp and rsp should be
3366 c - size = lratio*nsp.
3367 c fvira - rsp - real working storage divided up into various arrays
3368 c - needed by the subroutines. isp and rsp should be
3371 c nr - esp - if sufficient storage was available to perform the
3372 c - symbolic factorization (nsfc), then esp is set to
3373 c - the amount of excess storage provided (negative if
3374 c - insufficient storage was available to perform the
3375 c - numeric factorization (nnfc)).
3378 c conversion to KPP_REAL
3380 c to convert these routines for KPP_REAL arrays..
3381 c (1) use the KPP_REAL declarations in place of the real
3382 c declarations in each subprogram, as given in comment cards.
3383 c (2) change the data-loaded value of the integer lratio
3384 c in subroutine cdrv, as indicated below.
3385 c (3) change e0 to d0 in the constants in statement number 10
3386 c in subroutine nnfc and the line following that.
3388 integer r
(1), c
(1), ic
(1), ia
(1), ja
(1), isp
(1), esp
, path
,
3389 * flag
, d
, u
, q
, row
, tmp
, ar
, umax
3390 KPP_REAL a
(1), b
(1), z
(1), rsp
(1)
3392 c set lratio equal to the ratio between the length of floating point
3393 c and integer array data. e. g., lratio = 1 for (real, integer),
3394 c lratio = 2 for (KPP_REAL, integer)
3398 if (path
.lt
.1 .or
. 5.lt
.path
) go to 111
3399 c******initialize and divide up temporary storage *******************
3408 c ****** reorder a if necessary, CALL nsfc if flag is set ***********
3409 if ((path
-1) * (path
-5) .ne
. 0) go to 5
3410 max
= (lratio*nsp
+ 1 - jl
) - (n
+1) - 5*n
3419 jumax
= lratio*nsp
+ 1 - jutmp
3421 if (jlmax
.le
.0 .or
. jumax
.le
.0) go to 110
3424 if (c
(i
).ne
.i
) go to 2
3429 * (n
, ic
, ia
,ja
,a
, isp
(il
), rsp
(ar
), isp
(iu
), flag
)
3430 if (flag
.ne
.0) go to 100
3434 * jlmax
, isp
(il
), isp
(jl
), isp
(ijl
),
3435 * jumax
, isp
(iu
), isp
(jutmp
), isp
(iju
),
3436 * isp
(q
), isp
(ira
), isp
(jra
), isp
(irac
),
3437 * isp
(irl
), isp
(jrl
), isp
(iru
), isp
(jru
), flag
)
3438 if(flag
.ne
. 0) go to 100
3439 c ****** move ju next to jl *****************************************
3440 jlmax
= isp
(ijl
+n
-1)
3442 jumax
= isp
(iju
+n
-1)
3443 if (jumax
.le
.0) go to 5
3445 4 isp
(ju
+j
-1) = isp
(jutmp
+j
-1)
3447 c ****** CALL remaining subroutines *********************************
3448 5 jlmax
= isp
(ijl
+n
-1)
3450 jumax
= isp
(iju
+n
-1)
3451 l
= (ju
+ jumax
- 2 + lratio
) / lratio
+ 1
3452 lmax
= isp
(il
+n
) - 1
3458 esp
= umax
- (isp
(iu
+n
) - 1)
3460 if ((path
-1) * (path
-2) .ne
. 0) go to 6
3461 if (umax
.lt
.0) go to 110
3463 * (n
, r
, c
, ic
, ia
, ja
, a
, z
, b
,
3464 * lmax
, isp
(il
), isp
(jl
), isp
(ijl
), rsp
(l
), rsp
(d
),
3465 * umax
, isp
(iu
), isp
(ju
), isp
(iju
), rsp
(u
),
3466 * rsp
(row
), rsp
(tmp
), isp
(irl
), isp
(jrl
), flag
)
3467 if(flag
.ne
. 0) go to 100
3469 6 if ((path
-3) .ne
. 0) go to 7
3471 * (n
, r
, c
, isp
(il
), isp
(jl
), isp
(ijl
), rsp
(l
),
3472 * rsp
(d
), isp
(iu
), isp
(ju
), isp
(iju
), rsp
(u
),
3475 7 if ((path
-4) .ne
. 0) go to 8
3477 * (n
, r
, c
, isp
(il
), isp
(jl
), isp
(ijl
), rsp
(l
),
3478 * rsp
(d
), isp
(iu
), isp
(ju
), isp
(iju
), rsp
(u
),
3482 c ** error.. error detected in nroc, nsfc, nnfc, or nnsc
3484 c ** error.. insufficient storage
3487 c ** error.. illegal path specification
3491 subroutine prep
(neq
, y
, yh
, savf
, ewt
, ftem
, ia
, ja
,
3492 1 wk
, iwk
, ipper
, f
, jac
)
3495 integer neq
(*), ia
(*), ja
(*), iwk
(*), ipper
3496 integer iownd
, iowns
,
3497 1 icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
3498 2 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
3499 integer iplost
, iesp
, istatc
, iys
, iba
, ibian
, ibjan
, ibjgp
,
3500 1 ipian
, ipjan
, ipjgp
, ipigp
, ipr
, ipc
, ipic
, ipisp
, iprsp
, ipa
,
3501 2 lenyh
, lenyhm
, lenwk
, lreq
, lrat
, lrest
, lwmin
, moss
, msbj
,
3502 3 nslj
, ngp
, nlu
, nnz
, nsp
, nzl
, nzu
3503 integer i
, ibr
, ier
, ipil
, ipiu
, iptt1
, iptt2
, j
, jfound
, k
,
3504 1 knew
, kmax
, kmin
, ldif
, lenigp
, liwk
, maxg
, np1
, nzsut
3505 KPP_REAL y
(*), yh
(*), savf
(*), ewt
(*), ftem
(*), wk
(*)
3507 1 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
3508 KPP_REAL con0
, conmin
, ccmxj
, psmall
, rbig
, seth
3509 KPP_REAL dq
, dyj
, erwt
, fac
, yj
, JJJ
(n
,n
)
3510 common /ls0001
/ rowns
(209),
3511 2 ccmax
, el0
, h
, hmin
, hmxi
, hu
, rc
, tn
, uround
,
3512 3 iownd
(14), iowns
(6),
3513 4 icf
, ierpj
, iersl
, jcur
, jstart
, kflag
, l
, meth
, miter
,
3514 5 maxord
, maxcor
, msbp
, mxncf
, n
, nq
, nst
, nfe
, nje
, nqu
3515 common /lss001
/ con0
, conmin
, ccmxj
, psmall
, rbig
, seth
,
3516 1 iplost
, iesp
, istatc
, iys
, iba
, ibian
, ibjan
, ibjgp
,
3517 2 ipian
, ipjan
, ipjgp
, ipigp
, ipr
, ipc
, ipic
, ipisp
, iprsp
, ipa
,
3518 3 lenyh
, lenyhm
, lenwk
, lreq
, lrat
, lrest
, lwmin
, moss
, msbj
,
3519 4 nslj
, ngp
, nlu
, nnz
, nsp
, nzl
, nzu
3520 c-----------------------------------------------------------------------
3521 c this routine performs preprocessing related to the sparse linear
3522 c systems that must be solved if miter = 1 or 2.
3523 c the operations that are performed here are..
3524 c * compute sparseness structure of jacobian according to moss,
3525 c * compute grouping of column indices (miter = 2),
3526 c * compute a new ordering of rows and columns of the matrix,
3527 c * reorder ja corresponding to the new ordering,
3528 c * perform a symbolic lu factorization of the matrix, and
3529 c * set pointers for segments of the iwk/wk array.
3530 c in addition to variables described previously, prep uses the
3531 c following for communication..
3532 c yh = the history array. only the first column, containing the
3533 c current y vector, is used. used only if moss .ne. 0.
3534 c savf = a work array of length neq, used only if moss .ne. 0.
3535 c ewt = array of length neq containing (inverted) error weights.
3536 c used only if moss = 2 or if istate = moss = 1.
3537 c ftem = a work array of length neq, identical to acor in the driver,
3538 c used only if moss = 2.
3539 c wk = a real work array of length lenwk, identical to wm in
3541 c iwk = integer work array, assumed to occupy the same space as wk.
3542 c lenwk = the length of the work arrays wk and iwk.
3543 c istatc = a copy of the driver input argument istate (= 1 on the
3544 c first call, = 3 on a continuation call).
3545 c iys = flag value from odrv or cdrv.
3546 c ipper = output error flag with the following values and meanings..
3548 c -1 insufficient storage for internal structure pointers.
3549 c -2 insufficient storage for jgroup.
3550 c -3 insufficient storage for odrv.
3551 c -4 other error flag from odrv (should never occur).
3552 c -5 insufficient storage for cdrv.
3553 c -6 other error flag from cdrv.
3554 c-----------------------------------------------------------------------
3561 if (ipjan
+n
-1 .gt
. liwk
) go to 210
3562 if (moss
.eq
. 0) go to 30
3564 if (istatc
.eq
. 3) go to 20
3565 c istate = 1 and moss .ne. 0. perturb y for structure determination. --
3568 fac
= 1.0d0
+ 1.0d0
/(dfloat
(i
)+1.0d0
)
3569 y
(i
) = y
(i
) + fac*DSIGN
(erwt
,y
(i
))
3571 go to (70, 100), moss
3574 c istate = 3 and moss .ne. 0. load y from yh(*,1). --------------------
3577 go to (70, 100), moss
3579 c moss = 0. process user-s ia,ja. add diagonal entries if necessary. -
3586 if (kmin
.gt
. kmax
) go to 45
3589 if (i
.eq
. j
) jfound
= 1
3590 if (knew
.gt
. liwk
) go to 210
3594 if (jfound
.eq
. 1) go to 50
3595 45 if (knew
.gt
. liwk
) go to 210
3598 50 iwk
(ipian
+j
) = knew
+ 1 - ipjan
3603 c moss = 1. compute structure from user-supplied jacobian routine jac.
3605 c a dummy CALL to f allows user to create temporaries for use in jac. --
3606 CALL f
(neq
, tn
, y
, savf
)
3609 call jac_chem
(neq
, tn
, y
, JJJ
, j
, iwk
(ipian
), iwk
(ipjan
))
3611 if (k
.gt
. liwk
) go to 210
3616 C call jac_chem (neq, tn, y, j, iwk(ipian), iwk(ipjan), savf)
3621 if (dabs
(savf
(i
)) .le
. seth
) go to 80
3622 if (i
.eq
. j
) go to 80
3623 if (k
.gt
. liwk
) go to 210
3627 iwk
(ipian
+j
) = k
+ 1 - ipjan
3631 c moss = 2. compute structure from results of n + 1 calls to f. -------
3634 CALL f
(neq
, tn
, y
, savf
)
3636 if (k
.gt
. liwk
) go to 210
3641 dyj
= DSIGN
(erwt
,yj
)
3643 CALL f
(neq
, tn
, y
, ftem
)
3646 dq
= (ftem
(i
) - savf
(i
))/dyj
3647 if (dabs
(dq
) .le
. seth
) go to 110
3648 if (i
.eq
. j
) go to 110
3649 if (k
.gt
. liwk
) go to 210
3653 iwk
(ipian
+j
) = k
+ 1 - ipjan
3657 if (moss
.eq
. 0 .or
. istatc
.ne
. 1) go to 150
3658 c if istate = 1 and moss .ne. 0, restore y from yh. --------------------
3661 150 nnz
= iwk
(ipian
+n
) - 1
3664 if (miter
.ne
. 2) go to 160
3666 c compute grouping of column indices (miter = 2). ----------------------
3673 lreq
= iptt2
+ n
- 1
3674 if (lreq
.gt
. liwk
) go to 220
3675 CALL jgroup
(n
, iwk
(ipian
), iwk
(ipjan
), maxg
, ngp
, iwk
(ipigp
),
3676 1 iwk
(ipjgp
), iwk
(iptt1
), iwk
(iptt2
), ier
)
3677 if (ier
.ne
. 0) go to 220
3680 c compute new ordering of rows/columns of jacobian. --------------------
3681 160 ipr
= ipigp
+ lenigp
3685 iprsp
= (ipisp
- 2)/lrat
+ 2
3686 iesp
= lenwk
+ 1 - iprsp
3687 if (iesp
.lt
. 0) go to 230
3691 nsp
= liwk
+ 1 - ipisp
3692 CALL odrv
(n
, iwk
(ipian
), iwk
(ipjan
), wk
, iwk
(ipr
), iwk
(ipic
),
3693 1 nsp
, iwk
(ipisp
), 1, iys
)
3694 if (iys
.eq
. 11*n
+1) go to 240
3695 if (iys
.ne
. 0) go to 230
3697 c reorder jan and do symbolic lu factorization of matrix. --------------
3698 ipa
= lenwk
+ 1 - nnz
3700 lreq
= max0
(12*n
/lrat
, 6*n
/lrat
+2*n
+nnz
) + 3
3701 lreq
= lreq
+ iprsp
- 1 + nnz
3702 if (lreq
.gt
. lenwk
) go to 250
3705 180 wk
(iba
+i
) = 0.0d0
3706 ipisp
= lrat*
(iprsp
- 1) + 1
3707 CALL cdrv
(n
,iwk
(ipr
),iwk
(ipc
),iwk
(ipic
),iwk
(ipian
),iwk
(ipjan
),
3708 1 wk
(ipa
),wk
(ipa
),wk
(ipa
),nsp
,iwk
(ipisp
),wk
(iprsp
),iesp
,5,iys
)
3710 if (iys
.eq
. 10*n
+1) go to 250
3711 if (iys
.ne
. 0) go to 260
3713 ipiu
= ipil
+ 2*n
+ 1
3714 nzu
= iwk
(ipil
+n
) - iwk
(ipil
)
3715 nzl
= iwk
(ipiu
+n
) - iwk
(ipiu
)
3716 if (lrat
.gt
. 1) go to 190
3717 CALL adjlr
(n
, iwk
(ipisp
), ldif
)
3720 if (lrat
.eq
. 2 .and
. nnz
.eq
. n
) lreq
= lreq
+ 1
3721 nsp
= nsp
+ lreq
- lenwk
3722 ipa
= lreq
+ 1 - nnz
3728 lreq
= 2 + (2*n
+ 1)/lrat
3729 lreq
= max0
(lenwk
+1,lreq
)
3733 lreq
= (lreq
- 1)/lrat
+ 1
3737 CALL cntnzu
(n
, iwk
(ipian
), iwk
(ipjan
), nzsut
)
3738 lreq
= lenwk
- iesp
+ (3*n
+ 4*nzsut
- 1)/lrat
+ 1
3750 c----------------------- end of subroutine prep ------------------------
3752 subroutine cntnzu
(n
, ia
, ja
, nzsut
)
3753 integer n
, ia
, ja
, nzsut
3754 dimension ia
(1), ja
(1)
3755 c-----------------------------------------------------------------------
3756 c this routine counts the number of nonzero elements in the strict
3757 c upper triangle of the matrix m + m(transpose), where the sparsity
3758 c structure of m is given by pointer arrays ia and ja.
3759 c this is needed to compute the storage requirements for the
3760 c sparse matrix reordering operation in odrv.
3761 c-----------------------------------------------------------------------
3762 integer ii
, jj
, j
, jmin
, jmax
, k
, kmin
, kmax
, num
3768 if (jmin
.gt
. jmax
) go to 50
3770 if (ja
(j
) - ii
) 10, 40, 30
3774 if (kmin
.gt
. kmax
) go to 30
3776 if (ja
(k
) .eq
. ii
) go to 40
3783 c----------------------- end of subroutine cntnzu ----------------------
3786 * (n
, r
, c
, il
, jl
, ijl
, l
, d
, iu
, ju
, iju
, u
, z
, b
, tmp
)
3788 c*** subroutine nntc
3789 c*** numeric solution of the transpose of a sparse nonsymmetric system
3790 c of linear equations given lu-factorization (compressed pointer
3794 c input variables.. n, r, c, il, jl, ijl, l, d, iu, ju, iju, u, b
3795 c output variables.. z
3797 c parameters used internally..
3798 c fia - tmp - temporary vector which gets result of solving ut y = b
3801 c internal variables..
3802 c jmin, jmax - indices of the first and last positions in a row of
3803 c u or l to be used.
3805 integer r
(1), c
(1), il
(1), jl
(1), ijl
(1), iu
(1), ju
(1), iju
(1)
3806 KPP_REAL l
(1), d
(1), u
(1), b
(1), z
(1), tmp
(1), tmpk
,sum
3808 c ****** set tmp to reordered b *************************************
3811 c ****** solve ut y = b by forward substitution *******************
3816 if (jmin
.gt
. jmax
) go to 3
3819 2 tmp
(ju
(mu
+j
)) = tmp
(ju
(mu
+j
)) + tmpk
* u
(j
)
3821 c ****** solve lt x = y by back substitution **********************
3827 if (jmin
.gt
. jmax
) go to 5
3830 4 sum
= sum
+ l
(j
) * tmp
(jl
(ml
+j
))
3831 5 tmp
(k
) = -sum
* d
(k
)
3838 * (n
, r
, c
, il
, jl
, ijl
, l
, d
, iu
, ju
, iju
, u
, z
, b
, tmp
)
3840 c*** subroutine nnsc
3841 c*** numerical solution of sparse nonsymmetric system of linear
3842 c equations given ldu-factorization (compressed pointer storage)
3845 c input variables.. n, r, c, il, jl, ijl, l, d, iu, ju, iju, u, b
3846 c output variables.. z
3848 c parameters used internally..
3849 c fia - tmp - temporary vector which gets result of solving ly = b.
3852 c internal variables..
3853 c jmin, jmax - indices of the first and last positions in a row of
3854 c u or l to be used.
3856 integer r
(1), c
(1), il
(1), jl
(1), ijl
(1), iu
(1), ju
(1), iju
(1)
3857 KPP_REAL l
(1), d
(1), u
(1), b
(1), z
(1), tmp
(1), tmpk
,sum
3859 c ****** set tmp to reordered b *************************************
3862 c ****** solve ly = b by forward substitution *********************
3866 tmpk
= -d
(k
) * tmp
(k
)
3868 if (jmin
.gt
. jmax
) go to 3
3871 2 tmp
(jl
(ml
+j
)) = tmp
(jl
(ml
+j
)) + tmpk
* l
(j
)
3873 c ****** solve ux = y by back substitution ************************
3879 if (jmin
.gt
. jmax
) go to 5
3882 4 sum
= sum
+ u
(j
) * tmp
(ju
(mu
+j
))
3889 subroutine nroc
(n
, ic
, ia
, ja
, a
, jar
, ar
, p
, flag
)
3892 c ----------------------------------------------------------------
3894 c yale sparse matrix package - nonsymmetric codes
3895 c solving the system of equations mx = b
3897 c i. calling sequences
3898 c the coefficient matrix can be processed by an ordering routine
3899 c (e.g., to reduce fillin or ensure numerical stability) before using
3900 c the remaining subroutines. if no reordering is done, then set
3901 c r(i) = c(i) = ic(i) = i for i=1,...,n. if an ordering subroutine
3902 c is used, then nroc should be used to reorder the coefficient matrix
3903 c the calling sequence is --
3904 c ( (matrix ordering))
3905 c (nroc (matrix reordering))
3906 c nsfc (symbolic factorization to determine where fillin will
3907 c occur during numeric factorization)
3908 c nnfc (numeric factorization into product ldu of unit lower
3909 c triangular matrix l, diagonal matrix d, and unit
3910 c upper triangular matrix u, and solution of linear
3912 c nnsc (solution of linear system for additional right-hand
3913 c side using ldu factorization from nnfc)
3914 c (if only one system of equations is to be solved, then the
3915 c subroutine trk should be used.)
3917 c ii. storage of sparse matrices
3918 c the nonzero entries of the coefficient matrix m are stored
3919 c row-by-row in the array a. to identify the individual nonzero
3920 c entries in each row, we need to know in which column each entry
3921 c lies. the column indices which correspond to the nonzero entries
3922 c of m are stored in the array ja. i.e., if a(k) = m(i,j), then
3923 c ja(k) = j. in addition, we need to know where each row starts and
3924 c how long it is. the index positions in ja and a where the rows of
3925 c m begin are stored in the array ia. i.e., if m(i,j) is the first
3926 c (leftmost) entry in the i-th row and a(k) = m(i,j), then
3927 c ia(i) = k. moreover, the index in ja and a of the first location
3928 c following the last element in the last row is stored in ia(n+1).
3929 c thus, the number of entries in the i-th row is given by
3930 c ia(i+1) - ia(i), the nonzero entries of the i-th row are stored
3932 c a(ia(i)), a(ia(i)+1), ..., a(ia(i+1)-1),
3933 c and the corresponding column indices are stored consecutively in
3934 c ja(ia(i)), ja(ia(i)+1), ..., ja(ia(i+1)-1).
3935 c for example, the 5 by 5 matrix
3938 c m = ( 0. 4. 5. 6. 0.)
3941 c would be stored as
3942 c - 1 2 3 4 5 6 7 8 9
3943 c ---+--------------------------
3945 c ja - 1 3 2 2 3 4 4 4 5
3946 c a - 1. 2. 3. 4. 5. 6. 7. 8. 9. .
3948 c the strict upper (lower) triangular portion of the matrix
3949 c u (l) is stored in a similar fashion using the arrays iu, ju, u
3950 c (il, jl, l) except that an additional array iju (ijl) is used to
3951 c compress storage of ju (jl) by allowing some sequences of column
3952 c (row) indices to used for more than one row (column) (n.b., l is
3953 c stored by columns). iju(k) (ijl(k)) points to the starting
3954 c location in ju (jl) of entries for the kth row (column).
3955 c compression in ju (jl) occurs in two ways. first, if a row
3956 c (column) i was merged into the current row (column) k, and the
3957 c number of elements merged in from (the tail portion of) row
3958 c (column) i is the same as the final length of row (column) k, then
3959 c the kth row (column) and the tail of row (column) i are identical
3960 c and iju(k) (ijl(k)) points to the start of the tail. second, if
3961 c some tail portion of the (k-1)st row (column) is identical to the
3962 c head of the kth row (column), then iju(k) (ijl(k)) points to the
3963 c start of that tail portion. for example, the nonzero structure of
3964 c the strict upper triangular part of the matrix
3970 c would be represented as
3976 c the diagonal entries of l and u are assumed to be equal to one and
3977 c are not stored. the array d contains the reciprocals of the
3978 c diagonal entries of the matrix d.
3980 c iii. additional storage savings
3981 c in nsfc, r and ic can be the same array in the calling
3982 c sequence if no reordering of the coefficient matrix has been done.
3983 c in nnfc, r, c, and ic can all be the same array if no
3984 c reordering has been done. if only the rows have been reordered,
3985 c then c and ic can be the same array. if the row and column
3986 c orderings are the same, then r and c can be the same array. z and
3987 c row can be the same array.
3988 c in nnsc or nntc, r and c can be the same array if no
3989 c reordering has been done or if the row and column orderings are the
3990 c same. z and b can be the same array. however, then b will be
3994 c following is a list of parameters to the programs. names are
3995 c uniform among the various subroutines. class abbreviations are --
3996 c n - integer variable
3998 c v - supplies a value to a subroutine
3999 c r - returns a result from a subroutine
4000 c i - used internally by a subroutine
4005 c fva - a - nonzero entries of the coefficient matrix m, stored
4007 c - size = number of nonzero entries in m.
4008 c fva - b - right-hand side b.
4010 c nva - c - ordering of the columns of m.
4012 c fvra - d - reciprocals of the diagonal entries of the matrix d.
4014 c nr - flag - error flag. values and their meanings are --
4015 c - 0 no errors detected
4016 c - n+k null row in a -- row = k
4017 c - 2n+k duplicate entry in a -- row = k
4018 c - 3n+k insufficient storage for jl -- row = k
4019 c - 4n+1 insufficient storage for l
4020 c - 5n+k null pivot -- row = k
4021 c - 6n+k insufficient storage for ju -- row = k
4022 c - 7n+1 insufficient storage for u
4023 c - 8n+k zero pivot -- row = k
4024 c nva - ia - pointers to delimit the rows of a.
4026 c nvra - ijl - pointers to the first element in each column in jl,
4027 c - used to compress storage in jl.
4029 c nvra - iju - pointers to the first element in each row in ju, used
4030 c - to compress storage in ju.
4032 c nvra - il - pointers to delimit the columns of l.
4034 c nvra - iu - pointers to delimit the rows of u.
4036 c nva - ja - column numbers corresponding to the elements of a.
4037 c - size = size of a.
4038 c nvra - jl - row numbers corresponding to the elements of l.
4040 c nv - jlmax - declared dimension of jl. jlmax must be larger than
4041 c - the number of nonzeros in the strict lower triangle
4042 c - of m plus fillin minus compression.
4043 c nvra - ju - column numbers corresponding to the elements of u.
4045 c nv - jumax - declared dimension of ju. jumax must be larger than
4046 c - the number of nonzeros in the strict upper triangle
4047 c - of m plus fillin minus compression.
4048 c fvra - l - nonzero entries in the strict lower triangular portion
4049 c - of the matrix l, stored by columns.
4051 c nv - lmax - declared dimension of l. lmax must be larger than
4052 c - the number of nonzeros in the strict lower triangle
4053 c - of m plus fillin (il(n+1)-1 after nsfc).
4054 c nv - n - number of variables/equations.
4055 c nva - r - ordering of the rows of m.
4057 c fvra - u - nonzero entries in the strict upper triangular portion
4058 c - of the matrix u, stored by rows.
4060 c nv - umax - declared dimension of u. umax must be larger than
4061 c - the number of nonzeros in the strict upper triangle
4062 c - of m plus fillin (iu(n+1)-1 after nsfc).
4063 c fra - z - solution x.
4066 c ----------------------------------------------------------------
4068 c*** subroutine nroc
4069 c*** reorders rows of a, leaving row order unchanged
4072 c input parameters.. n, ic, ia, ja, a
4073 c output parameters.. ja, a, flag
4075 c parameters used internally..
4076 c nia - p - at the kth step, p is a linked list of the reordered
4077 c - column indices of the kth row of a. p(n+1) points
4078 c - to the first entry in the list.
4080 c nia - jar - at the kth step,jar contains the elements of the
4081 c - reordered column indices of a.
4083 c fia - ar - at the kth step, ar contains the elements of the
4084 c - reordered row of a.
4087 integer ic
(1), ia
(1), ja
(1), jar
(1), p
(1), flag
4088 KPP_REAL a
(1), ar
(1)
4090 c ****** for each nonempty row *******************************
4094 if(jmin
.gt
. jmax
) go to 5
4096 c ****** insert each element in the list *********************
4100 1 if(p
(i
) .ge
. newj
) go to 2
4103 2 if(p
(i
) .eq
. newj
) go to 102
4109 c ****** replace old row in ja and a *************************
4119 c ** error.. duplicate entry in a
4123 subroutine adjlr
(n
, isp
, ldif
)
4124 integer n
, isp
, ldif
4126 c-----------------------------------------------------------------------
4127 c this routine computes an adjustment, ldif, to the required
4128 c integer storage space in iwk (sparse matrix work space).
4129 c it is called only if the word length ratio is lrat = 1.
4130 c this is to account for the possibility that the symbolic lu phase
4131 c may require more storage than the numerical lu and solution phases.
4132 c-----------------------------------------------------------------------
4133 integer ip
, jlmax
, jumax
, lnfc
, lsfc
, nzlu
4136 c get jlmax = ijl(n) and jumax = iju(n) (sizes of jl and ju). ----------
4139 c nzlu = (size of l) + (size of u) = (il(n+1)-il(1)) + (iu(n+1)-iu(1)).
4140 nzlu
= isp
(n
+1) - isp
(1) + isp
(ip
+n
+1) - isp
(ip
+1)
4141 lsfc
= 12*n
+ 3 + 2*max0
(jlmax
,jumax
)
4142 lnfc
= 9*n
+ 2 + jlmax
+ jumax
+ nzlu
4143 ldif
= max0
(0, lsfc
- lnfc
)
4145 c----------------------- end of subroutine adjlr -----------------------
4148 * (n
, ia
,ja
,a
, p
,ip
, nsp
,isp
, path
, flag
)
4151 c***********************************************************************
4152 c odrv -- driver for sparse matrix reordering routines
4153 c***********************************************************************
4157 c odrv finds a minimum degree ordering of the rows and columns
4158 c of a matrix m stored in (ia,ja,a) format (see below). for the
4159 c reordered matrix, the work and storage required to perform
4160 c gaussian elimination is (usually) significantly less.
4162 c note.. odrv and its subordinate routines have been modified to
4163 c compute orderings for general matrices, not necessarily having any
4164 c symmetry. the miminum degree ordering is computed for the
4165 c structure of the symmetric matrix m + m-transpose.
4166 c modifications to the original odrv module have been made in
4167 c the coding in subroutine mdi, and in the initial comments in
4168 c subroutines odrv and md.
4170 c if only the nonzero entries in the upper triangle of m are being
4171 c stored, then odrv symmetrically reorders (ia,ja,a), (optionally)
4172 c with the diagonal entries placed first in each row. this is to
4173 c ensure that if m(i,j) will be in the upper triangle of m with
4174 c respect to the new ordering, then m(i,j) is stored in row i (and
4175 c thus m(j,i) is not stored), whereas if m(i,j) will be in the
4176 c strict lower triangle of m, then m(j,i) is stored in row j (and
4177 c thus m(i,j) is not stored).
4180 c storage of sparse matrices
4182 c the nonzero entries of the matrix m are stored row-by-row in the
4183 c array a. to identify the individual nonzero entries in each row,
4184 c we need to know in which column each entry lies. these column
4185 c indices are stored in the array ja. i.e., if a(k) = m(i,j), then
4186 c ja(k) = j. to identify the individual rows, we need to know where
4187 c each row starts. these row pointers are stored in the array ia.
4188 c i.e., if m(i,j) is the first nonzero entry (stored) in the i-th row
4189 c and a(k) = m(i,j), then ia(i) = k. moreover, ia(n+1) points to
4190 c the first location following the last element in the last row.
4191 c thus, the number of entries in the i-th row is ia(i+1) - ia(i),
4192 c the nonzero entries in the i-th row are stored consecutively in
4194 c a(ia(i)), a(ia(i)+1), ..., a(ia(i+1)-1),
4196 c and the corresponding column indices are stored consecutively in
4198 c ja(ia(i)), ja(ia(i)+1), ..., ja(ia(i+1)-1).
4200 c since the coefficient matrix is symmetric, only the nonzero entries
4201 c in the upper triangle need be stored. for example, the matrix
4209 c could be stored as
4211 c - 1 2 3 4 5 6 7 8 9 10 11 12 13
4212 c ---+--------------------------------------
4213 c ia - 1 4 5 8 12 14
4214 c ja - 1 3 4 2 1 3 4 1 3 4 5 4 5
4215 c a - 1 2 3 4 2 5 6 3 6 7 8 8 9
4217 c or (symmetrically) as
4219 c - 1 2 3 4 5 6 7 8 9
4220 c ---+--------------------------
4222 c ja - 1 3 4 2 3 4 4 5 5
4223 c a - 1 2 3 4 5 6 7 8 9 .
4228 c n - order of the matrix
4230 c ia - integer one-dimensional array containing pointers to delimit
4231 c rows in ja and a. dimension = n+1
4233 c ja - integer one-dimensional array containing the column indices
4234 c corresponding to the elements of a. dimension = number of
4235 c nonzero entries in (the upper triangle of) m
4237 c a - real one-dimensional array containing the nonzero entries in
4238 c (the upper triangle of) m, stored by rows. dimension =
4239 c number of nonzero entries in (the upper triangle of) m
4241 c p - integer one-dimensional array used to return the permutation
4242 c of the rows and columns of m corresponding to the minimum
4243 c degree ordering. dimension = n
4245 c ip - integer one-dimensional array used to return the inverse of
4246 c the permutation returned in p. dimension = n
4248 c nsp - declared dimension of the one-dimensional array isp. nsp
4249 c must be at least 3n+4k, where k is the number of nonzeroes
4250 c in the strict upper triangle of m
4252 c isp - integer one-dimensional array used for working storage.
4255 c path - integer path specification. values and their meanings are -
4256 c 1 find minimum degree ordering only
4257 c 2 find minimum degree ordering and reorder symmetrically
4258 c stored matrix (used when only the nonzero entries in
4259 c the upper triangle of m are being stored)
4260 c 3 reorder symmetrically stored matrix as specified by
4261 c input permutation (used when an ordering has already
4262 c been determined and only the nonzero entries in the
4263 c upper triangle of m are being stored)
4264 c 4 same as 2 but put diagonal entries at start of each row
4265 c 5 same as 3 but put diagonal entries at start of each row
4267 c flag - integer error flag. values and their meanings are -
4268 c 0 no errors detected
4269 c 9n+k insufficient storage in md
4270 c 10n+1 insufficient storage in odrv
4271 c 11n+1 illegal path specification
4274 c conversion from real to KPP_REAL
4276 c change the real declarations in odrv and sro to KPP_REAL
4279 c-----------------------------------------------------------------------
4281 integer ia
(1), ja
(1), p
(1), ip
(1), isp
(1), path
, flag
,
4282 * v
, l
, head
, tmp
, q
4286 c----initialize error flag and validate path specification
4288 if (path
.lt
.1 .or
. 5.lt
.path
) go to 111
4290 c----allocate storage and find minimum degree ordering
4291 if ((path
-1) * (path
-2) * (path
-4) .ne
. 0) go to 1
4297 if (max
.lt
.n
) go to 110
4300 * (n
, ia
,ja
, max
,isp
(v
),isp
(l
), isp
(head
),p
,ip
, isp
(v
), flag
)
4301 if (flag
.ne
.0) go to 100
4303 c----allocate storage and symmetrically reorder matrix
4304 1 if ((path
-2) * (path
-3) * (path
-4) * (path
-5) .ne
. 0) go to 2
4306 q
= tmp
- (ia
(n
+1)-1)
4307 if (q
.lt
.1) go to 110
4309 dflag
= path
.eq
.4 .or
. path
.eq
.5
4311 * (n
, ip
, ia
, ja
, a
, isp
(tmp
), isp
(q
), dflag
)
4315 c ** error -- error detected in md
4317 c ** error -- insufficient storage
4320 c ** error -- illegal path specified
4325 * (n
, r
,c
,ic
, ia
,ja
,a
, z
, b
,
4326 * lmax
,il
,jl
,ijl
,l
, d
, umax
,iu
,ju
,iju
,u
,
4327 * row
, tmp
, irl
,jrl
, flag
)
4329 c*** subroutine nnfc
4330 c*** numerical ldu-factorization of sparse nonsymmetric matrix and
4331 c solution of system of linear equations (compressed pointer
4335 c input variables.. n, r, c, ic, ia, ja, a, b,
4336 c il, jl, ijl, lmax, iu, ju, iju, umax
4337 c output variables.. z, l, d, u, flag
4339 c parameters used internally..
4340 c nia - irl, - vectors used to find the rows of l. at the kth step
4341 c nia - jrl of the factorization, jrl(k) points to the head
4342 c - of a linked list in jrl of column indices j
4343 c - such j .lt. k and l(k,j) is nonzero. zero
4344 c - indicates the end of the list. irl(j) (j.lt.k)
4345 c - points to the smallest i such that i .ge. k and
4346 c - l(i,j) is nonzero.
4347 c - size of each = n.
4348 c fia - row - holds intermediate values in calculation of u and l.
4350 c fia - tmp - holds new right-hand side b* for solution of the
4351 c - equation ux = b*.
4354 c internal variables..
4355 c jmin, jmax - indices of the first and last positions in a row to
4357 c sum - used in calculating tmp.
4360 integer r
(1), c
(1), ic
(1), ia
(1), ja
(1), il
(1), jl
(1), ijl
(1)
4361 integer iu
(1), ju
(1), iju
(1), irl
(1), jrl
(1), flag
4362 KPP_REAL a
(1), l
(1), d
(1), u
(1), z
(1), b
(1), row
(1)
4363 KPP_REAL tmp
(1), lki
, sum
, dk
4365 c ****** initialize pointers and test storage ***********************
4366 if(il
(n
+1)-1 .gt
. lmax
) go to 104
4367 if(iu
(n
+1)-1 .gt
. umax
) go to 107
4373 c ****** for each row ***********************************************
4375 c ****** reverse jrl and zero row where kth row of l will fill in ***
4378 if (jrl
(k
) .eq
. 0) go to 3
4385 if (i
.ne
. 0) go to 2
4386 c ****** set row to zero where u will fill in ***********************
4388 jmax
= jmin
+ iu
(k
+1) - iu
(k
) - 1
4389 if (jmin
.gt
. jmax
) go to 5
4392 c ****** place kth row of a in row **********************************
4397 row
(ic
(ja
(j
))) = a
(j
)
4399 c ****** initialize sum, and link through jrl ***********************
4402 if (i
.eq
. 0) go to 10
4403 c ****** assign the kth row of l and adjust row, sum ****************
4405 c ****** if l is not required, then comment out the following line **
4407 sum
= sum
+ lki
* tmp
(i
)
4410 if (jmin
.gt
. jmax
) go to 9
4413 8 row
(ju
(mu
+j
)) = row
(ju
(mu
+j
)) + lki
* u
(j
)
4415 if (i
.ne
. 0) go to 7
4417 c ****** assign kth row of u and diagonal d, set tmp(k) *************
4418 10 if (row
(k
) .eq
. 0.0d0
) go to 108
4422 if (k
.eq
. n
) go to 19
4425 if (jmin
.gt
. jmax
) go to 12
4428 11 u
(j
) = row
(ju
(mu
+j
)) * dk
4431 c ****** update irl and jrl, keeping jrl in decreasing order ********
4433 if (i
.eq
. 0) go to 18
4434 14 irl
(i
) = irl
(i
) + 1
4436 if (irl
(i
) .ge
. il
(i
+1)) go to 17
4437 ijlb
= irl
(i
) - il
(i
) + ijl
(i
)
4439 15 if (i
.gt
. jrl
(j
)) go to 16
4445 if (i
.ne
. 0) go to 14
4446 18 if (irl
(k
) .ge
. il
(k
+1)) go to 19
4452 c ****** solve ux = tmp by back substitution **********************
4458 if (jmin
.gt
. jmax
) go to 21
4461 20 sum
= sum
- u
(j
) * tmp
(ju
(mu
+j
))
4468 c ** error.. insufficient storage for l
4471 c ** error.. insufficient storage for u
4474 c ** error.. zero pivot
4478 subroutine jgroup
(n
,ia
,ja
,maxg
,ngrp
,igp
,jgp
,incl
,jdone
,ier
)
4480 integer n
, ia
, ja
, maxg
, ngrp
, igp
, jgp
, incl
, jdone
, ier
4481 dimension ia
(1), ja
(1), igp
(1), jgp
(n
), incl
(n
), jdone
(n
)
4482 c-----------------------------------------------------------------------
4483 c this subroutine constructs groupings of the column indices of
4484 c the jacobian matrix, used in the numerical evaluation of the
4485 c jacobian by finite differences.
4488 c n = the order of the matrix.
4489 c ia,ja = sparse structure descriptors of the matrix by rows.
4490 c maxg = length of available storate in the igp array.
4493 c ngrp = number of groups.
4494 c jgp = array of length n containing the column indices by groups.
4495 c igp = pointer array of length ngrp + 1 to the locations in jgp
4496 c of the beginning of each group.
4497 c ier = error indicator. ier = 0 if no error occurred, or 1 if
4498 c maxg was insufficient.
4500 c incl and jdone are working arrays of length n.
4501 c-----------------------------------------------------------------------
4502 integer i
, j
, k
, kmin
, kmax
, ncol
, ng
4513 c reject column j if it is already in a group.--------------------------
4514 if (jdone
(j
) .eq
. 1) go to 50
4518 c reject column j if it overlaps any column already in this group.------
4520 if (incl
(i
) .eq
. 1) go to 50
4522 c accept column j into group ng.----------------------------------------
4530 c stop if this group is empty (grouping is complete).-------------------
4531 if (ncol
.eq
. igp
(ng
)) go to 70
4533 c error return if not all columns were chosen (maxg too small).---------
4534 if (ncol
.le
. n
) go to 80
4540 c----------------------- end of subroutine jgroup ----------------------
4543 * (n
, r
, ic
, ia
,ja
, jlmax
,il
,jl
,ijl
, jumax
,iu
,ju
,iju
,
4544 * q
, ira
,jra
, irac
, irl
,jrl
, iru
,jru
, flag
)
4546 c*** subroutine nsfc
4547 c*** symbolic ldu-factorization of nonsymmetric sparse matrix
4548 c (compressed pointer storage)
4551 c input variables.. n, r, ic, ia, ja, jlmax, jumax.
4552 c output variables.. il, jl, ijl, iu, ju, iju, flag.
4554 c parameters used internally..
4555 c nia - q - suppose m* is the result of reordering m. if
4556 c - processing of the ith row of m* (hence the ith
4557 c - row of u) is being done, q(j) is initially
4558 c - nonzero if m*(i,j) is nonzero (j.ge.i). since
4559 c - values need not be stored, each entry points to the
4560 c - next nonzero and q(n+1) points to the first. n+1
4561 c - indicates the end of the list. for example, if n=9
4562 c - and the 5th row of m* is
4563 c - 0 x x 0 x 0 0 x 0
4564 c - then q will initially be
4565 c - a a a a 8 a a 10 5 (a - arbitrary).
4566 c - as the algorithm proceeds, other elements of q
4567 c - are inserted in the list because of fillin.
4568 c - q is used in an analogous manner to compute the
4569 c - ith column of l.
4571 c nia - ira, - vectors used to find the columns of m. at the kth
4572 c nia - jra, step of the factorization, irac(k) points to the
4573 c nia - irac head of a linked list in jra of row indices i
4574 c - such that i .ge. k and m(i,k) is nonzero. zero
4575 c - indicates the end of the list. ira(i) (i.ge.k)
4576 c - points to the smallest j such that j .ge. k and
4577 c - m(i,j) is nonzero.
4578 c - size of each = n.
4579 c nia - irl, - vectors used to find the rows of l. at the kth step
4580 c nia - jrl of the factorization, jrl(k) points to the head
4581 c - of a linked list in jrl of column indices j
4582 c - such j .lt. k and l(k,j) is nonzero. zero
4583 c - indicates the end of the list. irl(j) (j.lt.k)
4584 c - points to the smallest i such that i .ge. k and
4585 c - l(i,j) is nonzero.
4586 c - size of each = n.
4587 c nia - iru, - vectors used in a manner analogous to irl and jrl
4588 c nia - jru to find the columns of u.
4589 c - size of each = n.
4591 c internal variables..
4592 c jlptr - points to the last position used in jl.
4593 c juptr - points to the last position used in ju.
4594 c jmin,jmax - are the indices in a or u of the first and last
4595 c elements to be examined in a given row.
4596 c for example, jmin=ia(k), jmax=ia(k+1)-1.
4598 integer cend
, qm
, rend
, rk
, vj
4599 integer ia
(1), ja
(1), ira
(1), jra
(1), il
(1), jl
(1), ijl
(1)
4600 integer iu
(1), ju
(1), iju
(1), irl
(1), jrl
(1), iru
(1), jru
(1)
4601 integer r
(1), ic
(1), q
(1), irac
(1), flag
4603 c ****** initialize pointers ****************************************
4616 c ****** initialize column pointers for a ***************************
4620 if (iak
.ge
. ia
(rk
+1)) go to 101
4622 if (jaiak
.gt
. k
) go to 105
4623 jra
(k
) = irac
(jaiak
)
4627 c ****** for each column of l and row of u **************************
4630 c ****** initialize q for computing kth column of l *****************
4633 c ****** by filling in kth column of a ******************************
4635 if (vj
.eq
. 0) go to 5
4639 if (qm
.lt
. vj
) go to 4
4640 if (qm
.eq
. vj
) go to 102
4645 if (vj
.ne
. 0) go to 3
4646 c ****** link through jru *******************************************
4652 if (i
.eq
. 0) go to 10
4655 jmax
= ijl
(i
) + il
(i
+1) - il
(i
) - 1
4657 if (long
.lt
. 0) go to 6
4659 if (jtmp
.ne
. k
) long
= long
+ 1
4660 if (jtmp
.eq
. k
) r
(i
) = -r
(i
)
4661 if (lastid
.ge
. long
) go to 7
4664 c ****** and merge the corresponding columns into the kth column ****
4669 if (qm
.lt
. vj
) go to 8
4670 if (qm
.eq
. vj
) go to 9
4677 c ****** lasti is the longest column merged into the kth ************
4678 c ****** see if it equals the entire kth column *********************
4680 if (qm
.ne
. k
) go to 105
4681 if (luk
.eq
. 0) go to 17
4682 if (lastid
.ne
. luk
) go to 11
4683 c ****** if so, jl can be compressed ********************************
4686 if (jl
(irll
) .ne
. k
) ijl
(k
) = ijl
(k
) - 1
4688 c ****** if not, see if kth column can overlap the previous one *****
4689 11 if (jlmin
.gt
. jlptr
) go to 15
4692 if (jl
(j
) - qm
) 12, 13, 15
4697 if (jl
(i
) .ne
. qm
) go to 15
4699 if (qm
.gt
. n
) go to 17
4702 c ****** move column indices from q to jl, update vectors ***********
4703 15 jlmin
= jlptr
+ 1
4705 if (luk
.eq
. 0) go to 17
4707 if (jlptr
.gt
. jlmax
) go to 103
4713 il
(k
+1) = il
(k
) + luk
4715 c ****** initialize q for computing kth row of u ********************
4718 c ****** by filling in kth row of reordered a ***********************
4722 if (jmin
.gt
. jmax
) go to 20
4728 if (qm
.lt
. vj
) go to 18
4729 if (qm
.eq
. vj
) go to 102
4734 c ****** link through jrl, ******************************************
4741 if (i
.eq
. 0) go to 26
4745 jmax
= iju
(i
) + iu
(i
+1) - iu
(i
) - 1
4747 if (long
.lt
. 0) go to 21
4749 if (jtmp
.eq
. k
) go to 22
4750 c ****** update irl and jrl, *****************************************
4752 cend
= ijl
(i
) + il
(i
+1) - il
(i
)
4754 if (irl
(i
) .ge
. cend
) go to 22
4758 22 if (lastid
.ge
. long
) go to 23
4761 c ****** and merge the corresponding rows into the kth row **********
4762 23 do 25 j
=jmin
,jmax
4766 if (qm
.lt
. vj
) go to 24
4767 if (qm
.eq
. vj
) go to 25
4774 c ****** update jrl(k) and irl(k) ***********************************
4775 26 if (il
(k
+1) .le
. il
(k
)) go to 27
4779 c ****** lasti is the longest row merged into the kth ***************
4780 c ****** see if it equals the entire kth row ************************
4782 if (qm
.ne
. k
) go to 105
4783 if (luk
.eq
. 0) go to 34
4784 if (lastid
.ne
. luk
) go to 28
4785 c ****** if so, ju can be compressed ********************************
4788 if (ju
(irul
) .ne
. k
) iju
(k
) = iju
(k
) - 1
4790 c ****** if not, see if kth row can overlap the previous one ********
4791 28 if (jumin
.gt
. juptr
) go to 32
4794 if (ju
(j
) - qm
) 29, 30, 32
4799 if (ju
(i
) .ne
. qm
) go to 32
4801 if (qm
.gt
. n
) go to 34
4804 c ****** move row indices from q to ju, update vectors **************
4805 32 jumin
= juptr
+ 1
4807 if (luk
.eq
. 0) go to 34
4809 if (juptr
.gt
. jumax
) go to 106
4815 iu
(k
+1) = iu
(k
) + luk
4817 c ****** update iru, jru ********************************************
4820 if (r
(i
) .lt
. 0) go to 36
4821 rend
= iju
(i
) + iu
(i
+1) - iu
(i
)
4822 if (iru
(i
) .ge
. rend
) go to 37
4829 if (i
.eq
. 0) go to 38
4833 c ****** update ira, jra, irac **************************************
4835 if (i
.eq
. 0) go to 41
4838 if (ira
(i
) .ge
. ia
(r
(i
)+1)) go to 40
4840 jairai
= ic
(ja
(irai
))
4841 if (jairai
.gt
. i
) go to 40
4842 jra
(i
) = irac
(jairai
)
4845 if (i
.ne
. 0) go to 39
4853 c ** error.. null row in a
4856 c ** error.. duplicate entry in a
4859 c ** error.. insufficient storage for jl
4862 c ** error.. null pivot
4865 c ** error.. insufficient storage for ju
4870 * (n
, ip
, ia
,ja
,a
, q
, r
, dflag
)
4872 c***********************************************************************
4873 c sro -- symmetric reordering of sparse symmetric matrix
4874 c***********************************************************************
4878 c the nonzero entries of the matrix m are assumed to be stored
4879 c symmetrically in (ia,ja,a) format (i.e., not both m(i,j) and m(j,i)
4880 c are stored if i ne j).
4882 c sro does not rearrange the order of the rows, but does move
4883 c nonzeroes from one row to another to ensure that if m(i,j) will be
4884 c in the upper triangle of m with respect to the new ordering, then
4885 c m(i,j) is stored in row i (and thus m(j,i) is not stored), whereas
4886 c if m(i,j) will be in the strict lower triangle of m, then m(j,i) is
4887 c stored in row j (and thus m(i,j) is not stored).
4890 c additional parameters
4892 c q - integer one-dimensional work array. dimension = n
4894 c r - integer one-dimensional work array. dimension = number of
4895 c nonzero entries in the upper triangle of m
4897 c dflag - logical variable. if dflag = .true., then store nonzero
4898 c diagonal elements at the beginning of the row
4900 c-----------------------------------------------------------------------
4902 integer ip
(1), ia
(1), ja
(1), q
(1), r
(1)
4907 c--phase 1 -- find row in which to store each nonzero
4908 c----initialize count of nonzeroes to be stored in each row
4912 c----for each nonzero element a(j)
4916 if (jmin
.gt
.jmax
) go to 3
4919 c--------find row (=r(j)) and column (=ja(j)) in which to store a(j) ...
4921 if (ip
(k
).lt
.ip
(i
)) ja
(j
) = i
4922 if (ip
(k
).ge
.ip
(i
)) k
= i
4925 c--------... and increment count of nonzeroes (=q(r(j)) in that row
4930 c--phase 2 -- find new ia and permutation to apply to (ja,a)
4931 c----determine pointers to delimit rows in permuted (ja,a)
4933 ia
(i
+1) = ia
(i
) + q
(i
)
4936 c----determine where each (ja(j),a(j)) is stored in permuted (ja,a)
4937 c----for each nonzero element (in reverse order)
4942 do 6 jdummy
=jmin
,jmax
4944 if (.not
.dflag
.or
. ja
(j
).ne
.i
.or
. i
.eq
.ilast
) go to 5
4946 c------if dflag, then put diagonal nonzero at beginning of row
4951 c------put (off-diagonal) nonzero in last unused location in row
4958 c--phase 3 -- permute (ja,a) to upper triangular form (wrt new ordering)
4960 7 if (r
(j
).eq
.j
) go to 8
4976 * (n
, ia
,ja
, max
, v
,l
, head
,last
,next
, mark
, flag
)
4978 c***********************************************************************
4979 c md -- minimum degree algorithm (based on element model)
4980 c***********************************************************************
4984 c md finds a minimum degree ordering of the rows and columns of a
4985 c general sparse matrix m stored in (ia,ja,a) format.
4986 c when the structure of m is nonsymmetric, the ordering is that
4987 c obtained for the symmetric matrix m + m-transpose.
4990 c additional parameters
4992 c max - declared dimension of the one-dimensional arrays v and l.
4993 c max must be at least n+2k, where k is the number of
4994 c nonzeroes in the strict upper triangle of m + m-transpose
4996 c v - integer one-dimensional work array. dimension = max
4998 c l - integer one-dimensional work array. dimension = max
5000 c head - integer one-dimensional work array. dimension = n
5002 c last - integer one-dimensional array used to return the permutation
5003 c of the rows and columns of m corresponding to the minimum
5004 c degree ordering. dimension = n
5006 c next - integer one-dimensional array used to return the inverse of
5007 c the permutation returned in last. dimension = n
5009 c mark - integer one-dimensional work array (may be the same as v).
5012 c flag - integer error flag. values and their meanings are -
5013 c 0 no errors detected
5014 c 9n+k insufficient storage in md
5017 c definitions of internal parameters
5019 c ---------+---------------------------------------------------------
5020 c v(s) - value field of list entry
5021 c ---------+---------------------------------------------------------
5022 c l(s) - link field of list entry (0 =) end of list)
5023 c ---------+---------------------------------------------------------
5024 c l(vi) - pointer to element list of uneliminated vertex vi
5025 c ---------+---------------------------------------------------------
5026 c l(ej) - pointer to boundary list of active element ej
5027 c ---------+---------------------------------------------------------
5028 c head(d) - vj =) vj head of d-list d
5029 c - 0 =) no vertex in d-list d
5032 c - vi uneliminated vertex
5033 c - vi in ek - vi not in ek
5034 c ---------+-----------------------------+---------------------------
5035 c next(vi) - undefined but nonnegative - vj =) vj next in d-list
5036 c - - 0 =) vi tail of d-list
5037 c ---------+-----------------------------+---------------------------
5038 c last(vi) - (not set until mdp) - -d =) vi head of d-list d
5039 c --vk =) compute degree - vj =) vj last in d-list
5040 c - ej =) vi prototype of ej - 0 =) vi not in any d-list
5041 c - 0 =) do not compute degree -
5042 c ---------+-----------------------------+---------------------------
5043 c mark(vi) - mark(vk) - nonneg. tag .lt. mark(vk)
5046 c - vi eliminated vertex
5047 c - ei active element - otherwise
5048 c ---------+-----------------------------+---------------------------
5049 c next(vi) - -j =) vi was j-th vertex - -j =) vi was j-th vertex
5050 c - to be eliminated - to be eliminated
5051 c ---------+-----------------------------+---------------------------
5052 c last(vi) - m =) size of ei = m - undefined
5053 c ---------+-----------------------------+---------------------------
5054 c mark(vi) - -m =) overlap count of ei - undefined
5056 c - otherwise nonnegative tag -
5059 c-----------------------------------------------------------------------
5061 integer ia
(1), ja
(1), v
(1), l
(1), head
(1), last
(1), next
(1),
5062 * mark
(1), flag
, tag
, dmin
, vk
,ek
, tail
5068 * (n
, ia
,ja
, max
,v
,l
, head
,last
,next
, mark
,tag
, flag
)
5069 if (flag
.ne
.0) return
5074 c----while k .lt. n do
5075 1 if (k
.ge
.n
) go to 4
5077 c------search for vertex of minimum degree
5078 2 if (head
(dmin
).gt
.0) go to 3
5082 c------remove vertex vk of minimum degree from degree list
5084 head
(dmin
) = next
(vk
)
5085 if (head
(dmin
).gt
.0) last
(head
(dmin
)) = -dmin
5087 c------number vertex vk, adjust tag, and tag vk
5091 tag
= tag
+ last
(ek
)
5094 c------form element ek from uneliminated neighbors of vk
5096 * (vk
,tail
, v
,l
, last
,next
, mark
)
5098 c------purge inactive elements and do mass elimination
5100 * (k
,ek
,tail
, v
,l
, head
,last
,next
, mark
)
5102 c------update degrees of uneliminated vertices in ek
5104 * (ek
,dmin
, v
,l
, head
,last
,next
, mark
)
5108 c----generate inverse permutation from permutation
5116 * (n
, ia
,ja
, max
,v
,l
, head
,last
,next
, mark
,tag
, flag
)
5118 c***********************************************************************
5119 c mdi -- initialization
5120 c***********************************************************************
5121 integer ia
(1), ja
(1), v
(1), l
(1), head
(1), last
(1), next
(1),
5122 * mark
(1), tag
, flag
, sfs
, vi
,dvi
, vj
5124 c----initialize degrees, element lists, and degree lists
5131 c----create nonzero structure
5132 c----for each nonzero entry a(vi,vj)
5136 if (jmin
.gt
.jmax
) go to 6
5141 c------if a(vi,vj) is in strict lower triangle
5142 c------check for previous occurrence of a(vj,vi)
5145 if (kmax
.eq
. 0) go to 4
5148 if (v
(lvk
).eq
.vj
) go to 5
5150 c----for unentered entries a(vi,vj)
5151 4 if (sfs
.ge
.max
) go to 101
5153 c------enter vj in element list for vi
5154 mark
(vi
) = mark
(vi
) + 1
5160 c------enter vi in element list for vj
5161 mark
(vj
) = mark
(vj
) + 1
5169 c----create degree lists and initialize mark vector
5172 next
(vi
) = head
(dvi
)
5176 if (nextvi
.gt
.0) last
(nextvi
) = vi
5181 c ** error- insufficient storage
5186 * (vk
,tail
, v
,l
, last
,next
, mark
)
5188 c***********************************************************************
5189 c mdm -- form element from uneliminated neighbors of vk
5190 c***********************************************************************
5191 integer vk
, tail
, v
(1), l
(1), last
(1), next
(1), mark
(1),
5192 * tag
, s
,ls
,vs
,es
, b
,lb
,vb
, blp
,blpmax
5193 equivalence
(vs
, es
)
5195 c----initialize tag and list of uneliminated neighbors
5199 c----for each vertex/element vs/es in element list of vk
5205 if (next
(vs
).lt
.0) go to 2
5207 c------if vs is uneliminated vertex, then tag and append to list of
5208 c------uneliminated neighbors
5214 c------if es is active element, then ...
5215 c--------for each vertex vb in boundary list of element es
5223 c----------if vb is untagged vertex, then tag and append to list of
5224 c----------uneliminated neighbors
5225 if (mark
(vb
).ge
.tag
) go to 3
5231 c--------mark es inactive
5236 c----terminate list of uneliminated neighbors
5242 * (k
,ek
,tail
, v
,l
, head
,last
,next
, mark
)
5244 c***********************************************************************
5245 c mdp -- purge inactive elements and do mass elimination
5246 c***********************************************************************
5247 integer ek
, tail
, v
(1), l
(1), head
(1), last
(1), next
(1),
5248 * mark
(1), tag
, free
, li
,vi
,lvi
,evi
, s
,ls
,es
, ilp
,ilpmax
5253 c----for each vertex vi in ek
5256 if (ilpmax
.le
.0) go to 12
5262 c------remove vi from degree list
5263 if (last
(vi
).eq
.0) go to 3
5264 if (last
(vi
).gt
.0) go to 1
5265 head
(-last
(vi
)) = next
(vi
)
5267 1 next
(last
(vi
)) = next
(vi
)
5268 2 if (next
(vi
).gt
.0) last
(next
(vi
)) = last
(vi
)
5270 c------remove inactive items from element list of vi
5274 if (ls
.eq
.0) go to 6
5276 if (mark
(es
).lt
.tag
) go to 5
5282 c------if vi is interior vertex, then remove from list and eliminate
5284 if (lvi
.ne
.0) go to 7
5290 last
(ek
) = last
(ek
) - 1
5294 c--------classify vertex vi
5295 7 if (l
(lvi
).ne
.0) go to 9
5297 if (next
(evi
).ge
.0) go to 9
5298 if (mark
(evi
).lt
.0) go to 8
5300 c----------if vi is prototype vertex, then mark as such, initialize
5301 c----------overlap count for corresponding element, and move vi to end
5302 c----------of boundary list
5311 c----------else if vi is duplicate vertex, then mark as such and adjust
5312 c----------overlap count for corresponding element
5314 mark
(evi
) = mark
(evi
) - 1
5317 c----------else mark vi to compute degree
5320 c--------insert ek in element list of vi
5326 c----terminate boundary list
5332 * (ek
,dmin
, v
,l
, head
,last
,next
, mark
)
5334 c***********************************************************************
5335 c mdu -- update degrees of uneliminated vertices in ek
5336 c***********************************************************************
5337 integer ek
, dmin
, v
(1), l
(1), head
(1), last
(1), next
(1),
5338 * mark
(1), tag
, vi
,evi
,dvi
, s
,vs
,es
, b
,vb
, ilp
,ilpmax
,
5340 equivalence
(vs
, es
)
5343 tag
= mark
(ek
) - last
(ek
)
5345 c----for each vertex vi in ek
5348 if (ilpmax
.le
.0) go to 11
5352 if (last
(vi
)) 1, 10, 8
5354 c------if vi neither prototype nor duplicate vertex, then merge elements
5355 c------to compute degree
5359 c--------for each vertex/element vs/es in element list of vi
5364 if (next
(vs
).lt
.0) go to 3
5366 c----------if vs is uneliminated vertex, then tag and adjust degree
5371 c----------if es is active element, then expand
5372 c------------check for outmatched vertex
5373 3 if (mark
(es
).lt
.0) go to 6
5375 c------------for each vertex vb in es
5382 c--------------if vb is untagged, then tag and adjust degree
5383 if (mark
(vb
).ge
.tag
) go to 4
5390 c------else if vi is outmatched vertex, then adjust overlaps but do not
5391 c------compute degree
5393 mark
(es
) = mark
(es
) - 1
5395 if (s
.eq
.0) go to 10
5397 if (mark
(es
).lt
.0) mark
(es
) = mark
(es
) - 1
5400 c------else if vi is prototype vertex, then calculate degree by
5401 c------inclusion/exclusion and reset overlap count
5403 dvi
= last
(ek
) + last
(evi
) + mark
(evi
)
5406 c------insert vi in appropriate degree list
5407 9 next
(vi
) = head
(dvi
)
5410 if (next
(vi
).gt
.0) last
(next
(vi
)) = vi
5411 if (dvi
.lt
.dmin
) dmin
= dvi
5417 KPP_REAL
FUNCTION D1MACH
(IDUM
)
5419 C-----------------------------------------------------------------------
5420 C This routine computes the unit roundoff of the machine.
5421 C This is defined as the smallest positive machine number
5422 C u such that 1.0 + u .ne. 1.0
5424 C Subroutines/functions called by D1MACH.. None
5425 C-----------------------------------------------------------------------
5430 IF (COMP
.NE
. 1.0D0
) GO TO 10
5433 C----------------------- End of Function D1MACH ------------------------
5436 SUBROUTINE FUNC_CHEM
(N
, T
, V
, FCT
)
5438 INCLUDE
'KPP_ROOT_Parameters.h'
5439 INCLUDE
'KPP_ROOT_Global.h'
5440 KPP_REAL V
(NVAR
), FCT
(NVAR
)
5446 CALL Update_RCONST
()
5448 CALL Fun
(V
, FIX
, RCONST
, FCT
)
5452 SUBROUTINE JAC_CHEM
(N
, T
, V
, JV
, j
, ian
, jan
)
5454 INCLUDE
'KPP_ROOT_Parameters.h'
5455 INCLUDE
'KPP_ROOT_Global.h'
5456 KPP_REAL V
(NVAR
), JV
(NVAR
,NVAR
)
5458 INTEGER N
, j
, ian
(1), jan
(1), ii
, jj
5462 CALL Update_RCONST
()
5470 call Jac
(V
, FIX
, RCONST
, JV
)