1 ! ------------------------------------------------------------------------------
2 ! Subroutine for the derivative of Jac with respect to rate coefficients
4 ! -----------------------------------------------------------------------------
6 SUBROUTINE dJac_dRcoeff( V
, F
, U
, NCOEFF
, JCOEFF
, DJDR
)
8 USE KPP_ROOT_Parameters
9 USE KPP_ROOT_StoichiomSP
12 ! V - Concentrations of variable/fixed species
13 KPP_REAL
V(NVAR
), F(NFIX
)
14 ! U - User-supplied Vector
16 ! NCOEFF - the number of rate coefficients with respect to which we differentiate
18 ! JCOEFF - a vector of integers containing the indices of reactions (rate
19 ! coefficients) with respect to which we differentiate
20 INTEGER JCOEFF(NCOEFF
)
21 ! DFDR - a matrix containg derivative values; specifically,
22 ! column j contains d Jac(1:NVAR) / d RCT( JCOEFF(j) ) * U
23 ! for each 1 <= j <= NCOEFF
24 ! This matrix is stored in a column-wise linearized format
25 KPP_REAL
DJDR(NVAR
*NCOEFF
)
27 ! Local vector for Jacobian of reactant products
28 KPP_REAL
JV_RPROD(NJVRP
)
32 ! Compute the Jacobian of all reactant products
33 CALL JacReactantProd( V
, F
, JV_RPROD
)
35 ! Compute the derivatives by multiplying column JCOEFF(j) of the stoichiometric matrix with A_PROD
37 ! Initialize the j-th column of derivative matrix to zero
39 DJDR(i
+NVAR
*(j
-1)) = 0.0_dp
41 ! Column JCOEFF(j) in the stoichiometric matrix times the
42 ! ( Gradient of reactant product of the JCOEFF(j)-th reaction X user vector )
43 ! give the j-th column of the derivative matrix
45 ! Row JCOEFF(j) of JV_RPROD times the user vector
47 DO k
=CROW_JVRP(JCOEFF(j
)),CROW_JVRP(JCOEFF(j
)+1)-1
48 aj
= aj
+ JV_RPROD(k
)*U(ICOL_JVRP(k
))
50 ! Column JCOEFF(j) of Stoichiom. matrix times aj
51 DO k
=CCOL_STOICM(JCOEFF(j
)),CCOL_STOICM(JCOEFF(j
)+1)-1
52 DJDR(IROW_STOICM(k
)+NVAR
*(j
-1)) = STOICM(k
)*aj
56 END SUBROUTINE dJac_dRcoeff