source: palm/trunk/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm/chem_gasphase_mod_Jacobian.f90 @ 2696

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

Merge of branch palm4u into trunk

File size: 3.9 KB
Line 
1! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2!
3! The ODE Jacobian of Chemical Model File
4!
5! Generated by KPP-2.2.3 symbolic chemistry Kinetics PreProcessor
6!       (http://www.cs.vt.edu/~asandu/Software/KPP)
7! KPP is distributed under GPL, the general public licence
8!       (http://www.gnu.org/copyleft/gpl.html)
9! (C) 1995-1997, V. Damian & A. Sandu, CGRER, Univ. Iowa
10! (C) 1997-2005, A. Sandu, Michigan Tech, Virginia Tech
11!     With important contributions from:
12!        M. Damian, Villanova University, USA
13!        R. Sander, Max-Planck Institute for Chemistry, Mainz, Germany
14!
15! File                 : chem_gasphase_mod_Jacobian.f90
16! Time                 : Fri Dec  1 18:10:53 2017
17! Working directory    : /data/kanani/branches/palm4u/GASPHASE_PREPROC/tmp_kpp4palm
18! Equation file        : chem_gasphase_mod.kpp
19! Output root filename : chem_gasphase_mod
20!
21! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
22
23
24
25MODULE chem_gasphase_mod_Jacobian
26
27  USE chem_gasphase_mod_Parameters
28  USE chem_gasphase_mod_JacobianSP
29
30  IMPLICIT NONE
31
32CONTAINS
33
34
35! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
36!
37! Jac_SP - the Jacobian of Variables in sparse matrix representation
38!   Arguments :
39!      V         - Concentrations of variable species (local)
40!      F         - Concentrations of fixed species (local)
41!      RCT       - Rate constants (local)
42!      JVS       - sparse Jacobian of variables
43!
44! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
45
46SUBROUTINE Jac_SP ( V, F, RCT, JVS )
47
48! V - Concentrations of variable species (local)
49  REAL(kind=dp) :: V(NVAR)
50! F - Concentrations of fixed species (local)
51  REAL(kind=dp) :: F(NFIX)
52! RCT - Rate constants (local)
53  REAL(kind=dp) :: RCT(NREACT)
54! JVS - sparse Jacobian of variables
55  REAL(kind=dp) :: JVS(LU_NONZERO)
56
57
58! Local variables
59! B - Temporary array
60  REAL(kind=dp) :: B(3)
61
62! B(1) = dA(1)/dV(1)
63  B(1) = RCT(1)
64! B(2) = dA(2)/dV(2)
65  B(2) = RCT(2)
66! B(3) = dA(3)/dV(3)
67  B(3) = RCT(3)
68
69! Construct the Jacobian terms from B's
70! JVS(1) = Jac_FULL(1,1)
71  JVS(1) = 0
72! JVS(2) = Jac_FULL(2,2)
73  JVS(2) = 0
74! JVS(3) = Jac_FULL(3,3)
75  JVS(3) = 0
76     
77END SUBROUTINE Jac_SP
78
79! End of Jac_SP function
80! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
81
82
83! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
84!
85! Jac_SP_Vec - function for sparse multiplication: sparse Jacobian times vector
86!   Arguments :
87!      JVS       - sparse Jacobian of variables
88!      UV        - User vector for variables
89!      JUV       - Jacobian times user vector
90!
91! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
92
93SUBROUTINE Jac_SP_Vec ( JVS, UV, JUV )
94
95! JVS - sparse Jacobian of variables
96  REAL(kind=dp) :: JVS(LU_NONZERO)
97! UV - User vector for variables
98  REAL(kind=dp) :: UV(NVAR)
99! JUV - Jacobian times user vector
100  REAL(kind=dp) :: JUV(NVAR)
101
102  JUV(1) = JVS(1)*UV(1)
103  JUV(2) = JVS(2)*UV(2)
104  JUV(3) = JVS(3)*UV(3)
105     
106END SUBROUTINE Jac_SP_Vec
107
108! End of Jac_SP_Vec function
109! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
110
111
112! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
113!
114! JacTR_SP_Vec - sparse multiplication: sparse Jacobian transposed times vector
115!   Arguments :
116!      JVS       - sparse Jacobian of variables
117!      UV        - User vector for variables
118!      JTUV      - Jacobian transposed times user vector
119!
120! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
121
122SUBROUTINE JacTR_SP_Vec ( JVS, UV, JTUV )
123
124! JVS - sparse Jacobian of variables
125  REAL(kind=dp) :: JVS(LU_NONZERO)
126! UV - User vector for variables
127  REAL(kind=dp) :: UV(NVAR)
128! JTUV - Jacobian transposed times user vector
129  REAL(kind=dp) :: JTUV(NVAR)
130
131  JTUV(1) = JVS(1)*UV(1)
132  JTUV(2) = JVS(2)*UV(2)
133  JTUV(3) = JVS(3)*UV(3)
134     
135END SUBROUTINE JacTR_SP_Vec
136
137! End of JacTR_SP_Vec function
138! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
139
140
141
142END MODULE chem_gasphase_mod_Jacobian
143
Note: See TracBrowser for help on using the repository browser.