source: palm/trunk/UTIL/chemistry/gasphase_preproc/kpp/util/dJac_dRcoeff.f90 @ 4901

Last change on this file since 4901 was 2696, checked in by kanani, 6 years ago

Merge of branch palm4u into trunk

File size: 2.3 KB
Line 
1! ------------------------------------------------------------------------------
2! Subroutine for the derivative of Jac with respect to rate coefficients
3! Times a user vector
4! -----------------------------------------------------------------------------
5
6      SUBROUTINE  dJac_dRcoeff( V, F, U, NCOEFF, JCOEFF, DJDR )
7       
8      USE KPP_ROOT_Parameters
9      USE KPP_ROOT_StoichiomSP
10      IMPLICIT NONE 
11
12! V - Concentrations of variable/fixed species           
13      KPP_REAL V(NVAR), F(NFIX)
14! U - User-supplied Vector           
15      KPP_REAL U(NVAR)
16! NCOEFF - the number of rate coefficients with respect to which we differentiate
17      INTEGER NCOEFF       
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)
26
27! Local vector for Jacobian of reactant products
28      KPP_REAL JV_RPROD(NJVRP)
29      KPP_REAL aj
30      INTEGER i,j,k
31     
32! Compute the Jacobian of all reactant products   
33      CALL JacReactantProd( V, F, JV_RPROD )
34
35! Compute the derivatives by multiplying column JCOEFF(j) of the stoichiometric matrix with A_PROD       
36      DO j=1,NCOEFF
37!                  Initialize the j-th column of derivative matrix to zero       
38         DO i=1,NVAR
39           DJDR(i+NVAR*(j-1)) = 0.0_dp
40         END DO
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   
44!
45!          Row JCOEFF(j) of JV_RPROD times the user vector
46         aj = 0.0_dp
47         DO k=CROW_JVRP(JCOEFF(j)),CROW_JVRP(JCOEFF(j)+1)-1
48             aj = aj + JV_RPROD(k)*U(ICOL_JVRP(k))
49         END DO
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
53         END DO
54      END DO
55     
56      END SUBROUTINE  dJac_dRcoeff
Note: See TracBrowser for help on using the repository browser.