1 !**********************************************************************************
2 ! This computer software was prepared by Battelle Memorial Institute, hereinafter
3 ! the Contractor, under Contract No. DE-AC05-76RL0 1830 with the Department of
4 ! Energy (DOE). NEITHER THE GOVERNMENT NOR THE CONTRACTOR MAKES ANY WARRANTY,
5 ! EXPRESS OR IMPLIED, OR ASSUMES ANY LIABILITY FOR THE USE OF THIS SOFTWARE.
7 ! CBMZ module: see module_cbmz.F for references and terms of use
8 !**********************************************************************************
9 module module_cbmz_rodas3_solver
14 !-----------------------------------------------------------------------
16 subroutine rodas3_ff_x2( n, t, tnext, hmin, hmax, hstart, &
17 y, abstol, reltol, yposlimit, yneglimit, &
19 lu_nonzero_v, lu_crow_v, lu_diag_v, lu_icol_v, &
21 dydtsubr, yjacsubr, decompsubr, solvesubr )
22 ! include 'sparse_s.h'
24 ! stiffly accurate rosenbrock 3(2), with
25 ! stiffly accurate embedded formula for error control.
27 ! all the arguments aggree with the kpp syntax.
30 ! n = number of dependent variables (i.e., time-varying species)
31 ! [t, tnext] = the integration interval
32 ! hmin, hmax = lower and upper bounds for the selected step-size.
33 ! note that for step = hmin the current computed
34 ! solution is unconditionally accepted by the error
36 ! hstart = initial guess step-size
37 ! y = vector of (n) concentrations, contains the
38 ! initial values on input
39 ! abstol, reltol = (n) dimensional vectors of
40 ! componentwise absolute and relative tolerances.
41 ! yposlimit = vector of (n) upper-limit positive concentrations
42 ! yneglimit = vector of (n) upper-limit negative concentrations
43 ! yfixed = vector of (*) concentrations of fixed/non-reacting species
44 ! rconst = vector of (*) concentrations of fixed/non-reacting species
46 ! lu_nonzero_v = number of non-zero entries in the "augmented jacobian"
47 ! (i.e., the jacobian with all diagonal elements filled in)
48 ! lu_crow_v = vector of (n) pointers to the crow (?) elements
49 ! lu_diag_v = vector of (n) pointers to the diagonal elements
50 ! of the sparsely organized jacobian.
51 ! jac(lu_diag_v(i)) is the i,i diagonal element
52 ! lu_icol_v = vector of (lu_nonzero_v) pointers to the icol (?) elements
53 ! info(1) = 1 for autonomous system
54 ! = 0 for nonautonomous system
55 ! iok = completion code (output)
56 ! +1 = successful integration
57 ! +2 = successful integration, but some substeps were h=hmin
58 ! and error > abstol,reltol
59 ! -1 = failure -- lu decomposition failed with minimum stepsize h=hmin
60 ! -1001 --> -1999 = failure -- with minimum stepsize h=hmin,
61 ! species i = -(iok+1000) was NaN
62 ! -2001 --> -2999 = failure -- with minimum stepsize h=hmin,
63 ! species i = -(iok+2000) was > yneglimit
64 ! -3001 --> -3999 = failure -- with minimum stepsize h=hmin,
65 ! species i = -(iok+3000) was < yposlimit
66 ! -5001 --> -5999 = failure -- with minimum stepsize h=hmin,
67 ! species i = -(iok+5000) had abs(kn(i)) > ylimit_solvesubr
68 ! before call to solvesubr, where kn is either k1,k2,k3,k4
70 ! dydtsubr = name of routine of derivatives. kpp syntax.
71 ! see the header below.
72 ! yjacsubr = name of routine that computes the jacobian, in
73 ! sparse format. kpp syntax. see the header below.
74 ! decompsubr = name of routine that does sparse lu decomposition
75 ! solvesubr = name of routine that does sparse lu backsolve
78 ! y = the values of concentrations at tend.
79 ! t = equals tend on output.
80 ! info(2) = # of dydtsubr calls.
81 ! info(3) = # of yjacsubr calls.
82 ! info(4) = # of accepted steps.
83 ! info(5) = # of rejected steps.
84 ! info(6) = # of steps that were accepted but had
85 ! (hold.eq.hmin) .and. (err.gt.1)
86 ! which means stepsize=minimum and error>tolerance
88 ! adrian sandu, march 1996
89 ! the center for global and regional environmental research
91 use module_peg_util, only: peg_message, peg_error_fatal
95 integer nvar_maxd, lu_nonzero_v_maxd
96 parameter (nvar_maxd=99)
97 parameter (lu_nonzero_v_maxd=999)
99 ! common block variables
102 integer n, info(6), iok, lunerr, lu_nonzero_v
103 integer lu_crow_v(n), lu_diag_v(n), lu_icol_v(lu_nonzero_v)
104 real t, tnext, hmin, hmax, hstart
105 real y(n), abstol(n), reltol(n), yposlimit(n), yneglimit(n)
106 real yfixed(*), rconst(*)
107 external dydtsubr, yjacsubr, decompsubr, solvesubr
110 logical isreject, autonom
111 integer nfcn, njac, naccept, nreject, nnocnvg, i, j
114 real k1(nvar_maxd), k2(nvar_maxd)
115 real k3(nvar_maxd), k4(nvar_maxd)
116 real f1(nvar_maxd), ynew(nvar_maxd)
117 real jac(lu_nonzero_v_maxd)
119 real tin, tplus, h, hold, hlowest
120 real err, factor, facmax
121 real dround, c43, tau, x1, x2, ytol
122 real ylimit_solvesubr
126 ylimit_solvesubr = 1.0e18
128 ! check n and lu_nonzero_v
129 if (n .gt. nvar_maxd) then
130 call peg_message( lunerr, '*** rodas3 dimensioning problem' )
131 write(errmsg,9050) 'n, nvar_maxd = ', n, nvar_maxd
132 call peg_message( lunerr, errmsg )
133 call peg_error_fatal( lunerr, '*** rodas3 fatal error' )
134 else if (lu_nonzero_v .gt. lu_nonzero_v_maxd) then
135 call peg_message( lunerr, '*** rodas3 dimensioning problem' )
136 write(errmsg,9050) 'lu_nonvero_v, lu_nonzero_v_maxd = ', &
137 lu_nonzero_v, lu_nonzero_v_maxd
138 call peg_message( lunerr, errmsg )
139 call peg_error_fatal( lunerr, '*** rodas3 fatal error' )
141 9050 format( a, 2(1x,i6) )
145 dround = sqrt(uround)
147 ! check hmin and hmax
149 if (info(1) .eq. 1) hlowest = 1.0e-7
150 if (hmin .lt. hlowest) then
151 call peg_message( lunerr, '*** rodas3 -- hmin is too small' )
152 write(errmsg,9060) 'hmin and minimum allowed value = ', &
154 call peg_message( lunerr, errmsg )
155 call peg_error_fatal( lunerr, '*** rodas3 fatal error' )
156 else if (hmin .ge. hmax) then
157 call peg_message( lunerr, '*** rodas3 -- hmin >= hmax' )
158 write(errmsg,9060) 'hmin, hmax = ', hmin, hmax
159 call peg_message( lunerr, errmsg )
160 call peg_error_fatal( lunerr, '*** rodas3 fatal error' )
162 9060 format( a, 1p, 2e14.4 )
164 ! initialization of counters, etc.
165 autonom = info(1) .eq. 1
169 h = max( hstart, hmin )
180 ! === starting the time loop ===
183 if ( tplus .gt. tnext ) then
188 call yjacsubr( n, t, y, jac, yfixed, rconst )
192 jac(lu_diag_v(j)) = jac(lu_diag_v(j)) + ghinv
194 call decompsubr( n, jac, ier, lu_crow_v, lu_diag_v, lu_icol_v )
201 ! print *,'ier <> 0, h=',h
208 call dydtsubr( n, t, y, f1, yfixed, rconst )
210 ! ====== nonautonomous case ===============
211 if (.not. autonom) then
212 ! tau = sign(dround*max( 1.0e-6, abs(t) ), t)
213 tau = dround*max( 1.0e-6, abs(t) )
214 call dydtsubr( n, t+tau, y, k2, yfixed, rconst )
217 k3(j) = ( k2(j)-f1(j) )/tau
220 ! ----- stage 1 (nonautonomous) -----
223 k1(j) = f1(j) + x1*k3(j)
224 if (abs(k1(j)) .gt. ylimit_solvesubr) then
229 call solvesubr( jac, k1 )
231 ! ----- stage 2 (nonautonomous) -----
235 k2(j) = f1(j) - x1*k1(j) + x2*k3(j)
236 if (abs(k2(j)) .gt. ylimit_solvesubr) then
241 call solvesubr( jac, k2 )
243 ! ====== autonomous case ===============
245 ! ----- stage 1 (autonomous) -----
248 if (abs(k1(j)) .gt. ylimit_solvesubr) then
253 call solvesubr( jac, k1 )
255 ! ----- stage 2 (autonomous) -----
258 k2(j) = f1(j) - x1*k1(j)
259 if (abs(k2(j)) .gt. ylimit_solvesubr) then
264 call solvesubr( jac, k2 )
267 ! ----- stage 3 -----
269 ynew(j) = y(j) - 2.0e0*k1(j)
271 call dydtsubr( n, t+h, ynew, f1, yfixed, rconst )
274 k3(j) = f1(j) + ( -k1(j) + k2(j) )/h
275 if (abs(k3(j)) .gt. ylimit_solvesubr) then
280 call solvesubr( jac, k3 )
282 ! ----- stage 4 -----
284 ynew(j) = y(j) - 2.0e0*k1(j) - k3(j)
286 call dydtsubr( n, t+h, ynew, f1, yfixed, rconst )
289 k4(j) = f1(j) + ( -k1(j) + k2(j) - c43*k3(j) )/h
290 if (abs(k4(j)) .gt. ylimit_solvesubr) then
295 call solvesubr( jac, k4 )
297 ! ---- the solution ---
300 ynew(j) = y(j) - 2.0e0*k1(j) - k3(j) - k4(j)
304 ! ====== error estimation ========
308 ytol = abstol(i) + reltol(i)*abs(ynew(i))
309 err = err + ( k4(i)/ytol )**2
311 err = max( uround, sqrt( err/n ) )
313 ! ======= choose the stepsize ===============================
315 factor = 0.9/err**(1.e0/3.e0)
321 factor = max( 1.0e-1, min(factor,facmax) )
323 h = min( hmax, max(hmin,factor*h) )
325 ! ======= check for nan, too big, too small =================
326 ! if any of these conditions occur, either
327 ! exit if hold <= hmin
328 ! reduce step size and retry if hold > hmin
332 if (y(i) .ne. y(i)) then
335 else if (y(i) .lt. yneglimit(i)) then
338 else if (y(i) .gt. yposlimit(i)) then
343 135 if (iok .lt. 0) then
344 if (hold .le. hmin) then
349 h = max(hmin, 0.5*hold)
350 if (t.eq.tin) h = max(hmin, 1.0e-1*hold)
356 ! ======= rejected/accepted step ============================
358 if ( (err.gt.1).and.(hold.gt.hmin) ) then
361 if (t.eq.tin) h = max(hmin, 1.0e-1*hold)
375 ! ======= end of the time loop ===============================
376 if ( t .lt. tnext ) go to 10
379 if (nnocnvg .gt. 0) iok = 2
382 ! ======= output information =================================
390 end subroutine rodas3_ff_x2
393 end module module_cbmz_rodas3_solver