Update version info for release v4.6.1 (#2122)
[WRF.git] / chem / KPP / kpp / kpp-2.1 / util / dFun_dRcoeff.f90
blob281cc542317e81a627142dbd5441595dab5c0550
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
9 IMPLICIT NONE
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
14 INTEGER NCOEFF
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)
26 KPP_REAL aj
27 INTEGER i,j,k
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
33 DO j=1,NCOEFF
34 ! Initialize the j-th column of derivative matrix to zero
35 DO i=1,NVAR
36 DFDR(i+NVAR*(j-1)) = 0.0_dp
37 END DO
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
44 END DO
45 END DO
47 END SUBROUTINE dFun_dRcoeff