source: palm/trunk/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm/chem_gasphase_mod_Util.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: 6.4 KB
Line 
1! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2!
3! Auxiliary Routines 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_Util.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_Util
26
27  USE chem_gasphase_mod_Parameters
28  IMPLICIT NONE
29
30CONTAINS
31
32
33
34! User INLINED Utility Functions
35
36! End INLINED Utility Functions
37
38! Utility Functions from KPP_HOME/util/util
39! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
40!
41! UTIL - Utility functions
42!   Arguments :
43!
44! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
45
46! ****************************************************************
47!                           
48! InitSaveData - Opens the data file for writing
49!   Parameters :                                                 
50!
51! ****************************************************************
52
53      SUBROUTINE InitSaveData ()
54
55      USE chem_gasphase_mod_Parameters
56
57      open(10, file='chem_gasphase_mod.dat')
58
59      END SUBROUTINE InitSaveData
60
61! End of InitSaveData function
62! ****************************************************************
63
64! ****************************************************************
65!                           
66! SaveData - Write LOOKAT species in the data file
67!   Parameters :                                                 
68!
69! ****************************************************************
70
71      SUBROUTINE SaveData ()
72
73      USE chem_gasphase_mod_Global
74      USE chem_gasphase_mod_Monitor
75
76      INTEGER i
77
78      WRITE(10,999) (TIME-TSTART)/3600.D0,  &
79                   (C(LOOKAT(i))/CFACTOR, i=1,NLOOKAT)
80999   FORMAT(E24.16,100(1X,E24.16))
81
82      END SUBROUTINE SaveData
83
84! End of SaveData function
85! ****************************************************************
86
87! ****************************************************************
88!                           
89! CloseSaveData - Close the data file
90!   Parameters :                                                 
91!
92! ****************************************************************
93
94      SUBROUTINE CloseSaveData ()
95
96      USE chem_gasphase_mod_Parameters
97
98      CLOSE(10)
99
100      END SUBROUTINE CloseSaveData
101
102! End of CloseSaveData function
103! ****************************************************************
104
105! ****************************************************************
106!                           
107! GenerateMatlab - Generates MATLAB file to load the data file
108!   Parameters :
109!                It will have a character string to prefix each
110!                species name with.                                                 
111!
112! ****************************************************************
113
114      SUBROUTINE GenerateMatlab ( PREFIX )
115
116      USE chem_gasphase_mod_Parameters
117      USE chem_gasphase_mod_Global
118      USE chem_gasphase_mod_Monitor
119
120     
121      CHARACTER(LEN=8) PREFIX 
122      INTEGER i
123
124      open(20, file='chem_gasphase_mod.m')
125      write(20,*) 'load chem_gasphase_mod.dat;'
126      write(20,990) PREFIX
127990   FORMAT(A1,'c = chem_gasphase_mod;')
128      write(20,*) 'clear chem_gasphase_mod;'
129      write(20,991) PREFIX, PREFIX
130991   FORMAT(A1,'t=',A1,'c(:,1);')
131      write(20,992) PREFIX
132992   FORMAT(A1,'c(:,1)=[];')
133
134      do i=1,NLOOKAT
135        write(20,993) PREFIX, SPC_NAMES(LOOKAT(i)), PREFIX, i
136993     FORMAT(A1,A6,' = ',A1,'c(:,',I2,');')
137      end do
138     
139      CLOSE(20)
140
141      END SUBROUTINE GenerateMatlab
142
143! End of GenerateMatlab function
144! ****************************************************************
145
146
147! End Utility Functions from KPP_HOME/util/util
148! End of UTIL function
149! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
150
151
152! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
153!
154! Shuffle_user2kpp - function to copy concentrations from USER to KPP
155!   Arguments :
156!      V_USER    - Concentration of variable species in USER's order
157!      V         - Concentrations of variable species (local)
158!
159! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
160
161SUBROUTINE Shuffle_user2kpp ( V_USER, V )
162
163! V_USER - Concentration of variable species in USER's order
164  REAL(kind=dp) :: V_USER(NVAR)
165! V - Concentrations of variable species (local)
166  REAL(kind=dp) :: V(NVAR)
167
168  V(1) = V_USER(1)
169  V(2) = V_USER(2)
170     
171END SUBROUTINE Shuffle_user2kpp
172
173! End of Shuffle_user2kpp function
174! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
175
176
177! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
178!
179! Shuffle_kpp2user - function to restore concentrations from KPP to USER
180!   Arguments :
181!      V         - Concentrations of variable species (local)
182!      V_USER    - Concentration of variable species in USER's order
183!
184! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
185
186SUBROUTINE Shuffle_kpp2user ( V, V_USER )
187
188! V - Concentrations of variable species (local)
189  REAL(kind=dp) :: V(NVAR)
190! V_USER - Concentration of variable species in USER's order
191  REAL(kind=dp) :: V_USER(NVAR)
192
193  V_USER(1) = V(1)
194  V_USER(2) = V(2)
195     
196END SUBROUTINE Shuffle_kpp2user
197
198! End of Shuffle_kpp2user function
199! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
200
201
202! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
203!
204! GetMass - compute total mass of selected atoms
205!   Arguments :
206!      CL        - Concentration of all species (local)
207!      Mass      - value of mass balance
208!
209! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
210
211SUBROUTINE GetMass ( CL, Mass )
212
213! CL - Concentration of all species (local)
214  REAL(kind=dp) :: CL(NSPEC)
215! Mass - value of mass balance
216  REAL(kind=dp) :: Mass(1)
217
218     
219END SUBROUTINE GetMass
220
221! End of GetMass function
222! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
223
224
225
226END MODULE chem_gasphase_mod_Util
227
Note: See TracBrowser for help on using the repository browser.