source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_MOD/srf_flux_int_mod.f90 @ 6610

Last change on this file since 6610 was 6610, checked in by acosce, 10 months ago

INCA used for ICOLMDZORINCA_CO2_Transport_GMD_2023

File size: 23.0 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: srf_flux_int_mod.F90 104 2008-12-23 10:28:51Z acosce $
13!! =========================================================================
14!! INCA - INteraction with Chemistry and Aerosols
15!!
16!! Copyright Laboratoire des Sciences du Climat et de l'Environnement (LSCE)
17!!           Unite mixte CEA-CNRS-UVSQ
18!!
19!! Contributors to this INCA subroutine:
20!!
21!! Didier Hauglustaine, LSCE, hauglustaine@cea.fr
22!!
23!! Anne Cozic, LSCE, anne.cozic@cea.fr
24!! Yann Meurdesoif, LSCE, yann.meurdesoif@cea.fr
25!!
26!! This software is a computer program whose purpose is to simulate the
27!! atmospheric gas phase and aerosol composition. The model is designed to be
28!! used within a transport model or a general circulation model. This version
29!! of INCA was designed to be coupled to the LMDz GCM. LMDz-INCA accounts
30!! for emissions, transport (resolved and sub-grid scale), photochemical
31!! transformations, and scavenging (dry deposition and washout) of chemical
32!! species and aerosols interactively in the GCM. Several versions of the INCA
33!! model are currently used depending on the envisaged applications with the
34!! chemistry-climate model.
35!!
36!! This software is governed by the CeCILL  license under French law and
37!! abiding by the rules of distribution of free software.  You can  use,
38!! modify and/ or redistribute the software under the terms of the CeCILL
39!! license as circulated by CEA, CNRS and INRIA at the following URL
40!! "http://www.cecill.info".
41!!
42!! As a counterpart to the access to the source code and  rights to copy,
43!! modify and redistribute granted by the license, users are provided only
44!! with a limited warranty  and the software's author,  the holder of the
45!! economic rights,  and the successive licensors  have only  limited
46!! liability.
47!!
48!! In this respect, the user's attention is drawn to the risks associated
49!! with loading,  using,  modifying and/or developing or reproducing the
50!! software by the user in light of its specific status of free software,
51!! that may mean  that it is complicated to manipulate,  and  that  also
52!! therefore means  that it is reserved for developers  and  experienced
53!! professionals having in-depth computer knowledge. Users are therefore
54!! encouraged to load and test the software's suitability as regards their
55!! requirements in conditions enabling the security of their systems and/or
56!! data to be ensured and,  more generally, to use and operate it in the
57!! same conditions as regards security.
58!!
59!! The fact that you are presently reading this means that you have had
60!! knowledge of the CeCILL license and that you accept its terms.
61!! =========================================================================
62
63
64MODULE SRF_FLUX_INT
65  !---------------------------------------------------------------
66  !     ... Monthly surface emissions fluxes
67  ! Didier Hauglustaine, IPSL, 1999.
68  !---------------------------------------------------------------
69
70  IMPLICIT NONE
71
72  INTEGER, SAVE :: ncidf, ncidfa, ncidfg, ncidfm, ncidfn
73  INTEGER, SAVE :: klonf
74  INTEGER, SAVE :: ntimef
75!$OMP THREADPRIVATE(ncidf,ncidfa, ncidfg, ncidfm, ncidfn)
76!$OMP THREADPRIVATE(klonf)
77!$OMP THREADPRIVATE(ntimef)
78
79  REAL, SAVE, ALLOCATABLE :: days(:)
80!$OMP THREADPRIVATE(days)
81
82  REAL,SAVE,ALLOCATABLE, DIMENSION(:,:) ::   &
83     flx_co2             ,                     &
84     flx_n2o             ,                     &
85     flx_ch4             ,                     &
86     flx_co              ,                     &
87     flx_cobbg           ,                     &
88     flx_h2              ,                     &
89     flx_no              ,                     &
90     flx_mcf             ,                     &
91     flx_ch3oh           ,                     &
92     flx_ch3oh_no_veg    ,                     &
93     flx_c2h5oh          ,                     &
94     flx_c2h6            ,                     &
95     flx_c2h6_no_veg     ,                     &
96     flx_c3h8            ,                     &
97     flx_c3h8_no_veg     ,                     &
98     flx_alkan           ,                     &
99     flx_c2h4            ,                     &
100     flx_c2h4_no_veg     ,                     &
101     flx_c3h6            ,                     &
102     flx_c3h6_no_veg     ,                     &
103     flx_c2h2            ,                     &
104     flx_c2h2_no_veg     ,                     &
105     flx_alken           ,                     &
106     flx_alken_no_veg    ,                     &
107     flx_arom            ,                     &
108     flx_ch2o            ,                     &
109     flx_ch2o_no_veg     ,                     &
110     flx_ch3cho          ,                     &
111     flx_ch3cho_no_veg   ,                     &
112     flx_ch3coch3        ,                     &
113     flx_ch3coch3_no_veg ,                     &
114     flx_mek             ,                     &
115     flx_mvk             ,                     &
116     flx_ch3cooh         ,                     &
117     flx_ch3cooh_no_veg  ,                     &
118     flx_isop            ,                     &
119     flx_isop_no_veg     ,                     &
120     flx_apin            ,                     &
121     flx_apin_no_veg
122     
123!$OMP THREADPRIVATE(flx_co2,flx_n2o,flx_ch4,flx_co,flx_cobbg,flx_h2,flx_no)
124!$OMP THREADPRIVATE(flx_mcf,flx_ch3oh,flx_ch3oh_no_veg,flx_c2h5oh,flx_c2h6,flx_c3h8,flx_alkan)
125!$OMP THREADPRIVATE(flx_c2h4,flx_c3h6,flx_c2h2,flx_alken,flx_arom,flx_ch2o)
126!$OMP THREADPRIVATE(flx_alken_no_veg, flx_ch2o_no_veg, flx_c2h2_no_veg, flx_c3h6_no_veg, flx_c2h4_no_veg,flx_c3h8_no_veg, flx_c2h6_no_veg)
127!$OMP THREADPRIVATE(flx_ch3cho,flx_ch3cho_no_veg,flx_ch3coch3,flx_ch3coch3_no_veg, flx_mek,flx_mvk,flx_ch3cooh,flx_ch3cooh_no_veg,flx_isop,flx_apin)
128!$OMP THREADPRIVATE(flx_isop_no_veg,flx_apin_no_veg)
129
130  REAL,SAVE,ALLOCATABLE, DIMENSION(:,:) ::  &
131     flx_co2bio  ,                     &
132     flx_co2oce  ,                     &
133     flx_co2tot  ,                     &
134     flx_so2     ,                     &
135     flx_bbso2   ,                     &
136     flx_asso4m  ,                     &
137     flx_h2s     ,                     &
138     conc_dms   
139!$OMP THREADPRIVATE(flx_co2bio,flx_co2oce,flx_co2tot,flx_so2,flx_bbso2,flx_asso4m,flx_h2s,conc_dms)
140
141  REAL, SAVE, ALLOCATABLE, DIMENSION(:,:) ::   &
142     flx_bc  ,                            &
143     flx_pom ,                             &
144     flx_bbbc ,                           &
145     flx_bbpom,                           &
146     fractnat_aer,                        &
147     fractnat_bc,                         &
148     fractnat_pom,                        &
149     fractnat_so4,                        &
150     fractnat_dust,                       &
151     fractnat_ss
152!$OMP THREADPRIVATE(flx_bc,flx_pom)
153!$OMP THREADPRIVATE(flx_bbbc,flx_bbpom)
154!$OMP THREADPRIVATE(fractnat_aer, fractnat_bc, fractnat_pom,fractnat_so4,fractnat_dust, fractnat_ss) 
155
156  REAL, SAVE, ALLOCATABLE, DIMENSION(:,:) :: flx_nh3, flx_bbnh3
157!$OMP THREADPRIVATE(flx_nh3,flx_bbnh3)
158
159    !Anthropogenic emissions (ANT)
160    REAL,SAVE,ALLOCATABLE, DIMENSION(:,:) ::   &
161     flx_co2_ant         ,                     &
162     flx_n2o_ant         ,                     &
163     flx_ch4_ant         ,                     &
164     flx_ch4_ant_interp         ,                     &
165     flx_co_ant          ,                     &
166     flx_h2_ant          ,                     &
167     flx_no_ant          ,                     &
168     flx_mcf_ant         ,                     &
169     flx_ch3oh_ant       ,                     &
170     flx_c2h5oh_ant      ,                     &
171     flx_c2h6_ant        ,                     &
172     flx_c3h8_ant        ,                     &
173     flx_alkan_ant       ,                     &
174     flx_c2h4_ant        ,                     &
175     flx_c3h6_ant        ,                     &
176     flx_c2h2_ant        ,                     &
177     flx_alken_ant       ,                     &
178     flx_arom_ant        ,                     &
179     flx_ch2o_ant        ,                     &
180     flx_ch3cho_ant      ,                     &
181     flx_ch3coch3_ant    ,                     &
182     flx_mek_ant         ,                     &
183     flx_mvk_ant         ,                     &
184     flx_ch3cooh_ant     ,                     &
185     flx_isop_ant        ,                     &
186     flx_apin_ant        ,                     &
187     flx_so2_ant         ,                     &
188     flx_h2s_ant         ,                     &
189     flx_so4_ant         ,                     &
190     flx_bc_ant          ,                     &
191     flx_pom_ant         ,                                 &
192     flx_nh3_ant
193     
194!$OMP THREADPRIVATE(flx_co2_ant,flx_n2o_ant,flx_ch4_ant,flx_ch4_ant_interp, flx_co_ant,flx_h2_ant,flx_no_ant)
195!$OMP THREADPRIVATE(flx_mcf_ant,flx_ch3oh_ant,flx_c2h5oh_ant,flx_c2h6_ant,flx_c3h8_ant,flx_alkan_ant)
196!$OMP THREADPRIVATE(flx_c2h4_ant,flx_c3h6_ant,flx_c2h2_ant,flx_alken_ant,flx_arom_ant,flx_ch2o_ant)
197!$OMP THREADPRIVATE(flx_ch3cho_ant,flx_ch3coch3_ant,flx_mek_ant,flx_mvk_ant,flx_ch3cooh_ant,flx_isop_ant,flx_apin_ant)
198!$OMP THREADPRIVATE(flx_so2_ant,flx_so4_ant,flx_h2s_ant,flx_bc_ant,flx_pom_ant,flx_nh3_ant)
199
200    !Natural emissions (NAT)
201    REAL,SAVE,ALLOCATABLE, DIMENSION(:,:) ::   &
202     flx_co2_nat         ,                     &
203     flx_n2o_nat         ,                     &
204     flx_ch4_nat         ,                     &
205     flx_co_nat          ,                     &
206     flx_h2_nat          ,                     &
207     flx_no_nat          ,                     &
208     flx_mcf_nat         ,                     &
209     flx_ch3oh_nat       ,                     &
210     flx_c2h5oh_nat      ,                     &
211     flx_c2h6_nat        ,                     &
212     flx_c3h8_nat        ,                     &
213     flx_alkan_nat       ,                     &
214     flx_c2h4_nat        ,                     &
215     flx_c3h6_nat        ,                     &
216     flx_c2h2_nat        ,                     &
217     flx_alken_nat       ,                     &
218     flx_arom_nat        ,                     &
219     flx_ch2o_nat        ,                     &
220     flx_ch3cho_nat      ,                     &
221     flx_ch3coch3_nat    ,                     &
222     flx_mek_nat         ,                     &
223     flx_mvk_nat         ,                     &
224     flx_ch3cooh_nat     ,                     &
225     flx_isop_nat        ,                     &
226     flx_apin_nat        ,                     &
227     flx_so2_nat         ,                     &
228     flx_h2s_nat         ,                     &
229     flx_so4_nat         ,                     &
230     flx_bc_nat          ,                     &
231     flx_pom_nat         ,                                 &
232     flx_nh3_nat
233     
234!$OMP THREADPRIVATE(flx_co2_nat,flx_n2o_nat,flx_ch4_nat,flx_co_nat,flx_h2_nat,flx_no_nat)
235!$OMP THREADPRIVATE(flx_mcf_nat,flx_ch3oh_nat,flx_c2h5oh_nat,flx_c2h6_nat,flx_c3h8_nat,flx_alkan_nat)
236!$OMP THREADPRIVATE(flx_c2h4_nat,flx_c3h6_nat,flx_c2h2_nat,flx_alken_nat,flx_arom_nat,flx_ch2o_nat)
237!$OMP THREADPRIVATE(flx_ch3cho_nat,flx_ch3coch3_nat,flx_mek_nat,flx_mvk_nat,flx_ch3cooh_nat,flx_isop_nat,flx_apin_nat)
238!$OMP THREADPRIVATE(flx_so2_nat,flx_so4_nat,flx_h2s_nat,flx_bc_nat,flx_pom_nat,flx_nh3_nat)
239
240    !Biomass burning emissions (BBG)
241    REAL,SAVE,ALLOCATABLE, DIMENSION(:,:) ::   &
242     flx_co2_bbg         ,                     &
243     flx_n2o_bbg         ,                     &
244     flx_ch4_bbg         ,                     &
245     flx_co_bbg          ,                     &
246     flx_h2_bbg          ,                     &
247     flx_no_bbg          ,                     &
248     flx_mcf_bbg         ,                     &
249     flx_ch3oh_bbg       ,                     &
250     flx_c2h5oh_bbg      ,                     &
251     flx_c2h6_bbg        ,                     &
252     flx_c3h8_bbg        ,                     &
253     flx_alkan_bbg       ,                     &
254     flx_c2h4_bbg        ,                     &
255     flx_c3h6_bbg        ,                     &
256     flx_c2h2_bbg        ,                     &
257     flx_alken_bbg       ,                     &
258     flx_arom_bbg        ,                     &
259     flx_ch2o_bbg        ,                     &
260     flx_ch3cho_bbg      ,                     &
261     flx_ch3coch3_bbg    ,                     &
262     flx_mek_bbg         ,                     &
263     flx_mvk_bbg         ,                     &
264     flx_ch3cooh_bbg     ,                     &
265     flx_isop_bbg        ,                     &
266     flx_apin_bbg        ,                     &
267     flx_so2_bbg         ,                     &
268     flx_h2s_bbg         ,                     &
269     flx_bc_bbg          ,                     &
270     flx_pom_bbg         ,                                 &
271     flx_so4_bbg         ,                                 &
272     flx_nh3_bbg
273     
274!$OMP THREADPRIVATE(flx_co2_bbg,flx_n2o_bbg,flx_ch4_bbg,flx_co_bbg,flx_h2_bbg,flx_no_bbg)
275!$OMP THREADPRIVATE(flx_mcf_bbg,flx_ch3oh_bbg,flx_c2h5oh_bbg,flx_c2h6_bbg,flx_c3h8_bbg,flx_alkan_bbg)
276!$OMP THREADPRIVATE(flx_c2h4_bbg,flx_c3h6_bbg,flx_c2h2_bbg,flx_alken_bbg,flx_arom_bbg,flx_ch2o_bbg)
277!$OMP THREADPRIVATE(flx_ch3cho_bbg,flx_ch3coch3_bbg,flx_mek_bbg,flx_mvk_bbg,flx_ch3cooh_bbg,flx_isop_bbg,flx_apin_bbg)
278!$OMP THREADPRIVATE(flx_so2_bbg,flx_so4_bbg,flx_h2s_bbg,flx_bc_bbg,flx_pom_bbg,flx_nh3_bbg)
279
280CONTAINS
281 
282  SUBROUTINE init_srf_flux_int
283    USE INCA_DIM
284    IMPLICIT NONE
285   
286    ALLOCATE(flx_co2(PLON,12))
287    ALLOCATE(flx_n2o(PLON,12))
288    ALLOCATE(flx_ch4(PLON,12))
289    ALLOCATE(flx_co(PLON,12))
290    ALLOCATE(flx_cobbg(PLON,12))
291    ALLOCATE(flx_h2(PLON,12))
292    ALLOCATE(flx_no(PLON,12))
293    ALLOCATE(flx_mcf(PLON,12))
294    ALLOCATE(flx_ch3oh(PLON,12))
295    ALLOCATE(flx_ch3oh_no_veg(PLON,12))
296    ALLOCATE(flx_c2h5oh(PLON,12))
297    ALLOCATE(flx_c2h6(PLON,12))
298    ALLOCATE(flx_c2h6_no_veg(PLON,12))
299    ALLOCATE(flx_c3h8(PLON,12))
300    ALLOCATE(flx_c3h8_no_veg(PLON,12))
301    ALLOCATE(flx_alkan(PLON,12))
302    ALLOCATE(flx_c2h4(PLON,12))
303    ALLOCATE(flx_c2h4_no_veg(PLON,12))
304    ALLOCATE(flx_c3h6(PLON,12))
305    ALLOCATE(flx_c3h6_no_veg(PLON,12))
306    ALLOCATE(flx_c2h2(PLON,12))
307    ALLOCATE(flx_c2h2_no_veg(PLON,12))
308    ALLOCATE(flx_alken(PLON,12))
309    ALLOCATE(flx_alken_no_veg(PLON,12))
310    ALLOCATE(flx_arom(PLON,12))
311    ALLOCATE(flx_ch2o(PLON,12))
312    ALLOCATE(flx_ch2o_no_veg(PLON,12))
313    ALLOCATE(flx_ch3cho(PLON,12))
314    ALLOCATE(flx_ch3cho_no_veg(PLON,12))
315    ALLOCATE(flx_ch3coch3(PLON,12))
316    ALLOCATE(flx_ch3coch3_no_veg(PLON,12))
317    ALLOCATE(flx_mek(PLON,12))
318    ALLOCATE(flx_mvk(PLON,12))
319    ALLOCATE(flx_ch3cooh(PLON,12))
320    ALLOCATE(flx_ch3cooh_no_veg(PLON,12))
321    ALLOCATE(flx_isop(PLON,12))
322    ALLOCATE(flx_isop_no_veg(PLON,12))
323    ALLOCATE(flx_apin(PLON,12))
324    ALLOCATE(flx_apin_no_veg(PLON,12))
325    flx_co2             = 0.
326    flx_n2o             = 0.
327    flx_ch4             = 0.
328    flx_co              = 0.
329    flx_cobbg           = 0.
330    flx_h2              = 0.
331    flx_no              = 0.
332    flx_mcf             = 0.
333    flx_ch3oh           = 0.
334    flx_ch3oh_no_veg    = 0.
335    flx_c2h5oh          = 0.
336    flx_c2h6            = 0.
337    flx_c2h6_no_veg     = 0.
338    flx_c3h8            = 0.
339    flx_c3h8_no_veg     = 0.
340    flx_alkan           = 0.
341    flx_c2h4            = 0.
342    flx_c2h4_no_veg     = 0.
343    flx_c3h6            = 0.
344    flx_c3h6_no_veg     = 0.
345    flx_c2h2            = 0.
346    flx_c2h2_no_veg     = 0.
347    flx_alken           = 0.
348    flx_alken_no_veg    = 0.
349    flx_arom            = 0.
350    flx_ch2o            = 0.
351    flx_ch2o_no_veg     = 0.
352    flx_ch3cho          = 0.
353    flx_ch3cho_no_veg   = 0.
354    flx_ch3coch3        = 0.
355    flx_ch3coch3_no_veg = 0.
356    flx_mek             = 0.
357    flx_mvk             = 0.
358    flx_ch3cooh         = 0.
359    flx_ch3cooh_no_veg  = 0.
360    flx_isop            = 0.
361    flx_isop_no_veg     = 0.
362    flx_apin            = 0.
363    flx_apin_no_veg     = 0.
364
365    ALLOCATE(flx_co2bio(PLON,12))
366    ALLOCATE(flx_co2oce(PLON,12))
367    ALLOCATE(flx_co2tot(PLON,12))
368    ALLOCATE(flx_so2(PLON,12))
369    ALLOCATE(flx_bbso2(PLON,12))
370    ALLOCATE(flx_asso4m(PLON,12))
371    ALLOCATE(flx_h2s(PLON,12))
372    ALLOCATE(conc_dms(PLON,12))
373    ALLOCATE(flx_bc(PLON,12))
374    ALLOCATE(flx_pom(PLON,12))
375    ALLOCATE(flx_bbbc(PLON,12))
376    ALLOCATE(flx_bbpom(PLON,12))
377    ALLOCATE(fractnat_aer(PLON,12))
378    ALLOCATE(fractnat_bc(PLON,12))
379    ALLOCATE(fractnat_pom(PLON,12))
380    ALLOCATE(fractnat_so4(PLON,12))
381    ALLOCATE(fractnat_dust(PLON,12))
382    ALLOCATE(fractnat_ss(PLON,12))
383    ALLOCATE(flx_nh3(PLON,12))
384    ALLOCATE(flx_bbnh3(PLON,12))
385    flx_nh3    = 0.
386    flx_bbnh3    = 0.
387    fractnat_ss = 0.
388    flx_co2bio = 0.
389    flx_co2oce = 0.
390    flx_co2tot = 0.
391    flx_so2    = 0.
392    flx_bbso2  = 0.
393    flx_asso4m = 0.
394    flx_h2s    = 0.
395    conc_dms   = 0.
396    flx_bc     = 0.
397    flx_pom    = 0. 
398    flx_bbbc     = 0.
399    flx_bbpom    = 0. 
400    fractnat_aer = 0.
401    fractnat_bc = 0.
402    fractnat_pom = 0.
403    fractnat_so4 = 0.
404    fractnat_dust = 0.
405
406    !Anthropogenic emissions (ANT)
407    ALLOCATE(flx_co2_ant(PLON,12))
408    ALLOCATE(flx_n2o_ant(PLON,12))
409    ALLOCATE(flx_ch4_ant(PLON,12))
410    ALLOCATE(flx_ch4_ant_interp(PLON,12))
411    ALLOCATE(flx_co_ant(PLON,12))
412    ALLOCATE(flx_h2_ant(PLON,12))
413    ALLOCATE(flx_no_ant(PLON,12))
414    ALLOCATE(flx_mcf_ant(PLON,12))
415    ALLOCATE(flx_ch3oh_ant(PLON,12))
416    ALLOCATE(flx_c2h5oh_ant(PLON,12))
417    ALLOCATE(flx_c2h6_ant(PLON,12))
418    ALLOCATE(flx_c3h8_ant(PLON,12))
419    ALLOCATE(flx_alkan_ant(PLON,12))
420    ALLOCATE(flx_c2h4_ant(PLON,12))
421    ALLOCATE(flx_c3h6_ant(PLON,12))
422    ALLOCATE(flx_c2h2_ant(PLON,12))
423    ALLOCATE(flx_alken_ant(PLON,12))
424    ALLOCATE(flx_arom_ant(PLON,12))
425    ALLOCATE(flx_ch2o_ant(PLON,12))
426    ALLOCATE(flx_ch3cho_ant(PLON,12))
427    ALLOCATE(flx_ch3coch3_ant(PLON,12))
428    ALLOCATE(flx_mek_ant(PLON,12))
429    ALLOCATE(flx_mvk_ant(PLON,12))
430    ALLOCATE(flx_ch3cooh_ant(PLON,12))
431    ALLOCATE(flx_isop_ant(PLON,12))
432    ALLOCATE(flx_apin_ant(PLON,12))
433    ALLOCATE(flx_so2_ant(PLON,12))
434    ALLOCATE(flx_h2s_ant(PLON,12))
435    ALLOCATE(flx_bc_ant(PLON,12))
436    ALLOCATE(flx_pom_ant(PLON,12))
437    ALLOCATE(flx_nh3_ant(PLON,12))
438    ALLOCATE(flx_so4_ant(PLON,12))
439   
440    flx_co2_ant             = 0.
441    flx_n2o_ant             = 0.
442    flx_ch4_ant             = 0.
443    flx_ch4_ant_interp      = 0.
444    flx_co_ant              = 0.
445    flx_h2_ant              = 0.
446    flx_no_ant              = 0.
447    flx_mcf_ant             = 0.
448    flx_ch3oh_ant           = 0.
449    flx_c2h5oh_ant          = 0.
450    flx_c2h6_ant            = 0.
451    flx_c3h8_ant            = 0.
452    flx_alkan_ant           = 0.
453    flx_c2h4_ant            = 0.
454    flx_c3h6_ant            = 0.
455    flx_c2h2_ant            = 0.
456    flx_alken_ant           = 0.
457    flx_arom_ant            = 0.
458    flx_ch2o_ant            = 0.
459    flx_ch3cho_ant          = 0.
460    flx_ch3coch3_ant        = 0.
461    flx_mek_ant             = 0.
462    flx_mvk_ant             = 0.
463    flx_ch3cooh_ant         = 0.
464    flx_isop_ant            = 0.
465    flx_apin_ant            = 0.
466    flx_nh3_ant             = 0.
467    flx_so2_ant             = 0.
468    flx_h2s_ant             = 0.
469    flx_bc_ant              = 0.
470    flx_pom_ant             = 0. 
471    flx_so4_ant             = 0. 
472
473    !Natural emissions (NAT)
474    ALLOCATE(flx_co2_nat(PLON,12))
475    ALLOCATE(flx_n2o_nat(PLON,12))
476    ALLOCATE(flx_ch4_nat(PLON,12))
477    ALLOCATE(flx_co_nat(PLON,12))
478    ALLOCATE(flx_h2_nat(PLON,12))
479    ALLOCATE(flx_no_nat(PLON,12))
480    ALLOCATE(flx_mcf_nat(PLON,12))
481    ALLOCATE(flx_ch3oh_nat(PLON,12))
482    ALLOCATE(flx_c2h5oh_nat(PLON,12))
483    ALLOCATE(flx_c2h6_nat(PLON,12))
484    ALLOCATE(flx_c3h8_nat(PLON,12))
485    ALLOCATE(flx_alkan_nat(PLON,12))
486    ALLOCATE(flx_c2h4_nat(PLON,12))
487    ALLOCATE(flx_c3h6_nat(PLON,12))
488    ALLOCATE(flx_c2h2_nat(PLON,12))
489    ALLOCATE(flx_alken_nat(PLON,12))
490    ALLOCATE(flx_arom_nat(PLON,12))
491    ALLOCATE(flx_ch2o_nat(PLON,12))
492    ALLOCATE(flx_ch3cho_nat(PLON,12))
493    ALLOCATE(flx_ch3coch3_nat(PLON,12))
494    ALLOCATE(flx_mek_nat(PLON,12))
495    ALLOCATE(flx_mvk_nat(PLON,12))
496    ALLOCATE(flx_ch3cooh_nat(PLON,12))
497    ALLOCATE(flx_isop_nat(PLON,12))
498    ALLOCATE(flx_apin_nat(PLON,12))
499    ALLOCATE(flx_so2_nat(PLON,12))
500    ALLOCATE(flx_h2s_nat(PLON,12))
501    ALLOCATE(flx_bc_nat(PLON,12))
502    ALLOCATE(flx_pom_nat(PLON,12))
503    ALLOCATE(flx_nh3_nat(PLON,12))
504    ALLOCATE(flx_so4_nat(PLON,12))
505
506    flx_co2_nat             = 0.
507    flx_n2o_nat             = 0.
508    flx_ch4_nat             = 0.
509    flx_co_nat              = 0.
510    flx_h2_nat              = 0.
511    flx_no_nat              = 0.
512    flx_mcf_nat             = 0.
513    flx_ch3oh_nat           = 0.
514    flx_c2h5oh_nat          = 0.
515    flx_c2h6_nat            = 0.
516    flx_c3h8_nat            = 0.
517    flx_alkan_nat           = 0.
518    flx_c2h4_nat            = 0.
519    flx_c3h6_nat            = 0.
520    flx_c2h2_nat            = 0.
521    flx_alken_nat           = 0.
522    flx_arom_nat            = 0.
523    flx_ch2o_nat            = 0.
524    flx_ch3cho_nat          = 0.
525    flx_ch3coch3_nat        = 0.
526    flx_mek_nat             = 0.
527    flx_mvk_nat             = 0.
528    flx_ch3cooh_nat         = 0.
529    flx_isop_nat            = 0.
530    flx_apin_nat            = 0.
531    flx_nh3_nat             = 0.
532    flx_so2_nat             = 0.
533    flx_h2s_nat             = 0.
534    flx_bc_nat              = 0.
535    flx_pom_nat             = 0. 
536    flx_so4_nat             = 0. 
537
538    !Biomass burning emissions (BBG)
539    ALLOCATE(flx_co2_bbg(PLON,12))
540    ALLOCATE(flx_n2o_bbg(PLON,12))
541    ALLOCATE(flx_ch4_bbg(PLON,12))
542    ALLOCATE(flx_co_bbg(PLON,12))
543    ALLOCATE(flx_h2_bbg(PLON,12))
544    ALLOCATE(flx_no_bbg(PLON,12))
545    ALLOCATE(flx_mcf_bbg(PLON,12))
546    ALLOCATE(flx_ch3oh_bbg(PLON,12))
547    ALLOCATE(flx_c2h5oh_bbg(PLON,12))
548    ALLOCATE(flx_c2h6_bbg(PLON,12))
549    ALLOCATE(flx_c3h8_bbg(PLON,12))
550    ALLOCATE(flx_alkan_bbg(PLON,12))
551    ALLOCATE(flx_c2h4_bbg(PLON,12))
552    ALLOCATE(flx_c3h6_bbg(PLON,12))
553    ALLOCATE(flx_c2h2_bbg(PLON,12))
554    ALLOCATE(flx_alken_bbg(PLON,12))
555    ALLOCATE(flx_arom_bbg(PLON,12))
556    ALLOCATE(flx_ch2o_bbg(PLON,12))
557    ALLOCATE(flx_ch3cho_bbg(PLON,12))
558    ALLOCATE(flx_ch3coch3_bbg(PLON,12))
559    ALLOCATE(flx_mek_bbg(PLON,12))
560    ALLOCATE(flx_mvk_bbg(PLON,12))
561    ALLOCATE(flx_ch3cooh_bbg(PLON,12))
562    ALLOCATE(flx_isop_bbg(PLON,12))
563    ALLOCATE(flx_apin_bbg(PLON,12))
564    ALLOCATE(flx_so2_bbg(PLON,12))
565    ALLOCATE(flx_h2s_bbg(PLON,12))
566    ALLOCATE(flx_bc_bbg(PLON,12))
567    ALLOCATE(flx_pom_bbg(PLON,12))
568    ALLOCATE(flx_nh3_bbg(PLON,12))
569    ALLOCATE(flx_so4_bbg(PLON,12))
570
571    flx_co2_bbg             = 0.
572    flx_n2o_bbg             = 0.
573    flx_ch4_bbg             = 0.
574    flx_co_bbg              = 0.
575    flx_h2_bbg              = 0.
576    flx_no_bbg              = 0.
577    flx_mcf_bbg             = 0.
578    flx_ch3oh_bbg           = 0.
579    flx_c2h5oh_bbg          = 0.
580    flx_c2h6_bbg            = 0.
581    flx_c3h8_bbg            = 0.
582    flx_alkan_bbg           = 0.
583    flx_c2h4_bbg            = 0.
584    flx_c3h6_bbg            = 0.
585    flx_c2h2_bbg            = 0.
586    flx_alken_bbg           = 0.
587    flx_arom_bbg            = 0.
588    flx_ch2o_bbg            = 0.
589    flx_ch3cho_bbg          = 0.
590    flx_ch3coch3_bbg        = 0.
591    flx_mek_bbg             = 0.
592    flx_mvk_bbg             = 0.
593    flx_ch3cooh_bbg         = 0.
594    flx_isop_bbg            = 0.
595    flx_apin_bbg            = 0.
596    flx_nh3_bbg             = 0.
597    flx_so2_bbg             = 0.
598    flx_h2s_bbg             = 0.
599    flx_bc_bbg              = 0.
600    flx_pom_bbg             = 0. 
601    flx_so4_bbg             = 0. 
602
603   
604  END SUBROUTINE init_srf_flux_int
605 
606END MODULE SRF_FLUX_INT
607
608
Note: See TracBrowser for help on using the repository browser.