1 SUBROUTINE INTEGRATE
( NSENSIT
, Y
, TIN
, TOUT
)
3 INCLUDE
'KPP_ROOT_params.h'
4 INCLUDE
'KPP_ROOT_global.h'
11 C Y - Concentrations and Sensitivities
12 KPP_REAL Y
(NVAR*
(NSENSIT
+1))
13 C --- Note: Y contains: (1:NVAR) concentrations, followed by
14 C --- (1:NVAR) sensitivities w.r.t. first parameter, followed by
15 C --- etc., followed by
16 C --- (1:NVAR) sensitivities w.r.t. NSENSIT's parameter
20 EXTERNAL FUNC_CHEM
, JAC_CHEM
24 CALL ROS2_DDM
(NVAR
,NSENSIT
,TIN
,TOUT
,STEPMIN
,STEPMAX
,
25 + STEPMIN
,Y
,ATOL
,RTOL
,
26 + Info
,FUNC_CHEM
,JAC_CHEM
)
35 SUBROUTINE ROS2_DDM
(N
,NSENSIT
,T
,Tnext
,Hmin
,Hmax
,Hstart
,
37 + Info
,FUNC_CHEM
,JAC_CHEM
)
39 INCLUDE
'KPP_ROOT_params.h'
40 INCLUDE
'KPP_ROOT_global.h'
41 INCLUDE
'KPP_ROOT_sparse.h'
43 C Ros2 with direct-decoupled calculation of sensitivities
45 C The global variable DDMTYPE distinguishes between:
46 C DDMTYPE = 0 : sensitivities w.r.t. initial values
47 C DDMTYPE = 1 : sensitivities w.r.t. parameters
50 C y = Vector of: (1:NVAR) concentrations, followed by
51 C (1:NVAR) sensitivities w.r.t. first parameter, followed by
53 C (1:NVAR) sensitivities w.r.t. NSENSIT's parameter
54 C (y contains initial values at input, final values at output)
55 C [T, Tnext] = the integration interval
56 C Hmin, Hmax = lower and upper bounds for the selected step-size.
57 C Note that for Step = Hmin the current computed
58 C solution is unconditionally accepted by the error
60 C AbsTol, RelTol = (NVAR) dimensional vectors of
61 C componentwise absolute and relative tolerances.
62 C FUNC_CHEM = name of routine of derivatives. KPP syntax.
63 C See the header below.
64 C JAC_CHEM = name of routine that computes the Jacobian, in
65 C sparse format. KPP syntax. See the header below.
66 C Info(1) = 1 for autonomous system
67 C = 0 for nonautonomous system
70 C y = the values of concentrations at TEND.
71 C T = equals TEND on output.
72 C Info(2) = # of FUNC_CHEM calls.
73 C Info(3) = # of JAC_CHEM calls.
74 C Info(4) = # of accepted steps.
75 C Info(5) = # of rejected steps.
77 C Adrian Sandu, December 2001
81 KPP_REAL y
(NVAR*
(NSENSIT
+1)), ynew
(NVAR*
(NSENSIT
+1))
82 KPP_REAL K1
(NVAR*
(NSENSIT
+1))
83 KPP_REAL K2
(NVAR*
(NSENSIT
+1))
85 KPP_REAL DFDT
(NVAR*
(NSENSIT
+1))
86 KPP_REAL DFDP
(NVAR*NSENSIT
+1), DFDPDT
(NVAR*NSENSIT
+1)
87 KPP_REAL DJDP
(NVAR*NSENSIT
+1)
88 KPP_REAL F1
(NVAR
), F2
(NVAR
)
89 KPP_REAL JAC
(LU_NONZERO
), AJAC
(LU_NONZERO
)
90 KPP_REAL DJDT
(LU_NONZERO
)
92 KPP_REAL Hmin
,Hmax
,Hnew
,Hstart
,ghinv
,uround
93 KPP_REAL AbsTol
(NVAR
), RelTol
(NVAR
)
94 KPP_REAL T
, Tnext
, H
, Hold
, Tplus
, e
95 KPP_REAL ERR
, factor
, facmax
, dround
, elo
, tau
, gam
97 INTEGER n
,nfcn
,njac
,Naccept
,Nreject
,i
,j
,ier
99 LOGICAL IsReject
,Autonomous
,Embed3
100 EXTERNAL FUNC_CHEM
, JAC_CHEM
, HESS_CHEM
103 KPP_REAL gamma
, m1
, m2
, alpha
, beta
, delta
, theta
, w
104 KPP_REAL gamma3
, d1
, d2
, d3
, beta1
, beta2
105 KPP_REAL c31
, c32
, c34
107 c Initialization of counters, etc.
108 Autonomous
= Info
(1) .EQ
. 1
109 Embed3
= Info
(2) .EQ
. 1
111 dround
= 1.0d
-7 ! DSQRT
(uround
)
112 H
= DMAX1
(1.d
-8, Hstart
)
119 gamma
= 1.d0
+ 1.d0
/DSQRT
(2.0d0
)
120 c31
= -1.0D0
/gamma**2*
(1.0D0
-7.0D0*gamma
+9.0D0*gamma**2
)
121 & /(-1.0D0
+2.0D0*gamma
)
122 c32
= -1.0D0
/gamma**2*
(1.0D0
-6.0D0*gamma
+6.0D0*gamma**2
)
123 & /(-1.0D0
+2.0D0*gamma
)/2
124 gamma3
= 0.5D0
- 2*gamma
125 d1
= ((-9.0D0*gamma
+8.0D0*gamma**2
+2.0D0
)/gamma**2
/
126 & (-1.0D0
+2*gamma
))/6.0D0
127 d2
= ((-1.0D0
+3.0D0*gamma
)/gamma**2
/
128 & (-1.0D0
+2.0D0*gamma
))/6.0D0
129 d3
= -1.0D0
/(3.0D0*gamma
)
130 m1
= -3.d0
/(2.d0*gamma
)
131 m2
= -1.d0
/(2.d0*gamma
)
134 C === Starting the time loop ===
137 IF ( Tplus
.gt
. Tnext
) THEN
142 C Initial Function, Jacobian, and Hessian Values
143 CALL FUNC_CHEM
(NVAR
, T
, y
, F1
)
144 CALL JAC_CHEM
(NVAR
, T
, y
, JAC
)
145 CALL HESS_CHEM
( NVAR
, T
, y
, HESS
)
146 IF (DDMTYPE
.EQ
. 1) THEN
147 CALL DFUNDPAR
(NVAR
, NSENSIT
, T
, y
, DFDP
)
150 C Estimate the time derivatives in non-autonomous case
151 IF (.not
. Autonomous
) THEN
152 tau
= DSIGN
(dround*DMAX1
( 1.0d0
, DABS
(T
) ), T
)
153 CALL FUNC_CHEM
(NVAR
, T
+tau
, y
, K2
)
155 CALL JAC_CHEM
(NVAR
, T
+tau
, y
, AJAC
)
158 DFDT
(j
) = ( K2
(j
)-F1
(j
) )/tau
160 DO 30 j
= 1,LU_NONZERO
161 DJDT
(j
) = ( AJAC
(j
)-JAC
(j
) )/tau
164 CALL Jac_SP_Vec
(DJDT
,y
(i*NVAR
+1),DFDT
(i*NVAR
+1))
166 END IF ! .not
. Autonomous
169 ghinv
= - 1.0d0
/(gamma*H
)
174 AJAC
(LU_DIAG
(j
)) = JAC
(LU_DIAG
(j
)) + ghinv
176 CALL KppDecomp
(AJAC
, ier
)
183 print
*,'IER <> 0, H=',H
191 C ----- STAGE 1 -----
196 IF (.NOT
. Autonomous
) THEN
198 K1
(j
) = K1
(j
) + delta*DFDT
(j
)
201 CALL KppSolve
(AJAC
, K1
)
202 C --- If derivative w.r.t. parameters
203 IF (DDMTYPE
.EQ
. 1) THEN
204 CALL DJACDPAR
(NVAR
, NSENSIT
, T
, y
, K1
(1), DJDP
)
206 C --- End of derivative w.r.t. parameters
208 CALL Jac_SP_Vec
(JAC
,y
(i*NVAR
+1),K1
(i*NVAR
+1))
209 CALL Hess_Vec
( HESS
, K1
(1), y
(i*NVAR
+1), F2
)
211 K1
(i*NVAR
+j
) = K1
(i*NVAR
+j
) + gHinv*F2
(j
)
213 IF (.NOT
. Autonomous
) THEN
215 K1
(i*NVAR
+j
) = K1
(i*NVAR
+j
) + delta*DFDT
(i*NVAR
+j
)
218 C --- If derivative w.r.t. parameters
219 IF (DDMTYPE
.EQ
. 1) THEN
221 K1
(i*NVAR
+j
) = K1
(i*NVAR
+j
) + DFDP
((i
-1)*NVAR
+j
)
222 & + DJDP
((i
-1)*NVAR
+j
)
225 C --- End of derivative w.r.t. parameters
226 CALL KppSolve
(AJAC
, K1
(i*NVAR
+1))
229 C ----- STAGE 2 -----
231 DO 130 j
= 1,NVAR*
(NSENSIT
+1)
232 ynew
(j
) = y
(j
) + alpha*K1
(j
)
234 CALL FUNC_CHEM
(NVAR
, T
+H
, ynew
, F1
)
235 IF (DDMTYPE
.EQ
.1) THEN
236 CALL DFUNDPAR
(NVAR
, NSENSIT
, T
+H
, ynew
, DFDP
)
239 beta1
= 2.d0
/(gamma*H
)
242 K2
(j
) = F1
(j
) + beta1*K1
(j
)
244 IF (.NOT
. Autonomous
) THEN
246 K2
(j
) = K2
(j
) + delta*DFDT
(j
)
249 CALL KppSolve
(AJAC
, K2
)
250 C --- If derivative w.r.t. parameters
251 IF (DDMTYPE
.EQ
. 1) THEN
252 CALL DJACDPAR
(NVAR
, NSENSIT
, T
, y
, K2
(1), DJDP
)
254 C --- End of derivative w.r.t. parameters
256 CALL JAC_CHEM
(NVAR
, T
+H
, Ynew
, JAC
)
259 CALL Jac_SP_Vec
(JAC
,ynew
(i*NVAR
+1),K2
(i*NVAR
+1))
260 CALL Jac_SP_Vec
(DJDT
,y
(i*NVAR
+1),F1
)
261 CALL Hess_Vec
( HESS
, K2
(1), y
(i*NVAR
+1), F2
)
263 K2
(i*NVAR
+j
) = K2
(i*NVAR
+j
) + beta1*K1
(i*NVAR
+j
)
266 IF (.NOT
. Autonomous
) THEN
268 K2
(i*NVAR
+j
) = K2
(i*NVAR
+j
) + delta*DFDT
(i*NVAR
+j
)
271 C --- If derivative w.r.t. parameters
272 IF (DDMTYPE
.EQ
. 1) THEN
274 K2
(i*NVAR
+j
) = K2
(i*NVAR
+j
) + DFDP
((i
-1)*NVAR
+j
)
275 & + DJDP
((i
-1)*NVAR
+j
)
278 C --- End of derivative w.r.t. parameters
279 CALL KppSolve
(AJAC
, K2
(i*NVAR
+1))
282 C ----- STAGE 3 for error control only -----
288 K3
(j
) = F1
(j
) + beta1*K1
(j
) + beta2*K2
(j
)
290 IF (.NOT
. Autonomous
) THEN
292 K3
(j
) = K3
(j
) + delta*DFDT
(j
)
295 CALL KppSolve
(AJAC
, K3
)
298 C ---- The Solution ---
299 DO 200 j
= 1,NVAR*
(NSENSIT
+1)
300 ynew
(j
) = y
(j
) + m1*K1
(j
) + m2*K2
(j
)
304 C ====== Error estimation for concentrations only; this can be easily adapted to
305 C estimate the sensitivity error too ========
309 w
= AbsTol
(i
) + RelTol
(i
)*DMAX1
(DABS
(y
(i
)),DABS
(ynew
(i
)))
311 e
= d1*K1
(i
) + d2*K2
(i
) + d3*K3
(i
)
313 e
= (1.d0
/(2.d0*gamma
))*(K1
(i
)+K2
(i
))
315 ERR
= ERR
+ ( e
/w
)**2
317 ERR
= DMAX1
( uround
, DSQRT
( ERR
/NVAR
) )
319 C ======= Choose the stepsize ===============================
322 elo
= 3.0D0
! estimator local order
326 factor
= DMAX1
(2.0D
-1,DMIN1
(6.0D0
,ERR**
(1.0D0
/elo
)/.9D0
))
327 Hnew
= DMIN1
(Hmax
,DMAX1
(Hmin
, H
/factor
))
329 C ======= Rejected/Accepted Step ============================
331 IF ( (ERR
.gt
.1).and
.(H
.gt
.Hmin
) ) THEN
336 DO 300 i
=1,NVAR*
(NSENSIT
+1)
340 IF (.NOT
.IsReject
) THEN
341 H
= Hnew
! Do not increase stepsize
if previous step was rejected
347 C ======= End of the time loop ===============================
348 IF ( T
.lt
. Tnext
) GO TO 10
352 C ======= Output Information =================================
363 SUBROUTINE FUNC_CHEM
(N
, T
, Y
, P
)
364 INCLUDE
'KPP_ROOT_params.h'
365 INCLUDE
'KPP_ROOT_global.h'
367 KPP_REAL Y
(NVAR
), P
(NVAR
)
372 CALL Fun
( Y
, FIX
, RCONST
, P
)
378 SUBROUTINE DFUNDPAR
(N
, NSENSIT
, T
, Y
, P
)
379 C --- Computes the partial derivatives of FUNC_CHEM w.r.t. parameters
380 INCLUDE
'KPP_ROOT_params.h'
381 INCLUDE
'KPP_ROOT_global.h'
382 C --- NCOEFF, JCOEFF useful for derivatives w.r.t. rate coefficients
383 INTEGER NCOEFF
, JCOEFF
(NREACT
)
384 COMMON /DDMRCOEFF
/ NCOEFF
, JCOEFF
387 KPP_REAL Y
(NVAR
), P
(NVAR*NSENSIT
)
393 IF (DDMTYPE
.EQ
. 0) THEN
394 C --- Note: the values below are for sensitivities w.r.t. initial values;
395 C --- they may have to be changed for other applications
398 P
(i
+NVAR*
(j
-1)) = 0.0D0
402 C --- Example: the call below is for sensitivities w.r.t. rate coefficients;
403 C --- JCOEFF(1:NSENSIT) are the indices of the NSENSIT rate coefficients
404 C --- w.r.t. which one differentiates
405 CALL dFun_dRcoeff
( Y
, FIX
, NCOEFF
, JCOEFF
, P
)
411 SUBROUTINE DJACDPAR
(N
, NSENSIT
, T
, Y
, U
, P
)
412 C --- Computes the partial derivatives of JAC w.r.t. parameters times user vector U
413 INCLUDE
'KPP_ROOT_params.h'
414 INCLUDE
'KPP_ROOT_global.h'
415 C --- NCOEFF, JCOEFF useful for derivatives w.r.t. rate coefficients
416 INTEGER NCOEFF
, JCOEFF
(NREACT
)
417 COMMON /DDMRCOEFF
/ NCOEFF
, JCOEFF
420 KPP_REAL Y
(NVAR
), U
(NVAR
)
421 KPP_REAL P
(NVAR*NSENSIT
)
427 IF (DDMTYPE
.EQ
. 0) THEN
428 C --- Note: the values below are for sensitivities w.r.t. initial values;
429 C --- they may have to be changed for other applications
432 P
(i
+NVAR*
(j
-1)) = 0.0D0
436 C --- Example: the call below is for sensitivities w.r.t. rate coefficients;
437 C --- JCOEFF(1:NSENSIT) are the indices of the NSENSIT rate coefficients
438 C --- w.r.t. which one differentiates
439 CALL dJac_dRcoeff
( Y
, FIX
, U
, NCOEFF
, JCOEFF
, P
)
445 SUBROUTINE JAC_CHEM
(N
, T
, Y
, J
)
446 INCLUDE
'KPP_ROOT_params.h'
447 INCLUDE
'KPP_ROOT_global.h'
450 KPP_REAL Y
(NVAR
), J
(LU_NONZERO
)
455 CALL Jac_SP
( Y
, FIX
, RCONST
, J
)
461 SUBROUTINE HESS_CHEM
(N
, T
, Y
, HESS
)
462 INCLUDE
'KPP_ROOT_params.h'
463 INCLUDE
'KPP_ROOT_global.h'
466 KPP_REAL Y
(NVAR
), HESS
(NHESS
)
471 CALL Hessian
( Y
, FIX
, RCONST
, HESS
)