1 ! ------------------------------------------------------------------------------
2 ! Subroutine for the derivative of Fun with respect to rate coefficients
3 ! -----------------------------------------------------------------------------
5 SUBROUTINE dFun_dRcoeff( V
, F
, NCOEFF
, JCOEFF
, DFDR
)
7 USE KPP_ROOT_Parameters
8 USE KPP_ROOT_StoichiomSP
11 ! V - Concentrations of variable/radical/fixed species
12 KPP_REAL
V(NVAR
), F(NFIX
)
13 ! NCOEFF - the number of rate coefficients with respect to which we differentiate
15 ! JCOEFF - a vector of integers containing the indices of reactions (rate
16 ! coefficients) with respect to which we differentiate
17 INTEGER JCOEFF(NCOEFF
)
18 ! DFDR - a matrix containg derivative values; specifically,
19 ! column j contains d Fun(1:NVAR) / d RCT( JCOEFF(j) )
20 ! for each 1 <= j <= NCOEFF
21 ! This matrix is stored in a column-wise linearized format
22 KPP_REAL
DFDR(NVAR
*NCOEFF
)
24 ! Local vector with reactant products
25 KPP_REAL
A_RPROD(NREACT
)
29 ! Compute the reactant products of all reactions
30 CALL ReactantProd ( V
, F
, A_RPROD
)
32 ! Compute the derivatives by multiplying column JCOEFF(j) of the stoichiometric matrix with A_RPROD
34 ! Initialize the j-th column of derivative matrix to zero
36 DFDR(i
+NVAR
*(j
-1)) = 0.0_dp
38 ! Column JCOEFF(j) in the stoichiometric matrix times the
39 ! reactant product of the JCOEFF(j)-th reaction
40 ! give the j-th column of the derivative matrix
41 aj
= A_RPROD(JCOEFF(j
))
42 DO k
=CCOL_STOICM(JCOEFF(j
)),CCOL_STOICM(JCOEFF(j
)+1)-1
43 DFDR(IROW_STOICM(k
)+NVAR
*(j
-1)) = STOICM(k
)*aj
47 END SUBROUTINE dFun_dRcoeff