source: branches/publications/ORCHIDEE_GLUC_r6545/src_sechiba/chemistry.f90 @ 6737

Last change on this file since 6737 was 4719, checked in by albert.jornet, 7 years ago

Merge: from revisions [4491:4695/trunk/ORCHIDEE]

Merge done in [4671:4718/perso/albert.jornet/MICT_MERGE]

  • Property svn:keywords set to Date Revision HeadURL
File size: 99.8 KB
Line 
1! ================================================================================================================================
2!  MODULE       : chemistry
3!
4!  CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6!  LICENCE      : IPSL (2006)
7!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF   
10!!
11!!\n DESCRIPTION:
12!!
13!! RECENT CHANGE(S): The content of this module were previously part of the diffuco module.
14!!                   ok_inca changed name into ok_bvoc and DIFFUCO_OK_INCA changed into CHEMISTRY_BVOC
15!!                   LEAFAGE_OK_INCA changed name into CHEMISTRY_LEAFAGE
16!!
17!! $HeadURL$
18!! $Date$
19!! $Revision$
20!! \n
21!_ ================================================================================================================================
22
23MODULE chemistry
24
25  USE ioipsl
26  USE xios_orchidee
27  USE constantes
28  USE qsat_moisture
29  USE sechiba_io_p
30  USE ioipsl
31  USE pft_parameters
32  USE grid
33  USE time, ONLY : one_day, dt_sechiba, julian_diff, one_hour, one_year
34  USE ioipsl_para 
35  USE xios_orchidee
36
37  IMPLICIT NONE
38
39  PRIVATE
40  PUBLIC :: chemistry_initialize, chemistry_bvoc, chemistry_flux_interface, chemistry_clear
41
42
43  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: flx_iso            !! Isoprene emissions from vegetation (kgC.m^{-2}.s^{-1})
44!$OMP THREADPRIVATE(flx_iso)
45  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: flx_mono           !! Monoterpene emissions from vegetation (kgC.m^{-2}.s^{-1})
46!$OMP THREADPRIVATE(flx_mono)
47  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: flx_ORVOC          !! Other Volatile Organic Compound emissions from vegetation (kgC.m^{-2}.s^{-1})
48!$OMP THREADPRIVATE(flx_ORVOC)
49  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: flx_MBO            !! 2-methyl-3-buten-2-ol emissions from vegetation (mainly pines in America) (kgC.m^{-2}.s^{-1})
50!$OMP THREADPRIVATE(flx_MBO)
51  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: flx_methanol       !! Methanol emissions from vegetation (kgC.m^{-2}.s^{-1})
52!$OMP THREADPRIVATE(flx_methanol)
53  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: flx_acetone        !! Acetone emissions from vegetation (kgC.m^{-2}.s^{-1})
54!$OMP THREADPRIVATE(flx_acetone)
55  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: flx_acetal         !! Acetaldehyde emissions from vegetation (kgC.m^{-2}.s^{-1})
56!$OMP THREADPRIVATE(flx_acetal)
57  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: flx_formal         !! Formaldehyde emissions from vegetation (kgC.m^{-2}.s^{-1})
58!$OMP THREADPRIVATE(flx_formal)
59  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: flx_acetic         !! Acetic acid emissions from vegetation (kgC.m^{-2}.s^{-1})
60!$OMP THREADPRIVATE(flx_acetic)
61  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: flx_formic         !! Formic acid emissions from vegetation (kgC.m^{-2}.s^{-1})
62!$OMP THREADPRIVATE(flx_formic)
63  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:)  :: flx_apinen         !! Alpha pinene emissions from vegetation (kgC.m^{-2}.s^{-1})
64!$OMP THREADPRIVATE(flx_apinen)
65  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:)  :: flx_bpinen         !! Beta pinene emissions from vegetation (kgC.m^{-2}.s^{-1})
66!$OMP THREADPRIVATE(flx_bpinen)
67  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:)  :: flx_limonen        !! Limonene emissions from vegetation (kgC.m^{-2}.s^{-1})
68!$OMP THREADPRIVATE(flx_limonen)
69  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:)  :: flx_myrcen         !! Myrcene emissions from vegetation (kgC.m^{-2}.s^{-1})
70!$OMP THREADPRIVATE(flx_myrcen)
71  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:)  :: flx_sabinen        !! Sabinene emissions from vegetation (kgC.m^{-2}.s^{-1})
72!$OMP THREADPRIVATE(flx_sabinen)
73  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:)  :: flx_camphen        !! Camphene emissions from vegetation (kgC.m^{-2}.s^{-1})
74!$OMP THREADPRIVATE(flx_camphen)
75  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:)  :: flx_3caren         !! 3-Carene emissions from vegetation (kgC.m^{-2}.s^{-1})
76!$OMP THREADPRIVATE(flx_3caren)
77  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:)  :: flx_tbocimen       !! T-beta Ocimene emissions from vegetation (kgC.m^{-2}.s^{-1})
78!$OMP THREADPRIVATE(flx_tbocimen)
79  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:)  :: flx_othermono      !! Emissions of other monoterpenes from vegetation (kgC.m^{-2}.s^{-1})
80!$OMP THREADPRIVATE(flx_othermono)
81  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:)  :: flx_sesquiter      !! Sesquiterpene emissions from vegetation (kgC.m^{-2}.s^{-1})
82!$OMP THREADPRIVATE(flx_sesquiter)
83  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: flx_fertil_no      !! Biogenic nitrogen oxide soil emission due to N-fertilisation (ngN.m^{-2}.s^{-1})
84!$OMP THREADPRIVATE(flx_fertil_no)
85  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: flx_no_soil        !! Nitrogen Oxide emissions from soil, before deposition on canopy
86                                                                       !! (ngN.m^{-2}.s^{-1})
87!$OMP THREADPRIVATE(flx_no_soil)
88  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: flx_no             !! Net nitrogen Oxide emissions from soil, after deposition on canopy
89!$OMP THREADPRIVATE(flx_no)
90  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: CRF                !! Canopy reduction factor for net NO flux calculation (kjpindex,nvm)   
91!$OMP THREADPRIVATE(CRF)
92
93  ! variables used inside diffuco_inca module
94  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:)     :: ok_siesta        !! Flag for controlling post-pulse period (true/false)
95!$OMP THREADPRIVATE(ok_siesta)
96  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:)     :: allow_pulse      !! Flag for controlling pulse period (true/false)
97!$OMP THREADPRIVATE(allow_pulse)
98  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pulse            !! Pulse fonction
99!$OMP THREADPRIVATE(pulse)
100  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pulseday         !! Counter for pulse period
101!$OMP THREADPRIVATE(pulseday)
102  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: siestaday        !! Counter for post-pulse period
103!$OMP THREADPRIVATE(siestaday)
104  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pulselim         !! Pulse period length
105!$OMP THREADPRIVATE(pulselim)
106  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: siestalim        !! Post-pulse period length
107!$OMP THREADPRIVATE(siestalim)
108  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: area2            !! Grid cell area (m^2)
109!$OMP THREADPRIVATE(area2)
110  REAL(r_std), SAVE                            :: nbre_precip 
111!$OMP THREADPRIVATE(nbre_precip)
112  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: flx_co2_bbg_year !! CO2 emissions from biomass burning
113                                                                   !! Read in an input file (kgC.m^{-2}.year^{-1})
114!$OMP THREADPRIVATE(flx_co2_bbg_year)
115  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: N_qt_WRICE_year  !! N fertilizers applied on wetland rice
116                                                                   !! Read in an input file (kgN.yr^{-1})
117!$OMP THREADPRIVATE(N_qt_WRICE_year)
118  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: N_qt_OTHER_year  !! N fertilizers applied on other crops and grasses
119                                                                   !! Read in an input file (kgN.yr^{-1})
120!$OMP THREADPRIVATE(N_qt_OTHER_year)
121  LOGICAL, SAVE   :: l_first_chemistry_inca=.TRUE.                 !! Initialisation for chemistry_flux_interface
122!$OMP THREADPRIVATE(l_first_chemistry_inca)
123     
124
125
126CONTAINS
127
128!! ================================================================================================================================
129!! SUBROUTINE   : chemistry_initialize
130!!
131!>\BRIEF         This subroutine initializes the chemistry module
132!!
133!! DESCRIPTION  : Some of the variables and flags used chemistry_bvoc are allocated and initialised here.
134!!
135!! RECENT CHANGE(S): Changed name from diffuco_inca_init to chemistry_initialize
136!!
137!! MAIN OUTPUT VARIABLE(S): None
138!!
139!! REFERENCE(S) : None
140!!
141!! FLOWCHART    : None
142!_ ================================================================================================================================
143  SUBROUTINE chemistry_initialize(kjpindex, lalo, neighbours, resolution)
144
145    USE interpweight
146
147    IMPLICIT NONE
148   
149    !! 0. Variables and parameter declaration
150
151    !! 0.1 Input variables
152
153    INTEGER(i_std), INTENT(in)                         :: kjpindex         !! Domain size (unitless)
154    REAL(r_std), DIMENSION(kjpindex,2), INTENT (in)    :: lalo             !! Geographical coordinates
155    INTEGER(i_std), DIMENSION(kjpindex,8), INTENT (in) :: neighbours       !! Vector of neighbours for each
156                                                                           !! grid point (1=N, 2=E, 3=S, 4=W)
157    REAL(r_std),DIMENSION (kjpindex,2), INTENT(in)     :: resolution       !! The size in km of each grid-box in X and Y
158
159    !! 0.2 Output variables
160    REAL(r_std), DIMENSION(kjpindex)                   :: achem_wrice      !! Availability of data for the interpolation
161    REAL(r_std), DIMENSION(kjpindex)                   :: achem_other      !! Availability of data for the interpolation
162    REAL(r_std), DIMENSION(kjpindex)                   :: achem_co2        !! Availability of data for the interpolation
163
164    !! 0.3 Modified variables
165
166    !! 0.4 Local variables
167    LOGICAL                                            :: allow_weathergen
168    CHARACTER(LEN=80)                                  :: filename, fieldname
169    INTEGER(i_std)                                     :: iml, jml, lml, tml, force_id
170    INTEGER(i_std)                                     :: ier
171    REAL(r_std)                                        :: vmin, vmax       !! min/max values to use for the
172                                                                           !!   renormalization
173    CHARACTER(LEN=250)                                 :: maskvname        !! Variable to read the mask from
174                                                                           !! the file
175    CHARACTER(LEN=80)                                  :: lonname, latname !! lon, lat names in input file
176    REAL(r_std), DIMENSION(:), ALLOCATABLE             :: variabletypevals !! Values for all the types of the variable
177                                                                           !!   (variabletypevals(1) = -un, not used)
178    CHARACTER(LEN=50)                                  :: fractype         !! method of calculation of fraction
179                                                                           !!   'XYKindTime': Input values are kinds
180                                                                           !!     of something with a temporal
181                                                                           !!     evolution on the dx*dy matrix'
182    LOGICAL                                            :: nonegative       !! whether negative values should be removed
183    CHARACTER(LEN=50)                                  :: maskingtype      !! Type of masking
184                                                                           !!   'nomask': no-mask is applied
185                                                                           !!   'mbelow': take values below maskvals(1)
186                                                                           !!   'mabove': take values above maskvals(1)
187                                                                           !!   'msumrange': take values within 2 ranges;
188                                                                           !!      maskvals(2) <= SUM(vals(k)) <= maskvals(1)
189                                                                           !!      maskvals(1) < SUM(vals(k)) <= maskvals(3)
190                                                                           !!        (normalized by maskvals(3))
191                                                                           !!   'var': mask values are taken from a
192                                                                           !!     variable inside the file (>0)
193    REAL(r_std), DIMENSION(3)                          :: maskvals         !! values to use to mask (according to
194                                                                           !!   `maskingtype')
195    CHARACTER(LEN=250)                                 :: namemaskvar      !! name of the variable to use to mask
196    REAL(r_std)                                        :: chem_norefinf    !! No value
197    REAL(r_std)                                        :: chem_default     !! Default value
198
199!_ ================================================================================================================================
200
201    ALLOCATE (pulse(kjpindex),stat=ier)
202    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_initialize','Problem in allocate of variable pulse','','')
203    pulse(:) = un
204
205    ! If we acount for NOx pulse emissions
206    IF (ok_pulse_NOx) THEN
207
208       ALLOCATE (ok_siesta(kjpindex),stat=ier)
209       IF (ier /= 0) CALL ipslerr_p(3,'chemistry_initialize','Problem in allocate of variable ok_siesta','','')
210       ok_siesta(:) = .FALSE.
211
212       ALLOCATE (allow_pulse(kjpindex),stat=ier)
213       IF (ier /= 0) CALL ipslerr_p(3,'chemistry_initialize','Problem in allocate of variable allow_pulse','','')
214       allow_pulse(:) = .FALSE.
215
216       ALLOCATE (pulseday(kjpindex),stat=ier)
217       IF (ier /= 0) CALL ipslerr_p(3,'chemistry_initialize','Problem in allocate of variable pulseday','','')
218       pulseday(:) = zero
219
220       ALLOCATE (siestaday(kjpindex),stat=ier)
221       IF (ier /= 0) CALL ipslerr_p(3,'chemistry_initialize','Problem in allocate of variable siestaday','','')
222       siestaday(:) = zero
223
224       ALLOCATE (pulselim(kjpindex),stat=ier)
225       IF (ier /= 0) CALL ipslerr_p(3,'chemistry_initialize','Problem in allocate of variable pulselim','','')
226       pulselim(:) = zero
227
228       ALLOCATE (siestalim(kjpindex),stat=ier)
229       IF (ier /= 0) CALL ipslerr_p(3,'chemistry_initialize','Problem in allocate of variable siestalim','','')
230       siestalim(:) = zero
231
232    END IF ! (ok_pulse_NOx)
233
234    ! If we acount for NOx emissions by N-fertilizers
235    IF (ok_cropsfertil_NOx) THEN
236
237       ALLOCATE (area2(kjpindex),stat=ier)
238       IF (ier /= 0) CALL ipslerr_p(3,'chemistry_initialize','Problem in allocate of variable area2','','')
239       area2(:) = resolution(:,1)*resolution(:,2) 
240
241       ALLOCATE (N_qt_WRICE_year(kjpindex),stat=ier)  !! N fertilizers on wetland rice, read in file
242       IF (ier /= 0) CALL ipslerr_p(3,'chemistry_initialize','Problem in allocate of variable N_qt_WRICE_year','','')
243       N_qt_WRICE_year(:) = zero
244   
245       ALLOCATE (N_qt_OTHER_year(kjpindex),stat=ier)  !! N fertilizers on other crops and grasses, read in file
246       IF (ier /= 0) CALL ipslerr_p(3,'chemistry_initialize','Problem in allocate of variable N_qt_OTHER_year','','')
247       N_qt_OTHER_year(:) = zero
248
249       WRITE (numout,*) ' *********************** Interpolating N fertilizers files for NOx emissions... '
250
251       !Config Key   = N_FERTIL_FILE
252       !Config Desc  = File name
253       !Config If    = CHEMISTRY_BVOC and NOx_FERTILIZERS_USE
254       !Config Def   = orchidee_fertilizer_1995.nc
255       !Config Help  =
256       !Config Units = -
257       filename = 'orchidee_fertilizer_1995.nc'
258       CALL getin_p('N_FERTIL_FILE',filename) 
259       
260       !! Variables for interpweight
261       vmin = 0.
262       vmax = 0.
263       ! Type of calculation of cell fractions
264       fractype = 'default'
265       ! Name of the longitude and latitude in the input file
266       lonname = 'lon'
267       latname = 'lat'
268       ! Default value when no value is get from input file
269       chem_default = 0.
270       ! Reference value when no value is get from input file
271       chem_norefinf = 0.
272       ! Should negative values be set to zero from input file?
273       nonegative = .TRUE.
274       ! Type of mask to apply to the input data (see header for more details)
275       maskingtype = 'nomask'
276       ! Values to use for the masking
277       maskvals = (/ min_sechiba, undef_sechiba, undef_sechiba /)
278       ! Name of the variable with the values for the mask in the input file (only if maskkingtype='var') (here not used)
279       namemaskvar = ''
280
281       fieldname= 'N_qt_WRICE_year'
282       IF (printlev >= 1) WRITE(numout,*) "chemistry_initialize: Read and interpolate file " &
283            // TRIM(filename) //" for variable N_qt_WRICE_year"
284       CALL interpweight_2Dcont(kjpindex, 0, 0, lalo, resolution, neighbours,                        &
285            contfrac, filename, fieldname, lonname, latname, vmin, vmax, nonegative, maskingtype,       &
286            maskvals, namemaskvar, -1, fractype, chem_default, chem_norefinf,                           &
287            N_qt_WRICE_year, achem_wrice)
288       
289       fieldname= 'N_qt_OTHER_year'
290       IF (printlev >= 1) WRITE(numout,*) "chemistry_initialize: Read and interpolate file " &
291            // TRIM(filename) //" for variable N_qt_OTHER_year"
292       CALL interpweight_2Dcont(kjpindex, 0, 0, lalo, resolution, neighbours,                        &
293            contfrac, filename, fieldname, lonname, latname, vmin, vmax, nonegative, maskingtype,       &
294            maskvals, namemaskvar, -1, fractype, chem_default, chem_norefinf,                           &
295            N_qt_OTHER_year, achem_other)
296       
297    END IF
298
299    ALLOCATE (flx_iso(kjpindex,nvm), stat=ier) 
300    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_iso','','')
301    flx_iso(:,:) = 0. 
302
303    ALLOCATE (flx_mono(kjpindex,nvm), stat=ier) 
304    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_mono','','')
305    flx_mono(:,:) = 0. 
306
307    ALLOCATE (flx_ORVOC(kjpindex,nvm), stat=ier) 
308    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_ORVOC ','','')
309    flx_ORVOC(:,:) = 0. 
310
311    ALLOCATE (flx_MBO(kjpindex,nvm), stat=ier) 
312    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_MBO','','')
313    flx_MBO(:,:) = 0. 
314
315    ALLOCATE (flx_methanol(kjpindex,nvm), stat=ier) 
316    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_methanol','','')
317    flx_methanol(:,:) = 0. 
318
319    ALLOCATE (flx_acetone(kjpindex,nvm), stat=ier) 
320    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_acetone','','')
321    flx_acetone(:,:) = 0. 
322
323    ALLOCATE (flx_acetal(kjpindex,nvm), stat=ier) 
324    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_acetal','','')
325    flx_acetal(:,:) = 0. 
326
327    ALLOCATE (flx_formal(kjpindex,nvm), stat=ier) 
328    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_formal','','')
329    flx_formal(:,:) = 0. 
330
331    ALLOCATE (flx_acetic(kjpindex,nvm), stat=ier) 
332    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_acetic','','')
333    flx_acetic(:,:) = 0. 
334
335    ALLOCATE (flx_formic(kjpindex,nvm), stat=ier) 
336    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_formic','','')
337    flx_formic(:,:) = 0. 
338
339    ALLOCATE (flx_no_soil(kjpindex,nvm), stat=ier) 
340    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_no_soil','','')
341    flx_no_soil(:,:) = 0. 
342
343    ALLOCATE (flx_no(kjpindex,nvm), stat=ier) 
344    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_no','','')
345    flx_no(:,:) = 0. 
346       
347    ALLOCATE (flx_fertil_no(kjpindex,nvm), stat=ier) 
348    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_fertil_no','','')
349    flx_fertil_no(:,:) = 0. 
350
351    ALLOCATE (flx_apinen(kjpindex,nvm), stat=ier) 
352    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_apinen','','')
353    flx_apinen(:,:) = 0.       
354
355    ALLOCATE (flx_bpinen (kjpindex,nvm), stat=ier) 
356    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_bpinen','','')
357    flx_bpinen(:,:) = 0.     
358
359    ALLOCATE (flx_limonen  (kjpindex,nvm), stat=ier) 
360    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_limonen','','')
361    flx_limonen(:,:) = 0.   
362
363    ALLOCATE (flx_myrcen(kjpindex,nvm), stat=ier) 
364    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_myrcen','','')
365    flx_myrcen(:,:) = 0.       
366
367    ALLOCATE (flx_sabinen(kjpindex,nvm), stat=ier) 
368    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_sabinen','','')
369    flx_sabinen(:,:) = 0.     
370
371    ALLOCATE (flx_camphen(kjpindex,nvm), stat=ier) 
372    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_camphen','','')
373    flx_camphen(:,:) = 0.     
374
375    ALLOCATE (flx_3caren(kjpindex,nvm), stat=ier) 
376    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_3caren','','')
377    flx_3caren(:,:) = 0.       
378
379    ALLOCATE (flx_tbocimen(kjpindex,nvm), stat=ier) 
380    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_tbocimen','','')
381    flx_tbocimen(:,:) = 0.     
382
383    ALLOCATE (flx_othermono(kjpindex,nvm), stat=ier) 
384    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_othermono','','')
385    flx_othermono(:,:) = 0.   
386
387    ALLOCATE (flx_sesquiter(kjpindex,nvm), stat=ier) 
388    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable flx_sesquiter','','')
389    flx_sesquiter(:,:) = 0.   
390
391    ALLOCATE(CRF(kjpindex,nvm), stat=ier) 
392    IF (ier /= 0) CALL ipslerr_p(3,'chemistry_init','Problem in allocate of variable CRF ','','')
393    CRF(:,:) = 0. 
394
395
396    ! If we acount for NOx emissions due to Biomass Burning
397    IF (ok_bbgfertil_NOx) THEN
398
399       ALLOCATE (flx_co2_bbg_year(kjpindex),stat=ier) !! CO2 emissions from bbg, read in file
400       IF (ier /= 0) CALL ipslerr_p(3,'chemistry_initialize','Problem in allocate of variable flx_co2_bbg_year','','')
401       flx_co2_bbg_year(:) = zero   
402
403       WRITE (numout,*) ' *********************** Interpolating CO2 bbg files for NOx emissions... '
404       !Config Key   = N_FERTIL_FILE
405       !Config Desc  = File name
406       !Config If    = CHEMISTRY_BVOC and NOx_FERTILIZERS_USE
407       !Config Def   = orchidee_fertilizer_1995.nc
408       !Config Help  = ...
409       !Config Units = -
410       filename = 'orchidee_bbg_clim.nc'
411       CALL getin_p('CO2_BBG_FILE',filename)
412
413       !! Variables for interpweight
414       vmin = 0.
415       vmax = 0.
416       ! Type of calculation of cell fractions
417       fractype = 'default'
418       ! Name of the longitude and latitude in the input file
419       lonname = 'lon'
420       latname = 'lat'
421       ! Default value when no value is get from input file
422       chem_default = 0.
423       ! Reference value when no value is get from input file
424       chem_norefinf = 0.
425       ! Should negative values be set to zero from input file?
426       nonegative = .TRUE.
427       ! Type of mask to apply to the input data (see header for more details)
428       maskingtype = 'nomask'
429       ! Values to use for the masking
430       maskvals = (/ min_sechiba, undef_sechiba, undef_sechiba /)
431       ! Name of the variable with the values for the mask in the input file (only if maskkingtype='var') (here not used)
432       namemaskvar = ''
433
434       fieldname = 'flx_co2_bbg_year'
435       IF (printlev >= 1) WRITE(numout,*) "chemistry_initialize: Read and interpolate file " &
436            // TRIM(filename) //" for variable flx_co2_bbg_year"
437       CALL interpweight_2Dcont(kjpindex, 0, 0, lalo, resolution, neighbours,                         &
438            contfrac, filename, fieldname, lonname, latname, vmin, vmax, nonegative, maskingtype,     &
439            maskvals, namemaskvar, -1, fractype, chem_default, chem_norefinf,                         &
440            flx_co2_bbg_year, achem_co2)
441    END IF
442
443    IF ( OFF_LINE_MODE ) THEN
444
445       !-
446       !- What are the alowed options for the temporal interpolation
447       !-
448       ! ALLOW_WEATHERGEN : Allow weather generator to create data
449       ! This parameter is already read in the driver
450       allow_weathergen = .FALSE.
451       CALL getin_p('ALLOW_WEATHERGEN',allow_weathergen)
452       
453       ! FORCING_FILE : Name of file containing the forcing data
454       ! This parameter is already read in the driver
455       filename='forcing_file.nc'
456       CALL getin_p('FORCING_FILE',filename)
457       CALL flininfo(filename,iml, jml, lml, tml, force_id)   
458       WRITE(numout,*) 'Number of data per year in forcing file :', tml 
459       CALL flinclo(force_id)
460       WRITE(numout,*) 'Forcing file closed in chemistry_initialize'
461       
462       
463       IF ( allow_weathergen ) THEN
464          WRITE(numout,*) '**chemistry_initialize: Using weather generator, careful to precip division for NOx '
465          nbre_precip = un
466          WRITE(numout,*) 'Division pour les precip, NOx:', nbre_precip
467       ELSE
468          WRITE(numout,*) 'DT_SECHIBA :', dt_sechiba
469          nbre_precip = (one_day/dt_sechiba)/(tml/one_year)
470          WRITE(numout,*) 'Division pour les precip, NOx:', nbre_precip
471       END IF
472
473    ELSE ! (in coupled mode)
474
475       nbre_precip = un
476       
477    END IF  ! (OFF_LINE_MODE)
478
479    ! Write diagnostics
480    IF (ok_cropsfertil_NOx) THEN
481      CALL xios_orchidee_send_field("achem_wrice",achem_wrice)
482      CALL xios_orchidee_send_field("achem_other",achem_other)
483    END IF
484    IF (ok_bbgfertil_NOx) THEN
485      CALL xios_orchidee_send_field("achem_co2",achem_co2)
486    END IF
487
488       
489  END SUBROUTINE chemistry_initialize
490
491
492!! ================================================================================================================================
493!! SUBROUTINE   : chemistry_bvoc
494!!
495!>\BRIEF         This subroutine computes biogenic emissions of reactive compounds, that is of
496!!               VOCs (volatile organic compounds) from vegetation and NOx (nitrogen oxides) from soils.
497!!               Calculation are mostly based on the works by Guenther et al. (1995) and Yienger and Levy (1995).\n
498!!
499!! DESCRIPTION  : Biogenic VOC emissions from vegetation are based on the parameterisations developped by
500!!                Guenther et al. (1995). Biogenic VOCs considered here are: isoprene, monoterpenes, OVOC and ORVOC
501!!                as bulked emissions, methanol, acetone, acetaldehyde, formaldehyde, acetic acid, formic acid
502!!                as single emissions.\n
503!!                For every biogenic VOCs an emission factor (EF), depending on the PFT considered, is used.\n
504!!                Isoprene emissions depend on temperature and radiation. A partition between sunlit and shaded
505!!                leaves is taken into account and either one (if ok_multilayer = FALSE) or several layers
506!!                (if ok_multilayer = TRUE) in the canopy can be used.\n
507!!                When radiation extinction is considered, the canopy radiative transfer model takes into
508!!                account light extinction through canopy, calculating first need diffuse and direct radiation
509!!                based on Andrew Friend 2001 radiative model and Spitters et al. 1986. The calculation of lai,
510!!                parscat, parsh and parsun, laisun and laishabsed based on Guenther et al.(JGR, 1995) and Norman (1982).\n
511!!                Emissions for other BVOCs (monoterpenes, OVOC, ORVOC and other single compounds such as
512!!                methanol, acetone...) depend only on temperature.\n   
513!!                The impact of leaf age, using an emission activity prescribed for each of the 4 leaf age
514!!                classes can also be considered for isoprene and methanol emissions when ok_leafage = TRUE.\n
515!!                NOx emissions from soils are based on Yienger and Levy (1995) and depend on soil moisture
516!!                and temperature and PFT. The pulse effect, related to significant rain occuring after severe
517!!                drought can also be considered (ok_pulse_NOx = TRUE), as well as the increase in emissions related to
518!!                biomass buring (ok_bbgfertil_NOx = TRUE) or use of fertilizers (ok_cropsfertil_NOx = TRUE).
519!!                A net NO flux is eventually calculated taking into account loss by deposition on the surface, using
520!!                a Canopy Reduction Factor (CRF) based on stomatal and leaf area.\n
521!!                This subroutine is called by diffuco_main only if biogenic emissions are activated
522!!                for sechiba (flag CHEMISTRY_BVOC=TRUE).\n
523!!
524!! RECENT CHANGE(S): Changed name from diffuco_inca to chemistry_bvoc
525!!
526!! MAIN OUTPUT VARIABLE(S): :: PAR, :: PARsun, :: PARsh, :: laisun, :: laish,
527!!                          :: flx_iso, :: flx_mono, :: flx_ORVOC, :: flx_MBO,
528!!                          :: flx_methanol, :: flx_acetone, :: flx_acetal, :: flx_formal,
529!!                          :: flx_acetic, :: flx_formic, :: flx_no_soil, :: flx_no,
530!!                          :: CRF, :: flx_fertil_no, :: Trans, :: Fdf,
531!!                          :: PARdf, :: PARdr, :: PARsuntab, :: PARshtab
532!!
533!! REFERENCE(S) :
534!! - Andrew Friend (2001), Modelling canopy CO2 fluxes: are 'big-leaf' simplifications justified?
535!! Global Ecology and Biogeography, 10, 6, 603-619, doi: 10.1046/j.1466-822x.2001.00268.x
536!! - Spitters, C.J.T, Toussaint, H.A.J.M, Groudriaan, J. (1986), Separating the diffuse and direct
537!! component of global radiation and its implications for modeling canopy photosynthesis, Agricultural
538!! and Forest Meteorology, 38, 1-3, 217-229, doi:10.1016/0168-1923(86)90060-2
539!! - Norman JM (1982) Simulation of microclimates. In: Hatfield JL, Thomason IJ (eds)
540!!  Biometeorology in integrated pest management. Academic, New York, pp 65–99
541!! - Guenther, A., Hewitt, C. N., Erickson, D., Fall, R., Geron, C., Graedel, T., Harley, P.,
542!! Klinger, L., Lerdau, M., McKay, W. A., Pierce, T., Scholes, B., Steinbrecher, R., Tallamraju,
543!! R., Taylor, J. et Zimmerman, P. (1995), A global model of natural volatile organic compound
544!! emissions, J. Geophys. Res., 100, 8873-8892.
545!! - MacDonald, R. et Fall, R. (1993), Detection of substantial emissions of methanol from
546!! plants to the atmosphere, Atmos. Environ., 27A, 1709-1713.
547!! - Guenther, A., Geron, C., Pierce, T., Lamb, B., Harley, P. et Fall, R. (2000), Natural emissions
548!! of non-methane volatile organic compounds, carbon monoxide, and oxides of nitrogen from
549!! North America, Atmos. Environ., 34, 2205-2230.
550!! - Yienger, J. J. et Levy II, H. (1995), Empirical model of global soil-biogenic NOx emissions,
551!! J. Geophys. Res., 100, 11,447-11,464.
552!! - Lathiere, J., D.A. Hauglustaine, A. Friend, N. De Noblet-Ducoudre, N. Viovy, and
553!!  G. Folberth (2006), Impact of climate variability and land use changes on global biogenic volatile
554!! organic compound emissions, Atmospheric Chemistry and Physics, 6, 2129-2146.
555!! - Lathiere, J., D.A. Hauglustaine, N. De Noblet-Ducoudre, G. Krinner et G.A. Folberth (2005),
556!! Past and future changes in biogenic volatile organic compound emissions simulated with a global
557!! dynamic vegetation model, Geophysical Research Letters, 32, doi: 10.1029/2005GL024164.
558!! - Lathiere, J. (2005), Evolution des emissions de composes organiques et azotes par la biosphere
559!!  continentale dans le modele LMDz-INCA-ORCHIDEE, These de doctorat, Universite Paris VI.
560!!
561!! FLOWCHART    : None
562!_ ================================================================================================================================
563
564  SUBROUTINE chemistry_bvoc (kjpindex, swdown, coszang, temp_air, &
565       temp_sol, ptnlev1, precip_rain, humrel, veget_max, lai, &
566       frac_age, lalo, ccanopy, cim,  wind, snow, &
567       veget, hist_id, hist2_id,kjit, index, &
568       indexlai, indexveg)
569
570    !! 0. Variables and parameter declaration
571
572    !! 0.1 Input variables
573
574    INTEGER(i_std), INTENT(in)                                 :: kjpindex         !! Domain size - terrestrial pixels only (unitless)
575    INTEGER(i_std), INTENT(in)                                 :: kjit             !! Time step number (-)
576    INTEGER(i_std),INTENT (in)                                 :: hist_id          !! History file identifier (-)
577    INTEGER(i_std),INTENT (in)                                 :: hist2_id         !! History file 2 identifier (-)
578    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)           :: index            !! Indeces of the points on the map (-)
579    INTEGER(i_std),DIMENSION (kjpindex*(nlai+1)), INTENT (in)  :: indexlai         !! Indeces of the points on the 3D map
580    INTEGER(i_std),DIMENSION (kjpindex*nvm), INTENT (in)       :: indexveg         !! Indeces of the points on the 3D map (-)
581    REAL(r_std), DIMENSION(kjpindex), INTENT(in)               :: swdown           !! Down-welling surface short-wave flux
582                                                                                   !! (W.m^{-2})
583    REAL(r_std), DIMENSION(kjpindex), INTENT(in)               :: coszang          !! Cosine of the solar zenith angle (unitless)
584    REAL(r_std), DIMENSION(kjpindex), INTENT(in)               :: temp_air         !! Air temperature (K)
585    REAL(r_std), DIMENSION(kjpindex), INTENT(in)               :: temp_sol         !! Skin temperature (K)
586    REAL(r_std), DIMENSION(kjpindex), INTENT(in)               :: ptnlev1          !! 1st level of soil temperature (K)
587    REAL(r_std), DIMENSION(kjpindex), INTENT(in)               :: precip_rain      !! Rain precipitation !!?? init
588    REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)           :: humrel           !! Soil moisture stress (0-1, unitless)
589    REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)           :: veget_max        !! Max. vegetation fraction (0-1, unitless)
590    REAL(r_std),DIMENSION (kjpindex), INTENT (in)              :: snow             !! Snow mass (kg)
591    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)          :: veget            !! Fraction of vegetation type (-)
592    REAL(r_std), DIMENSION(kjpindex,nvm), INTENT(in)           :: lai              !! Leaf area index (m^2.m^{-2})
593    REAL(r_std), DIMENSION(kjpindex,nvm,nleafages), INTENT(in) :: frac_age         !! Age efficacity from STOMATE for iso
594    REAL(r_std), DIMENSION(kjpindex,2), INTENT(in)             :: lalo             !! Geographical coordinates for pixels (degrees)
595    REAL(r_std),DIMENSION (kjpindex), INTENT (in)              :: ccanopy          !! CO2 concentration inside the canopy
596    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)          :: cim              !! Intercellular CO2 over nlai
597    REAL(r_std), DIMENSION (kjpindex), INTENT(in)              :: wind             !! Wind module (m s^{-1})
598
599    !! 0.2 Output variables
600
601    !! 0.3 Modified variables
602
603    !! 0.4 Local variables
604
605    INTEGER(i_std)                             :: ji, jv, jf, jl    !! Indices (unitless)
606    REAL(r_std), DIMENSION(kjpindex,nvm)       :: fol_dens          !! foliar density (gDM.m^{-2})
607    REAL(r_std), DIMENSION(kjpindex)           :: tleaf             !! Foliar temperature (K)
608    REAL(r_std), DIMENSION(kjpindex)           :: t_no              !! Temperature used for soil NO emissions (C)
609    REAL(r_std), DIMENSION(kjpindex)           :: exp_1             !! First exponential used in the calculation of
610                                                                    !! isoprene dependancy to Temperature
611    REAL(r_std), DIMENSION(kjpindex)           :: exp_2             !! Second exponential used in the calculation of
612                                                                    !! Isoprene dependancy to Temperature
613    REAL(r_std), DIMENSION(kjpindex)           :: Ct_iso            !! Isoprene dependancy to Temperature
614    REAL(r_std), DIMENSION(kjpindex)           :: Cl_iso            !! Isoprene dependancy to Light
615    REAL(r_std), DIMENSION(kjpindex)           :: Ct_mono           !! Monoterpene dependancy to Temperature
616    REAL(r_std), DIMENSION(kjpindex)           :: Ct_sesq           !! Sesquiterpenes dependancy to Temperature
617    REAL(r_std), DIMENSION(kjpindex)           :: Ct_meth           !! Methanol dependancy to Temperature
618    REAL(r_std), DIMENSION(kjpindex)           :: Ct_acet           !! Acetone dependancy to Temperature
619    REAL(r_std), DIMENSION(kjpindex)           :: Ct_oxyVOC         !! Other oxygenated BVOC dependancy to Temperature
620    REAL(r_std)                                :: GAMMA_iso         !! Temperature and light dependancy for isoprene and fo each PFT
621    REAL(r_std)                                :: GAMMA_iso_m       !! Temperature and light dependancy for isoprene and fo each PFT for multilayer
622    REAL(r_std), DIMENSION(kjpindex)           :: Ylt_mono          !! Total Temperature and light dependancy for monoterpenes
623    REAL(r_std), DIMENSION(kjpindex)           :: Ylt_sesq          !! Total Temperature and light dependancy for sesquiterpens
624    REAL(r_std), DIMENSION(kjpindex)           :: Ylt_meth          !! Total Temperature and light dependancy for methanol
625    REAL(r_std), DIMENSION(kjpindex)           :: Ylt_acet          !! Total Temperature and light dependancy for acetone
626    REAL(r_std), DIMENSION(kjpindex)           :: Ct_MBO            !! MBO dependance to Temperature
627    REAL(r_std), DIMENSION(kjpindex)           :: Cl_MBO            !! MBO dependance to Light
628    REAL(r_std), DIMENSION(kjpindex)           :: Xvar              !! Parameter used in the calculation
629                                                                    !! of MBO dependance to Temperature
630    REAL(r_std), DIMENSION(kjpindex,nvm)       :: flx_OVOC          !! Biogenic OVOC emission -
631                                                                    !! Other Volatil Organic Components (kgC.m^{-2}.s^{-1})
632    !!Canopy radiative transfer model
633    REAL(r_std), DIMENSION(kjpindex)           :: So                !! Maximum radiation at the Earth surface (W.m^{-2})
634    REAL(r_std), DIMENSION(kjpindex)           :: Rfrac             !! Parameter in the regression of diffuse
635                                                                    !! share on transmission
636    REAL(r_std), DIMENSION(kjpindex)           :: Kfrac             !! Parameter in the regression of diffuse
637                                                                    !! share on transmission
638    REAL(r_std), DIMENSION(kjpindex)           :: swdf              !! Sw diffuse radiation (W.m^{-2})
639    REAL(r_std), DIMENSION(kjpindex)           :: swdr              !! Sw direct radiation (W.m^{-2})
640    REAL(r_std), DIMENSION(kjpindex,nvm)       :: PARscat           !! Scatter PAR @tex ($\mu mol m^{-2} s^{-1}$) @endtex
641    REAL(r_std), DIMENSION(kjpindex,nvm)       :: Clsun_iso         !! Isoprene dependance to light for sun leaves
642    REAL(r_std), DIMENSION(kjpindex,nvm)       :: Clsh_iso          !! Isoprene dependance to light for shaded leaves
643    !! for multilayer canopy model for iso flux
644    REAL(r_std), DIMENSION(kjpindex,nlai+1)    :: PARscattab        !! Scatter PAR @tex ($\mu mol m^{-2} s^{-1}$) @endtex
645    REAL(r_std), DIMENSION(nlai+1)             :: laitab            !! LAI per layer (m^2.m^{-2})
646    REAL(r_std), DIMENSION(kjpindex,nlai)      :: laisuntabdep      !! LAI of sun leaves in each layer (m^2.m^{-2})
647    REAL(r_std), DIMENSION(kjpindex,nlai)      :: laishtabdep       !! LAI of shaded leaves in each layer
648                                                                    !! (m^2.m^{-2})
649    REAL(r_std)                                :: Clsun_iso_tab     !! Isoprene dependance to light
650                                                                    !! for sun leaves and per layer
651    REAL(r_std)                                :: Clsh_iso_tab      !! Isoprene dependance to light
652                                                                    !! for shaded leaves and per layer
653    !for multilayer canopy model Spitter et al. 1986
654    REAL(r_std), DIMENSION(kjpindex,nlai+1)    :: PARnotscat        !! Not-Scattered PAR
655    REAL(r_std), DIMENSION(kjpindex,nlai+1)    :: PARabsdir         !! Absorbed light of the PAR direct flux 
656    REAL(r_std), DIMENSION(kjpindex,nlai+1)    :: PARabsdiff        !! Absorbed light of the PAR diffuse flux 
657    REAL(r_std), PARAMETER                     :: sigma = 0.20      !! scattering coefficient of single leaves and for visible radiation
658    REAL(r_std), PARAMETER                     :: cluster = 0.85    !! clustering coefficient for leaves, the same that is setting for default in MEGAN V2.10
659    REAL(r_std)                                :: rho               !! reflection index of a green, closed vegetation
660    REAL(r_std)                                :: kbl               !! extinction coefficient of black leaves
661    REAL(r_std)                                :: kdf               !! extinction coefficient of diffuse flux
662    !!Leaf age
663    REAL(r_std), DIMENSION(kjpindex,nvm)       :: Eff_age_iso       !! Isoprene emission dependance to Leaf Age
664    REAL(r_std), DIMENSION(kjpindex,nvm)       :: Eff_age_meth      !! Methanol emission dependance to Leaf Age
665    REAL(r_std), DIMENSION(kjpindex,nvm)       :: Eff_age_VOC       !! Other VOC emission dependance to Leaf Age
666    !!BBG and Fertilizers for NOx soil emission
667    REAL(r_std), DIMENSION(kjpindex)           :: veget_max_nowoody !! sum of veget_max for non-woody PFT
668    REAL(r_std), DIMENSION(kjpindex,nvm)       :: N_qt_WRICE_pft    !! N fertiliser on RICE
669                                                                    !! (kgN per year per grid cell)
670    REAL(r_std), DIMENSION(kjpindex,nvm)       :: N_qt_OTHER_pft    !! N fertiliser on other veg
671                                                                    !! (kgN per year per grid cell)
672    !! CO2 inhibition effect on isoprene
673    REAL(r_std),DIMENSION (kjpindex,nvm)       :: fco2_wshort       !! Wilkinson short term function for CO2 impact on BVOC (isoprene)
674    REAL(r_std),DIMENSION (kjpindex)           :: fco2_wlong        !! Wilkinson long term function for CO2 impact on BVOC (isoprene)
675    REAL(r_std)                                :: fco2_ctrl
676    REAL(r_std),DIMENSION (kjpindex,nvm)       :: fco2              !! Function for CO2 impact on BVOC (isoprene)
677    REAL(r_std), DIMENSION(kjpindex)           :: Ismax_short
678    REAL(r_std), DIMENSION(kjpindex)           :: h_short
679    REAL(r_std), DIMENSION(kjpindex)           :: Cstar_short
680    REAL(r_std)                                :: Ismax_long
681    REAL(r_std)                                :: h_long
682    REAL(r_std)                                :: Cstar_long
683
684    !! 0.5 Parameters values
685
686    REAL(r_std), PARAMETER :: CT1 = 95000.0       !! Empirical coeffcient (see Guenther .et. al, 1995, eq(10)) (J.mol^{-1})
687    REAL(r_std), PARAMETER :: CT2 = 230000.0      !! Empirical coefficient (see Guenther .et. al, 1995, eq(10)) (J.mol^{-1})
688    REAL(r_std), PARAMETER :: TS = 303.0          !! Leaf temperature at standard condition
689                                                  !! (see Guenther .et. al, 1995, eq(10)) (K)
690    REAL(r_std), PARAMETER :: TM = 314.0          !! Leaf temperature (see Guenther .et. al, 1995, eq(10)) (K)
691
692    REAL(r_std), PARAMETER :: alpha_ = 0.0027     !! Empirical coeffcient (see Guenther .et. al, 1995, eq(9)) (unitless)
693    REAL(r_std), PARAMETER :: CL1 = 1.066         !! Empirical coeffcient (see Guenther .et. al, 1995, eq(9)) (unitless)
694    REAL(r_std), PARAMETER :: beta = 0.09         !! Empirical coeffcient (see Guenther .et. al, 1995, eq(11)) (K^{-1})
695    REAL(r_std), PARAMETER :: lai_threshold = 11. !! Lai threshold for the calculation of scattered radiation
696                                                  !! based on Guenther .et. al (1995) (m^2.m^{-2})
697
698                                             
699    ! Biogenic emissions
700    REAL(r_std),DIMENSION(kjpindex)          :: PAR                !! Photosynthetic active radiation, half of swdown
701                                                                   !! @tex ($\mu mol photons. m^{-2} s^{-1}$) @endtex
702    REAL(r_std),DIMENSION(kjpindex,nvm)      :: PARsun             !! PAR received by sun leaves
703                                                                   !! @tex ($\mu mol m^{-2} s^{-1}$) @endtex
704    REAL(r_std),DIMENSION(kjpindex,nvm)      :: PARsh              !! PAR received by shaded leaves
705                                                                   !! @tex ($\mu mol m^{-2} s^{-1}$) @endtex
706    REAL(r_std),DIMENSION(kjpindex,nvm)      :: laisun             !! Leaf area index of Sun leaves (m^2.m^{-2})
707    REAL(r_std),DIMENSION(kjpindex,nvm)      :: laish              !! Leaf area index of Shaded leaves (m^2.m^{-2})
708
709    CHARACTER(LEN=14)                        :: tleafsun_name      !! To store variables names for I/O
710    CHARACTER(LEN=13)                        :: tleafsh_name       !! To store variables names for I/O
711    REAL(r_std), DIMENSION(kjpindex,nlai+1)  :: Tleafsun_temp      !! temporary sunlit leaf temperature matrix for writing
712    REAL(r_std), DIMENSION(kjpindex,nlai+1)  :: Tleafsh_temp       !! temporary shade leaf temperature matrix for writing
713    REAL(r_std),DIMENSION(kjpindex)          :: Fdf                !! Fraction of the radiation which is diffused (0-1, unitless)
714    REAL(r_std),DIMENSION(kjpindex,nlai+1)   :: PARsuntab          !! PAR received by sun leaves over LAI layers
715                                                                   !! @tex ($\mu mol m^{-2} s^{-1}$) @endtex
716    REAL(r_std),DIMENSION(kjpindex,nlai+1)   :: PARshtab           !! PAR received by shaded leaves over LAI layers
717                                                                   !! @tex ($\mu mol m^{-2} s^{-1}$) @endtex
718    REAL(r_std),DIMENSION(kjpindex)          :: PARdf              !! Diffuse photosynthetic active radiation
719                                                                   !! @tex ($\mu mol m^{-2} s^{-1}$) @endtex
720    REAL(r_std),DIMENSION(kjpindex)          :: PARdr              !! Direct photosynthetic active radiation
721                                                                   !! @tex ($\mu mol m^{-2} s^{-1}$) @endtex
722    REAL(r_std),DIMENSION(kjpindex)          :: Trans              !! Atmospheric Transmissivity (unitless)
723
724!_ ================================================================================================================================
725        fco2 = 0.
726        fco2_wshort = 0.
727        fco2_wlong = 0.
728        Fdf(:) = 0.
729        PAR(:) = 0. 
730        PARsun(:,:) = 0. 
731        PARsh(:,:) = 0. 
732        laisun(:,:) = 0. 
733        laish(:,:) = 0. 
734        CRF(:,:) = 0.               
735        Trans(:) = 0.           
736        PARdf(:) = 0.           
737        PARdr(:) = 0.           
738        PARsuntab(:,:) = 0.       
739        PARshtab(:,:) = 0.       
740   
741
742    !! 1. Canopy radiative transfer model
743
744    !! Canopy radiative transfer model: takes into account light extinction through canopy
745    !! First need to calculate diffuse and direct radiation
746    !! Based on Andrew Friend radiative model (Global Ecology & Biogeography, 2001)
747    !! And Spitters et al. (Agricultural and Forest Meteorology, 1986)
748       
749    IF ( ok_radcanopy ) THEN
750
751       DO ji = 1, kjpindex
752          IF (coszang(ji) .GT. zero) THEN
753             !! 1.1 Extra-terrestrial solar irradiance at a plan parallel to Earh's surface
754             So(ji) = Sct*( un + 0.033*COS(360.*pi/180.*julian_diff/365.))*coszang(ji)
755             !! 1.2 Atmospheric transmissivity
756             Trans(ji) = swdown(ji)/So(ji)
757             !! 1.3 Empirical calculation of fraction diffuse from transmission based on Spitters et al. (1986)
758             Rfrac(ji) = 0.847 - 1.61*coszang(ji) + 1.04*(coszang(ji)**2.)
759             Kfrac(ji) = (1.47 - Rfrac(ji))/1.66     
760             IF (Trans(ji) .LE. 0.22) THEN
761                Fdf(ji) = un
762             ELSE IF (Trans(ji) .LE. 0.35) THEN
763                Fdf(ji) = un - 6.4*((Trans(ji) - 0.22)**2.) 
764             ELSE IF (Trans(ji) .LE. Kfrac(ji)) THEN
765                Fdf(ji) = 1.47 - 1.66*Trans(ji)
766             ELSE
767                Fdf(ji) = Rfrac(ji)
768             END IF
769             !! 1.4 Direct and diffuse sw radiation in W.m^{-2}
770             swdf(ji) = swdown(ji)*Fdf(ji)
771             swdr(ji) = swdown(ji)*(un-Fdf(ji))
772          ELSE
773             swdf(ji) = zero
774             swdr(ji) = zero
775          END IF
776
777          !! 1.5 PAR diffuse and direct in umol/m^2/s
778          PARdf(ji) = swdf(ji) * W_to_mol * RG_to_PAR
779          PARdr(ji) = swdr(ji) * W_to_mol * RG_to_PAR 
780       END DO
781
782       !! 1.6 Calculation of lai, parscat, parsh and parsun, laisun and laish !!?? define the terms
783       !! Based on Guenther et al. (JGR, 1995) and Norman (1982)
784       ! One-layer canopy model or multi-layer canopy model
785       IF (ok_multilayer) THEN 
786
787
788          ! Calculation PER LAYER
789          DO jl = nlai+1, 1, -1
790            laitab(jl) = laimax*(EXP(lai_level_depth*(jl-1) - un)/(EXP(lai_level_depth*nlai) - un))
791
792         !introduction of the Spitter way to calculate radiation over the levels !!!!!!!
793             DO ji = 1, kjpindex
794                kdf = cluster*0.8*SQRT((1 - sigma))
795                IF (ABS(ACOS(coszang(ji))) .LT. pi/2. .AND. coszang(ji) .NE. zero) THEN
796                   ! Coefficients calculation:
797                   kbl = cluster*0.5/ABS(coszang(ji))
798                   rho = ((1-SQRT((1 - sigma)))/(1+SQRT((1 - sigma))))*(2/(1+1.6*ABS(coszang(ji))))
799
800                   PARnotscat(ji,jl) = (1 - sigma)*PARdr(ji)*kbl*EXP(-SQRT((1 - sigma))*kbl*laitab(jl))
801                   PARabsdir(ji,jl) = (1 - rho)*SQRT((1 - sigma))*PARdr(ji)*kbl*EXP(-SQRT((1 - sigma))*kbl*laitab(jl))
802                   PARabsdiff(ji,jl) = (1 - rho)*PARdf(ji)*kdf*EXP(-kdf*laitab(jl))
803                   PARshtab(ji,jl) = (PARabsdiff(ji,jl) + (PARabsdir(ji,jl) - PARnotscat(ji,jl)))/(1 - sigma)
804                   PARsuntab(ji,jl) = PARshtab(ji,jl) + (1-sigma)*kbl*PARdr(ji)/(1 - sigma) 
805
806                   !correction using the equation (4) in Bodin et al 2012 and (7) or (8) in Spitter et al 1986
807                   !using the extinction coefficient kbl = 0.5/coszang and not only 0.5
808                   IF (jl .NE. nlai+1) THEN
809                      laisuntabdep(ji,jl) =(laitab(jl+1)-laitab(jl))*EXP(-kbl*laitab(jl))
810                      laishtabdep(ji,jl) =(laitab(jl+1)-laitab(jl))*(1.-EXP(-kbl*laitab(jl)))
811                   ENDIF
812
813                ELSE
814
815                   PARshtab(ji,jl) = PARdf(ji)*kdf*EXP(-kdf*laitab(jl))
816                   PARsuntab(ji,jl) = 0.
817
818                   IF (jl .NE. nlai+1) THEN
819                      laisuntabdep(ji,jl) = 0.
820                      laishtabdep(ji,jl) = laitab(jl+1)-laitab(jl)
821
822                   ENDIF 
823                END IF
824             END DO
825          END DO
826
827
828
829       ! introduction of the Spitter way to calculate radiation over the levels !!!!!!!
830       ELSE
831          ! Calculation FOR one layer
832          DO jv = 1, nvm
833             DO ji = 1, kjpindex
834                IF (lai(ji,jv) .LE. lai_threshold) THEN
835                   PARscat(ji,jv) = 0.07*PARdr(ji)*(1.1 - 0.1*lai(ji,jv))*exp(-coszang(ji))
836                ELSE
837                   PARscat(ji,jv) = zero
838                END IF
839
840                IF (coszang(ji) .NE. zero ) THEN
841                   PARsh(ji,jv) = PARdf(ji)*exp(-0.5*((lai(ji,jv))**0.7)) + PARscat(ji,jv)
842                   PARsun(ji,jv) = PARdr(ji)*COS(60.*pi/180.)/coszang(ji) + PARsh(ji,jv)
843                ELSE
844                   PARsh(ji,jv) = PARdf(ji)*exp(-0.5*(lai(ji,jv)**0.7)) + PARscat(ji,jv)
845                   PARsun(ji,jv) = zero 
846                END IF
847                IF (ABS(ACOS(coszang(ji))) .LT. pi/2. .AND. ABS(coszang(ji)) .GT. min_sechiba) THEN 
848                   ! calculation as in Lathiere (2005) = with correction removing lai in Guenther (1995)
849                   laisun(ji,jv) = (un - exp(-0.5*lai(ji,jv)/(coszang(ji))))*coszang(ji)/COS(60.*pi/180.)
850                   laish(ji,jv) = lai(ji,jv) - laisun(ji,jv)
851                ELSE
852                   laisun(ji,jv) = zero
853                   laish(ji,jv) = lai(ji,jv)
854                END IF
855             END DO
856          END DO
857       ENDIF
858    END IF
859
860
861    !! 2. Calculation of non-PFT dependant parameters used for VOC emissions
862    DO ji = 1, kjpindex ! (loop over # pixels)
863       !! 2.1 Calculation of Tleaf (based on Lathiere, 2005)
864
865
866       tleaf(ji) = temp_air(ji)
867
868       !! 2.2 Isoprene emission dependency - with no PARsun/PARshaded partitioning - Guenther et al. (1995) and Lathiere (2005)
869       !> @codeinc $$?? ecrire les equation en latex ?
870       exp_1(ji) = exp( (CT1 * ( tleaf(ji) - TS )) / (RR*TS*tleaf(ji)) )
871       exp_2(ji) = exp( (CT2 *( tleaf(ji) - TM )) / (RR*TS*tleaf(ji)) )
872       PAR(ji)   = swdown(ji) * W_to_mol * RG_to_PAR        ! from W/m^2 to umol photons/m^2/s and half of sw for PAR
873       Ct_iso(ji)    = exp_1(ji)/(un + exp_2(ji))            ! temperature dependance 
874       Cl_iso(ji)    = alpha_*CL1*PAR(ji)/sqrt(un + (alpha_**2) * (PAR(ji)**2) ) ! light dependance
875       !> @endcodeinc
876 
877       !! 2.3 Monoterpene and oxy VOB emission dependency to Temperature
878       !!     light independant fraction
879       !> @codeinc
880       !Ct_mono(ji) = exp(beta*(tleaf(ji) - TS))  ! Old method
881       Ct_mono(ji) = exp(beta_mono*(tleaf(ji) - TS))
882       Ct_sesq(ji) = exp(beta_sesq*(tleaf(ji) - TS))
883       Ct_meth(ji) = exp(beta_meth*(tleaf(ji) - TS))
884       Ct_acet(ji) = exp(beta_acet*(tleaf(ji) - TS))
885       Ct_oxyVOC(ji) = exp(beta_oxyVOC*(tleaf(ji) - TS))     
886       !> @endcodeinc
887       !! 2.4 MBO biogenic emissions dependency, only from PFT7 and PFT4 for location of vegetation emitter
888       ! but in fact MBO fluxes only in America (ponderosa and lodgepole pines only found in these areas)
889       !> @codeinc
890       Xvar(ji) = ((un/312.3) - (un/tleaf(ji)))/RR
891       !> @endcodeinc
892       !! 2.4.1 temperature dependency
893       !> @codeinc
894       Ct_MBO(ji)    = (1.52*209000.0*exp(67000.0*Xvar(ji)))/(209000.0 - 67000.0*(un - exp(209000.0*Xvar(ji))))
895       !> @endcodeinc
896       !! 2.4.2 light dependency
897       Cl_MBO(ji)    = (0.0011*1.44*PAR(ji))/(sqrt(un + (0.0011**2)*(PAR(ji)**2)))
898       !! 2.5 NO biogenic emissions given in ngN/m^2/s, emission factor in ngN/m^2/s too
899       !! calculation of temperature used for NO soil emissions
900       t_no(ji) = ptnlev1(ji) - ZeroCelsius  !!temp must be in celsius to calculate no emissions
901       !! 2.6 calculation of non-woody veget_max fraction
902       IF (ok_cropsfertil_NOx) THEN
903          veget_max_nowoody(ji) = zero
904          DO jv = 1,nvm
905             IF ( (jv /= ibare_sechiba) .AND. .NOT.(is_tree(jv)) ) THEN
906                veget_max_nowoody(ji) = veget_max_nowoody(ji) + veget_max(ji,jv)
907             ENDIF
908          ENDDO
909       END IF
910    END DO ! (loop over # pixels)
911
912    !! 2bis. Calculation of CO2 function for inhibition effect on isoprene
913    ! 2 approaches can be used: either Possell et al. (2005) or Wilkinson et al. (2006)
914
915!! 19/04/2010 and then implemented in version revised by Nicolas Vuichard, 08042014
916!! Impact of atmospheric CO2 on isoprene emissions
917!! Can be activated or not
918!! If considered, can use either Possell 2005 or Wilkinson 2009 parameterisation
919!! This is used to rescale the emission factor, considered to be measured at 350 ppm of CO2
920!! to the CO2 conditions of the run
921
922IF ( ok_co2bvoc_poss ) THEN
923   WRITE(numout,*) 'CO2 impact on isoprene: Possell calculation'
924
925   !! Possell function needs to be normalized (experiments at 400 ppm and EF before 1995)
926   !! Normalized at 350 ppm
927   fco2_ctrl = (-0.0123+(441.4795/350.)+(-1282.65/(350.**2)))
928
929   !! 2 tests: using the canopy (atmospheric) CO2 'ccanopy'
930   !! or the intercellular CO2 over nlai 'cim'
931   !! with cim = ccanopy*0.667
932   !! in the end I go for ccanopy for the Possell function since too much differences
933   !! when using cim and also the function has been derived based on atmospheric CO2
934   DO ji = 1, kjpindex
935
936      fco2(ji,:) = (-0.0123+(441.4795/ccanopy(ji))+(-1282.65/(ccanopy(ji)*ccanopy(ji))))/fco2_ctrl
937
938   END DO
939ELSE IF ( ok_co2bvoc_wilk ) THEN
940   WRITE(numout,*) 'CO2 impact on isoprene: Wilkinson calculation'
941
942   !! In the Wilkinson function, 2 impacts are considered:
943   !! -short-term impact for CO2 variation during a single day (seconds/minutes)
944   !! -long-term impact for CO2 variation during leaf-growth (weeks/month)
945
946
947   !! Long-term parameters
948   !! Constant
949   Ismax_long = 1.344
950   h_long = 1.4614
951   Cstar_long = 585.
952   !! Short-term parameters
953   !! They have to be calculated based on atmospheric CO2
954   !! 10/05/2010
955   !! For atmospheric CO2 lower than 400 ppm or higher than 1200 ppm
956   !! (min and max CO2 level tested for short-term effect in Wilkinson et al. 2009)
957   !! we use the parameters calculated at 400/1200 ppm. For intermediate CO2 concentration,
958   !! parameters are calculated.
959   !! Linear interpolation
960
961   DO ji = 1, kjpindex
962
963      IF (ccanopy(ji) .LE. 400.) THEN
964
965         Ismax_short(ji) = 1.072
966         h_short(ji) = 1.7
967         Cstar_short(ji) = 1218.
968
969      ELSE IF (ccanopy(ji) .EQ. 600.) THEN
970
971         Ismax_short(ji) = 1.036
972         h_short(ji) = 2.0125
973         Cstar_short(ji) = 1150.
974
975      ELSE IF (ccanopy(ji) .EQ. 800.) THEN
976
977         Ismax_short(ji) = 1.046
978         h_short(ji) = 1.5380
979         Cstar_short(ji) = 2025.
980
981      ELSE IF (ccanopy(ji) .GE. 1200.) THEN
982
983         Ismax_short(ji) = 1.014
984         h_short(ji) = 2.8610
985         Cstar_short(ji) = 1525.
986
987
988      ELSE IF ((ccanopy(ji) .GT. 400.) .AND. (ccanopy(ji) .LT. 600.)) THEN
989
990         Ismax_short(ji) = 1.036 + (ccanopy(ji)-600.)*(1.036-1.072)/(600.-400.)
991         h_short(ji) = 2.0125 + (ccanopy(ji)-600.)*(2.0125-1.7)/(600.-400.)
992         Cstar_short(ji) =  1150. + (ccanopy(ji)-600.)*(1150.-1218.)/(600.-400.)
993
994      ELSE IF ((ccanopy(ji) .GT. 600.) .AND. (ccanopy(ji) .LT. 800.)) THEN
995
996         Ismax_short(ji) = 1.046 + (ccanopy(ji)-800.)*(1.046-1.036)/(800.-600.)
997         h_short(ji) = 1.5380 + (ccanopy(ji)-800.)*(1.5380-2.0125)/(800.-600.)
998         Cstar_short(ji) = 2025. + (ccanopy(ji)-800.)*(2025.-1150.)/(800.-600.)
999
1000      ELSE IF ((ccanopy(ji) .GT. 800.) .AND. (ccanopy(ji) .LT. 1200.)) THEN
1001
1002        Ismax_short(ji) = 1.014 + (ccanopy(ji)-1200.)*(1.014-1.046)/(1200.-800.)
1003        h_short(ji) = 2.8610 + (ccanopy(ji)-1200.)*(2.8610-1.5380)/(1200.-800.)
1004        Cstar_short(ji) = 1525. + (ccanopy(ji)-1200.)*(1525.-2025.)/(1200.-800.)
1005
1006
1007      END IF
1008
1009   END DO
1010
1011   WRITE(numout,*) '***Wilkinson BVOC-CO2 function: parameters***'
1012   WRITE(numout,*) 'Ismax_long: ', Ismax_long
1013   WRITE(numout,*) 'h_long: ', h_long
1014   WRITE(numout,*) 'Cstar_long: ', Cstar_long
1015   WRITE(numout,*) 'Ismax_short: ', MAXVAL(Ismax_short(:)) , MINVAL(Ismax_short(:))
1016   WRITE(numout,*) 'h_short: ', MAXVAL(h_short(:)) , MINVAL(h_short(:))
1017   WRITE(numout,*) 'Cstar_short: ', MAXVAL(Cstar_short(:)) , MINVAL(Cstar_short(:))
1018   WRITE(numout,*) '******'
1019
1020   DO ji = 1, kjpindex
1021      fco2_wlong(ji) = (Ismax_long-((Ismax_long*((0.667*ccanopy(ji))**h_long))/&
1022                     & ((Cstar_long**h_long)+(0.667*ccanopy(ji))**h_long)))/1.06566
1023      DO jv = 1, nvm
1024         fco2_wshort(ji,jv) = (Ismax_short(ji)-((Ismax_short(ji)*((cim(ji,jv))**h_short(ji)))/&
1025                            & ((Cstar_short(ji)**h_short(ji))+(cim(ji,jv))**h_short(ji))))/1.010803
1026      END DO
1027   END DO
1028
1029   DO ji = 1, kjpindex
1030      DO jv = 1, nvm
1031         fco2(ji,jv) = fco2_wshort(ji,jv)*fco2_wlong(ji)
1032      END DO
1033   END DO
1034
1035ELSE
1036      WRITE(numout,*) 'CO2 impact on isoprene not considered'
1037      fco2(:,:) = 1.
1038END IF
1039
1040
1041    !! 3. Calculation of PFT dependant parameters and
1042    ! Calculation of VOC emissions flux
1043
1044    Eff_age_iso(:,:) = zero
1045    Eff_age_meth(:,:) = zero
1046
1047
1048    DO jv = 1, nvm ! loop over the PDFs
1049       DO ji = 1, kjpindex ! loop over the grid cell
1050          ! 6-Calculation of Leaf Age Function (Lathiere 2005)
1051          IF ( ok_leafage ) THEN
1052             DO jf = 1, nleafages
1053                !> @codeinc
1054                Eff_age_iso(ji,jv) = Eff_age_iso(ji,jv) + frac_age(ji,jv,jf)*iso_activity(jf)
1055                Eff_age_meth(ji,jv) = Eff_age_meth(ji,jv) + frac_age(ji,jv,jf)*methanol_activity(jf)
1056                !> @endcodeinc
1057             END DO
1058             !> @codeinc
1059             Eff_age_VOC(ji,jv) = un
1060             !> @endcodeinc
1061          ELSE
1062             Eff_age_iso(ji,jv) = un
1063             Eff_age_meth(ji,jv) = un
1064             Eff_age_VOC(ji,jv) = un
1065          END IF
1066          !! 5. Calculation of foliar density
1067          IF ( sla(jv) .eq. zero ) THEN
1068             fol_dens(ji,jv) = zero
1069          ELSE
1070             ! 2 factor for conversion from gC to gDM
1071             fol_dens(ji,jv) = 2 * lai(ji,jv)/sla(jv)
1072          ENDIF
1073          !! 6. Calculation of VOC emissions from vegetation
1074          IF ( ok_radcanopy ) THEN
1075             ! if multi-layer canopy model
1076             IF (ok_multilayer) THEN
1077
1078                laisun(ji,jv) = zero
1079                laish(ji,jv) = zero
1080                GAMMA_iso_m  = zero
1081                flx_iso(ji,jv) = zero
1082                flx_mono(ji,jv) = zero
1083                flx_apinen(ji,jv) = zero
1084                flx_bpinen(ji,jv) = zero
1085                flx_limonen(ji,jv) = zero
1086                flx_myrcen(ji,jv) =  zero
1087                flx_sabinen(ji,jv) =  zero
1088                flx_camphen(ji,jv) = zero
1089                flx_3caren(ji,jv) = zero
1090                flx_tbocimen(ji,jv) = zero
1091                flx_othermono(ji,jv) = zero
1092                flx_sesquiter(ji,jv) =  zero
1093                flx_methanol(ji,jv) = zero
1094                flx_acetone(ji,jv) =  zero
1095                flx_acetal(ji,jv) = zero
1096                flx_formal(ji,jv) = zero
1097                flx_acetic(ji,jv) = zero
1098                flx_formic(ji,jv) = zero
1099                ! loop over the NLAI canopy layers
1100                DO jl = 1, nlai
1101                   IF ((laitab(jl) .LE. lai(ji,jv)).AND.(lai(ji,jv).NE.zero)) THEN
1102                      !sunlit vegetation
1103                      Clsun_iso_tab   = alpha_*CL1*PARsuntab(ji,jl)/sqrt(un + (alpha_**2) * (PARsuntab(ji,jl)**2) )
1104                      ! shaded vegetation
1105                      Clsh_iso_tab    = alpha_*CL1*PARshtab(ji,jl)/sqrt(un + (alpha_**2) * (PARshtab(ji,jl)**2) ) 
1106                      flx_iso(ji,jv) = flx_iso(ji,jv) + (laisuntabdep(ji,jl)*Clsun_iso_tab+ &
1107                           & laishtabdep(ji,jl)*Clsh_iso_tab)* &
1108                           & fol_dens(ji,jv)/lai(ji,jv)*Ct_iso(ji)*em_factor_isoprene(jv)* &
1109                           & Eff_age_iso(ji,jv)*fco2(ji,jv)*1e-9/one_hour
1110
1111                      GAMMA_iso_m = GAMMA_iso_m + (laisuntabdep(ji,jl)*Clsun_iso_tab+ &
1112                           & laishtabdep(ji,jl)*Clsh_iso_tab)* &
1113                           & fol_dens(ji,jv)/lai(ji,jv)*Ct_iso(ji)*1e-9/one_hour
1114
1115                      laisun(ji,jv) = laisun(ji,jv) + laisuntabdep(ji,jl)
1116                      laish(ji,jv)  = laish(ji,jv) + laishtabdep(ji,jl)
1117                   END IF
1118                END DO
1119
1120                !! 6.1 Calculation of monoterpene biogenic emissions
1121                flx_mono(ji,jv) = ((1-LDF_mono)*Ct_mono(ji)*1e-9/one_hour*fol_dens(ji,jv) + LDF_mono*GAMMA_iso_m)* &
1122                     & em_factor_monoterpene(jv)*Eff_age_VOC(ji,jv) 
1123                !! 6.12 Calculation of sesquiterpenes biogenic emission
1124                flx_sesquiter(ji,jv) = ((1-LDF_sesq)*Ct_sesq(ji)*1e-9/one_hour*fol_dens(ji,jv) +LDF_sesq*GAMMA_iso_m)* &
1125                     & em_factor_sesquiterp(jv)*Eff_age_VOC(ji,jv)
1126                !! 6.13 Calculation of methanol biogenic emissions
1127                flx_methanol(ji,jv) = ((1-LDF_meth)*Ct_meth(ji)*1e-9/one_hour*fol_dens(ji,jv) +LDF_meth*GAMMA_iso_m)* &
1128                     & em_factor_methanol(jv)*Eff_age_meth(ji,jv)
1129                !! 6.14 Calculation of acetone biogenic emissions
1130                flx_acetone(ji,jv) = ((1-LDF_acet)*Ct_acet(ji)*1e-9/one_hour*fol_dens(ji,jv) +LDF_acet*GAMMA_iso_m)* &
1131                     & em_factor_acetone(jv)*Eff_age_VOC(ji,jv)
1132                !! 6.14 Calculation of acetaldehyde biogenic emissions
1133                flx_acetal(ji,jv) = ((1-LDF_meth)*Ct_meth(ji)*1e-9/one_hour*fol_dens(ji,jv) +LDF_meth*GAMMA_iso_m)* &
1134                     & em_factor_acetal(jv)*Eff_age_VOC(ji,jv)
1135                !! 6.16 Calculation of formaldehyde biogenic emissions
1136                flx_formal(ji,jv) = ((1-LDF_meth)*Ct_meth(ji)*1e-9/one_hour*fol_dens(ji,jv) +LDF_meth*GAMMA_iso_m)* &
1137                     & em_factor_formal(jv)*Eff_age_VOC(ji,jv)
1138                !! 6.17 Calculation of acetic acid biogenic emissions
1139                flx_acetic(ji,jv) = ((1-LDF_meth)*Ct_meth(ji)*1e-9/one_hour*fol_dens(ji,jv) +LDF_meth*GAMMA_iso_m)* &
1140                     & em_factor_acetic(jv)*Eff_age_VOC(ji,jv)
1141                !! 6.18 Calculation of formic acid biogenic emissions
1142                flx_formic(ji,jv) = ((1-LDF_meth)*Ct_meth(ji)*1e-9/one_hour*fol_dens(ji,jv) +LDF_meth*GAMMA_iso_m)* &
1143                     & em_factor_formic(jv)*Eff_age_VOC(ji,jv)
1144
1145
1146                !! 6.3 Calculation of alfa pinene biogenic emission
1147                flx_apinen(ji,jv) = em_factor_apinene(jv)*flx_mono(ji,jv) 
1148                !! 6.4 Calculation of beta pinene biogenic emission
1149                flx_bpinen(ji,jv) = em_factor_bpinene(jv)*flx_mono(ji,jv) 
1150                !! 6.5 Calculation of limonene biogenic emission
1151                flx_limonen(ji,jv) = em_factor_limonene(jv)*flx_mono(ji,jv) 
1152                !! 6.6 Calculation of myrcene biogenic emission !!
1153                flx_myrcen(ji,jv) = em_factor_myrcene(jv)*flx_mono(ji,jv) 
1154                !! 6.7 Calculation of sabinene biogenic emission
1155                flx_sabinen(ji,jv) = em_factor_sabinene(jv)*flx_mono(ji,jv) 
1156                !! 6.8 Calculation of camphene biogenic emission
1157                flx_camphen(ji,jv) = em_factor_camphene(jv)*flx_mono(ji,jv) 
1158                !! 6.9 Calculation of 3-carene biogenic emission
1159                flx_3caren(ji,jv) = em_factor_3carene(jv)*flx_mono(ji,jv) 
1160                !! 6.10 Calculation of t-beta-ocimene biogenic emission
1161                flx_tbocimen(ji,jv) = em_factor_tbocimene(jv)*flx_mono(ji,jv) 
1162                !! 6.11 Calculation of other monoterpenes biogenic emission
1163                flx_othermono(ji,jv) = em_factor_othermonot(jv)*flx_mono(ji,jv) 
1164
1165                ! if mono-layer canopy model
1166             ELSE
1167                !sunlit vegetation
1168                Clsun_iso(ji,jv)   = alpha_*CL1*PARsun(ji,jv)/sqrt(un + (alpha_**2) * (PARsun(ji,jv)**2) )
1169                ! shaded vegetation     
1170                Clsh_iso(ji,jv)    = alpha_*CL1*PARsh(ji,jv)/sqrt(un + (alpha_**2) * (PARsh(ji,jv)**2) )       
1171                IF (lai(ji,jv) .NE. zero) THEN
1172                   !! 6.1 Calculation of isoprene biogenic emissions
1173                   GAMMA_iso = (laisun(ji,jv)*Clsun_iso(ji,jv) + laish(ji,jv)*Clsh_iso(ji,jv))/lai(ji,jv)*Ct_iso(ji)
1174                   flx_iso(ji,jv) = GAMMA_iso*fol_dens(ji,jv)*em_factor_isoprene(jv)*Eff_age_iso(ji,jv)*fco2(ji,jv)*1e-9/one_hour
1175                   !! 6.2 Calculation of monoterpene biogenic emissions
1176                   flx_mono(ji,jv) = ((1-LDF_mono)*Ct_mono(ji)+LDF_mono*GAMMA_iso)*fol_dens(ji,jv)* &
1177                        & em_factor_monoterpene(jv)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1178                   !! 6.3 Calculation of alfa pinene biogenic emission
1179                   flx_apinen(ji,jv) = em_factor_apinene(jv)*flx_mono(ji,jv)
1180                   !! 6.4 Calculation of beta pinene biogenic emission
1181                   flx_bpinen(ji,jv) = em_factor_bpinene(jv)*flx_mono(ji,jv)
1182                   !! 6.5 Calculation of limonene biogenic emission
1183                   flx_limonen(ji,jv) = em_factor_limonene(jv)*flx_mono(ji,jv)
1184                   !! 6.6 Calculation of myrcene biogenic emission
1185                   flx_myrcen(ji,jv) = em_factor_myrcene(jv)*flx_mono(ji,jv)
1186                   !! 6.7 Calculation of sabinene biogenic emission
1187                   flx_sabinen(ji,jv) = em_factor_sabinene(jv)*flx_mono(ji,jv)
1188                   !! 6.8 Calculation of camphene biogenic emission
1189                   flx_camphen(ji,jv) = em_factor_camphene(jv)*flx_mono(ji,jv)
1190                   !! 6.9 Calculation of 3-carene biogenic emission
1191                   flx_3caren(ji,jv) = em_factor_3carene(jv)*flx_mono(ji,jv)
1192                   !! 6.10 Calculation of t-beta-ocimene biogenic emission
1193                   flx_tbocimen(ji,jv) = em_factor_tbocimene(jv)*flx_mono(ji,jv)
1194                   !! 6.11 Calculation of other monoterpenes biogenic emission
1195                   flx_othermono(ji,jv) = em_factor_othermonot(jv)*flx_mono(ji,jv)
1196                   !! 6.12 Calculation of sesquiterpenes biogenic emission
1197                   flx_sesquiter(ji,jv) = ((1-LDF_sesq)*Ct_sesq(ji)+LDF_sesq*GAMMA_iso)*fol_dens(ji,jv)* &
1198                        & em_factor_sesquiterp(jv)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1199                   !! 6.13 Calculation of methanol biogenic emissions
1200                   flx_methanol(ji,jv) = ((1-LDF_meth)*Ct_meth(ji)+LDF_meth*GAMMA_iso)*fol_dens(ji,jv)* &
1201                        & em_factor_methanol(jv)*Eff_age_meth(ji,jv)*1e-9/one_hour
1202                   !! 6.14 Calculation of acetone biogenic emissions
1203                   flx_acetone(ji,jv) = ((1-LDF_acet)*Ct_acet(ji)+LDF_acet*GAMMA_iso)*fol_dens(ji,jv)* &
1204                        & em_factor_acetone(jv)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1205                   !! 6.15 Calculation of acetaldehyde biogenic emissions
1206                   flx_acetal(ji,jv) = ((1-LDF_meth)*Ct_meth(ji)+LDF_meth*GAMMA_iso)*fol_dens(ji,jv)* &
1207                        & em_factor_acetal(jv)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1208                   !! 6.16 Calculation of formaldehyde biogenic emissions
1209                   flx_formal(ji,jv) = ((1-LDF_meth)*Ct_meth(ji)+LDF_meth*GAMMA_iso)*fol_dens(ji,jv)* &
1210                        & em_factor_formal(jv)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1211                   !! 6.17 Calculation of acetic acid biogenic emissions
1212                   flx_acetic(ji,jv) = ((1-LDF_meth)*Ct_meth(ji)+LDF_meth*GAMMA_iso)*fol_dens(ji,jv)* &
1213                        & em_factor_acetic(jv)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1214                   !! 6.18 Calculation of formic acid biogenic emissions
1215                   flx_formic(ji,jv) = ((1-LDF_meth)*Ct_meth(ji)+LDF_meth*GAMMA_iso)*fol_dens(ji,jv)* &
1216                        & em_factor_formic(jv)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1217 
1218                ELSE
1219                   !
1220                   flx_iso(ji,jv) = zero
1221                   flx_mono(ji,jv) = zero
1222                   flx_apinen(ji,jv) = zero 
1223                   flx_bpinen(ji,jv) = zero 
1224                   flx_limonen(ji,jv) = zero 
1225                   flx_myrcen(ji,jv) =  zero
1226                   flx_sabinen(ji,jv) =  zero 
1227                   flx_camphen(ji,jv) = zero 
1228                   flx_3caren(ji,jv) = zero 
1229                   flx_tbocimen(ji,jv) = zero
1230                   flx_othermono(ji,jv) = zero 
1231                   flx_sesquiter(ji,jv) =  zero 
1232                   flx_methanol(ji,jv) = zero
1233                   flx_acetone(ji,jv) =  zero 
1234                   flx_acetal(ji,jv) = zero
1235                   flx_formal(ji,jv) = zero 
1236                   flx_acetic(ji,jv) = zero 
1237                   flx_formic(ji,jv) = zero 
1238                END IF
1239             END IF
1240             ! if no light extinction due to vegetation 
1241          ELSE
1242             !! Isoprene emissions - general equation
1243             flx_iso(ji,jv) = fol_dens(ji,jv)*Ct_iso(ji)*Cl_iso(ji)*Eff_age_iso(ji,jv)*fco2(ji,jv)* &
1244                  em_factor_isoprene(jv)*1e-9/one_hour
1245             !! 6.2 Calculation of monoterpene biogenic emissions
1246             Ylt_mono(ji) = ((1-LDF_mono)*Ct_mono(ji)+LDF_mono*Ct_iso(ji)*Cl_iso(ji)) 
1247             flx_mono(ji,jv) = fol_dens(ji,jv)*em_factor_monoterpene(jv)*Ylt_mono(ji)*Eff_age_VOC(ji,jv)*&
1248                  1e-9/one_hour
1249             !! 6.3 Calculation of alfa pinene biogenic emission
1250             flx_apinen(ji,jv) = em_factor_apinene(jv)*flx_mono(ji,jv) 
1251             !! 6.4 Calculation of beta pinene biogenic emission
1252             flx_bpinen(ji,jv) = em_factor_bpinene(jv)*flx_mono(ji,jv)                       
1253             !! 6.5 Calculation of limonene biogenic emission
1254             flx_limonen(ji,jv) = em_factor_limonene(jv)*flx_mono(ji,jv)                     
1255             !! 6.6 Calculation of myrcene biogenic emission
1256             flx_myrcen(ji,jv) = em_factor_myrcene(jv)*flx_mono(ji,jv)                       
1257             !! 6.7 Calculation of sabinene biogenic emission
1258             flx_sabinen(ji,jv) = em_factor_sabinene(jv)*flx_mono(ji,jv)           
1259             !! 6.8 Calculation of camphene biogenic emission
1260             flx_camphen(ji,jv) = em_factor_camphene(jv)*flx_mono(ji,jv)
1261             !! 6.9 Calculation of 3-carene biogenic emission
1262             flx_3caren(ji,jv) = em_factor_3carene(jv)*flx_mono(ji,jv)                       
1263             !! 6.10 Calculation of t-beta-ocimene biogenic emission
1264             flx_tbocimen(ji,jv) = em_factor_tbocimene(jv)*flx_mono(ji,jv)                     
1265             !! 6.11 Calculation of other monoterpenes biogenic emission
1266             flx_othermono(ji,jv) = em_factor_othermonot(jv)*flx_mono(ji,jv)                   
1267             !! 6.12 Calculation of sesquiterpenes biogenic emission
1268             Ylt_sesq(ji) = ((1-LDF_sesq)*Ct_sesq(ji)+LDF_sesq*Ct_iso(ji)*Cl_iso(ji))
1269             flx_sesquiter(ji,jv) = fol_dens(ji,jv)*em_factor_sesquiterp(jv)*Ylt_sesq(ji)*Eff_age_VOC(ji,jv)*1e-9/one_hour   
1270             !! 6.16 Calculation of methanol biogenic emissions
1271             Ylt_meth(ji) = ((1-LDF_meth)*Ct_meth(ji)+LDF_meth*Ct_iso(ji)*Cl_iso(ji))
1272             flx_methanol(ji,jv) = fol_dens(ji,jv)*em_factor_methanol(jv)*Ylt_meth(ji)*Eff_age_meth(ji,jv)*1e-9/one_hour
1273             !! 6.17 Calculation of acetone biogenic emissions
1274             Ylt_acet(ji) = ((1-LDF_acet)*Ct_acet(ji)+LDF_acet*Ct_iso(ji)*Cl_iso(ji))
1275             flx_acetone(ji,jv) = fol_dens(ji,jv)*em_factor_acetone(jv)*Ylt_acet(ji)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1276             !! 6.18 Calculation of acetaldehyde biogenic emissions
1277             flx_acetal(ji,jv) = fol_dens(ji,jv)*em_factor_acetal(jv)*Ylt_meth(ji)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1278             !! 6.19 Calculation of formaldehyde biogenic emissions
1279             flx_formal(ji,jv) = fol_dens(ji,jv)*em_factor_formal(jv)*Ylt_meth(ji)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1280             !! 6.20 Calculation of acetic acid biogenic emissions
1281             flx_acetic(ji,jv) = fol_dens(ji,jv)*em_factor_acetic(jv)*Ylt_meth(ji)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1282             !! 6.21 Calculation of formic acid biogenic emissions
1283             flx_formic(ji,jv) = fol_dens(ji,jv)*em_factor_formic(jv)*Ylt_meth(ji)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1284
1285          END IF
1286
1287          !! 6.22 Calculation of ORVOC biogenic emissions
1288          !! Other Reactive Volatile Organic Compounds
1289          !> @codeinc
1290          flx_ORVOC(ji,jv) = fol_dens(ji,jv)*em_factor_ORVOC(jv)*Ct_mono(ji)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1291          !> @endcodeinc
1292          !! 6.4 Calculation of OVOC biogenic emissions
1293          !! Other Volatile Organic Compounds
1294          flx_OVOC(ji,jv) = fol_dens(ji,jv)*em_factor_OVOC(jv)*Ct_mono(ji)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1295          !! 6.5 Calculation of MBO biogenic emissions
1296          !! 2-Methyl-3-Buten-2-ol
1297          IF(lalo(ji,1) .GE. 20. .AND. lalo(ji,2) .LE. -100) THEN
1298             flx_MBO(ji,jv) = fol_dens(ji,jv)*em_factor_MBO(jv)*Ct_MBO(ji)*Cl_MBO(ji)*Eff_age_VOC(ji,jv)*1e-9/one_hour
1299          ELSE
1300             flx_MBO(ji,jv) = zero
1301          END IF
1302       END DO
1303
1304    END DO
1305
1306
1307    !! 7. Calculation of NOx emissions from soils
1308    ! Based on Yienger & Levy (1995) and Lathiere (2005, chapter 3)
1309    DO ji = 1, kjpindex
1310       !! 7.1 Precipitation-related pulse function
1311       IF (ok_pulse_NOx) THEN
1312          ! if we are during a period where pulses are not allowed
1313          IF (ok_siesta(ji)) THEN
1314             ! if this period is not over
1315             IF (FLOOR(siestaday(ji)) .LE. siestalim(ji)) THEN
1316                siestaday(ji) = siestaday(ji) + (dt_sechiba/one_day)
1317                ! if this period is over
1318             ELSE
1319                ok_siesta(ji) = .FALSE.
1320                siestaday(ji) = zero
1321             END IF
1322          END IF
1323          ! if we are during a period where pulses are allowed
1324          IF ((.NOT. ok_siesta(ji)) .AND. (.NOT. allow_pulse(ji))) THEN
1325             IF (humrel(ji,1) .LT. 0.15) THEN
1326                ! if precip exceeds 1 mm/day over one time step => a pulse occurs
1327                IF(precip_rain(ji)/nbre_precip .GE. un/(one_day/dt_sechiba)) THEN
1328                   ! if precip is up to 5 mm/day => pulse length is 3 days
1329                   IF (precip_rain(ji)/nbre_precip .LT. 5./(one_day/dt_sechiba)) THEN
1330                      pulselim(ji) = 3.
1331                      ! if precip is up to 15 mm/day => pulse length is 7 days
1332                   ELSE IF (precip_rain(ji)/nbre_precip .LT. 15./(one_day/dt_sechiba)) THEN
1333                      pulselim(ji) = 7.
1334                      ! if precip is upper than 15 mm/day => pulse length is 14 days
1335                   ELSE IF (precip_rain(ji)/nbre_precip .GE. 15./(one_day/dt_sechiba)) THEN
1336                      pulselim(ji) = 14.
1337                   END IF
1338                   allow_pulse(ji)=.TRUE.
1339                   pulseday(ji) = un
1340                END IF
1341             END IF
1342          END IF
1343          ! if we were during a pulse period
1344          IF (allow_pulse(ji)) THEN
1345             ! if we are still during the pulse period
1346             ! 16/06/2010 We assume a (pulselim-1) days for the pulse length (NVui+Jlath)
1347             IF(FLOOR(pulseday(ji)) .LT. pulselim(ji)) THEN
1348                ! calculation of the pulse function
1349                IF (pulselim(ji).EQ.3) THEN
1350                   pulse(ji) = 11.19*exp(-0.805*pulseday(ji))
1351                ELSE IF (pulselim(ji).EQ.7) THEN
1352                   pulse(ji) = 14.68*exp(-0.384*pulseday(ji))
1353                ELSE IF (pulselim(ji).EQ.14) THEN
1354                   pulse(ji) = 18.46*exp(-0.208*pulseday(ji))
1355                END IF
1356                pulseday(ji) = pulseday(ji) + (dt_sechiba/one_day)
1357                ! if the pulse period is over
1358             ELSE
1359                ! pulse function is set to 1
1360                pulse(ji) = un
1361                allow_pulse(ji) = .FALSE.
1362                siestaday(ji) = un
1363                siestalim(ji) = pulselim(ji)
1364                ok_siesta(ji) = .TRUE. 
1365             END IF
1366          END IF
1367          ! no precipitation-related pulse function
1368       ELSE
1369          pulse(ji) = un
1370       END IF
1371    END DO
1372
1373    !! 7.2 Calculation of NO basal emissions including pulse effect
1374    DO jv = 1, nvm
1375       DO ji = 1, kjpindex
1376          !Tropical forests
1377          IF ( is_tropical(jv) .AND. is_evergreen(jv) ) THEN
1378             ! Wet soils
1379             IF (humrel(ji,1) .GT. 0.3) THEN
1380                flx_no_soil(ji,jv) = 2.6*pulse(ji)
1381                ! Dry soils
1382             ELSE
1383                flx_no_soil(ji,jv) = 8.6*pulse(ji)
1384             END IF
1385             !Else If agricultural lands OR Wet soils
1386          ELSE IF ( ( .NOT.(natural(jv)) ) .OR. ( humrel(ji,1) .GT. 0.3 ) ) THEN
1387             ! Calculation of NO emissions depending of Temperature
1388             IF (t_no(ji) .LT. zero) THEN
1389                flx_no_soil(ji,jv) = zero
1390             ELSE IF (t_no(ji) .LE. 10.) THEN
1391                flx_no_soil(ji,jv) = 0.28*em_factor_no_wet(jv)*t_no(ji)*pulse(ji)
1392             ELSE IF (t_no(ji) .LE. 30.) THEN
1393                flx_no_soil(ji,jv) = em_factor_no_wet(jv)*exp(0.103*t_no(ji))*pulse(ji)
1394             ELSE
1395                flx_no_soil(ji,jv) = 21.97*em_factor_no_wet(jv)*pulse(ji)
1396             END IF
1397             !Else if Temp negative
1398          ELSE IF (t_no(ji) .LT. zero) THEN
1399             flx_no_soil(ji,jv) = zero
1400             !Else if Temp <= 30
1401          ELSE IF (t_no(ji) .LE. 30.) THEN
1402             flx_no_soil(ji,jv) = (em_factor_no_dry(jv)*t_no(ji))/30.*pulse(ji)
1403          ELSE
1404             flx_no_soil(ji,jv) = em_factor_no_dry(jv)*pulse(ji)
1405          END IF
1406
1407          !! 7.3 IF ACTIVATED (ok_bbgfertil_NOx = TRUE) calculation of NOx soil emission increase due to biomass burning
1408          ! Calculation of Biomass-Burning-induced NOx emissions (Lathiere, 2005)
1409          ! => NOx emissions 3-fold increase
1410          IF (ok_bbgfertil_NOx) THEN
1411             IF ( natural(jv) ) THEN
1412                ! North Tropical zone from May to June
1413                IF ((lalo(ji,1) .LE. 30. .AND. lalo(ji,1) .GE. zero).AND. &
1414                     (julian_diff .GE. 121. .AND. julian_diff .LE. 181).AND.(flx_co2_bbg_year(ji) .GT. 0.1)) THEN
1415                   flx_no_soil(ji,jv) = flx_no_soil(ji,jv)*3.
1416                   ! South Tropical zone from November to December
1417                ELSE IF ((lalo(ji,1) .GE. -30. .AND. lalo(ji,1) .LT. zero).AND.(julian_diff .GE. 305.).AND. & 
1418                        (flx_co2_bbg_year(ji) .GT. 0.1)) THEN
1419                   flx_no_soil(ji,jv) = flx_no_soil(ji,jv)*3.
1420                END IF
1421             END IF
1422          END IF
1423
1424          !! 7.4 IF ACTIVATED (ok_cropsfertil_NOx = TRUE) calculation of NOx soil emission increase due to fertilizer use
1425          ! Calculation of N-fertiliser-induced NOx emissions
1426          flx_fertil_no(ji,jv) = zero
1427          IF (ok_cropsfertil_NOx) THEN
1428             IF (veget_max_nowoody(ji) .NE. zero) THEN
1429                ! Non-agricultural lands
1430                IF ( (jv == ibare_sechiba) .OR. is_tree(jv) ) THEN
1431                   N_qt_WRICE_pft(ji,jv) = zero
1432                   N_qt_OTHER_pft(ji,jv) = zero
1433                ! Grasslands or Croplands
1434                ELSE
1435                   N_qt_WRICE_pft(ji,jv) = N_qt_WRICE_year(ji)*veget_max(ji,jv)/veget_max_nowoody(ji)
1436                   N_qt_OTHER_pft(ji,jv) = N_qt_OTHER_year(ji)*veget_max(ji,jv)/veget_max_nowoody(ji)
1437                END IF
1438             ELSE
1439                N_qt_WRICE_pft(ji,jv) = zero
1440                N_qt_OTHER_pft(ji,jv) = zero
1441             END IF
1442
1443             ! North temperate regions from May to August
1444             ! OR South Temperate regions from November to February
1445             IF (((lalo(ji,1) .GT. 30.) .AND. (julian_diff .GE. 121. .AND. julian_diff .LE. 243.).AND. &
1446                  (veget_max(ji,jv) .GT. min_sechiba)) .OR. &
1447                  ((lalo(ji,1) .LT. -30.) .AND. (julian_diff .GE. 305. .OR. julian_diff .LE. 59.) .AND.&
1448                  (veget_max(ji,jv) .GT. min_sechiba))) THEN
1449                ! 1e12 for conversion from kg to Ng
1450                ! 1/(365/12*24*60*60*4) for conversion from year to seconds corrected for 4 months of emissions
1451                flx_fertil_no(ji,jv) = (N_qt_WRICE_pft(ji,jv)*(1/30.)+N_qt_OTHER_pft(ji,jv))*(2.5/100.) &
1452                     & *1e12/(365*24*60*60*4/12)/(area2(ji)*veget_max(ji,jv))
1453                ! OR Tropical regions all the year
1454             ELSE IF ((lalo(ji,1) .GE. -30.).AND.(lalo(ji,1) .LE. 30.).AND.(veget_max(ji,jv) .GT. min_sechiba)) THEN
1455                flx_fertil_no(ji,jv) = (N_qt_WRICE_pft(ji,jv)*(1/30.)+N_qt_OTHER_pft(ji,jv))*(2.5/100.) &
1456                     & *1e12/(365*24*60*60)/(area2(ji)*veget_max(ji,jv))
1457             END IF
1458             flx_no_soil(ji,jv) = flx_no_soil(ji,jv) + flx_fertil_no(ji,jv)
1459          END IF
1460
1461          !! 7.5 Calculation of net NO flux above soil accounting for surface deposition,
1462          !! based on the Canopy Reduction Factor (CRF), calculated using Leaf Area and Stomatal Area
1463          !kc=cuticle absorptivity = 0.24m^2/m^2
1464          !ks=stomatal absorptivity = 8.75m^2/m^2
1465          !Larch=Larcher SAI/LAI ratio given in Larcher 1991
1466          !> @codeinc
1467          CRF(ji,jv) = (exp(-8.75*Larch(jv)*lai(ji,jv)) + exp(-0.24*lai(ji,jv)))/2.
1468          flx_no(ji,jv) = flx_no_soil(ji,jv)*CRF(ji,jv)
1469          !> @endcodeinc
1470       END DO
1471    END DO
1472
1473
1474    ! Write output with XIOS
1475    CALL xios_orchidee_send_field("PAR",PAR)
1476    CALL xios_orchidee_send_field("flx_fertil_no",flx_fertil_no)
1477    CALL xios_orchidee_send_field("flx_iso",flx_iso)
1478    CALL xios_orchidee_send_field("flx_mono",flx_mono)
1479    CALL xios_orchidee_send_field("flx_ORVOC",flx_ORVOC)
1480    CALL xios_orchidee_send_field("flx_MBO",flx_MBO)
1481    CALL xios_orchidee_send_field("flx_methanol",flx_methanol)
1482    CALL xios_orchidee_send_field("flx_acetone",flx_acetone)
1483    CALL xios_orchidee_send_field("flx_acetal",flx_acetal)
1484    CALL xios_orchidee_send_field("flx_formal",flx_formal)
1485    CALL xios_orchidee_send_field("flx_acetic",flx_acetic)
1486    CALL xios_orchidee_send_field("flx_formic",flx_formic)
1487    CALL xios_orchidee_send_field("flx_no_soil",flx_no_soil)
1488    CALL xios_orchidee_send_field("flx_no",flx_no)
1489    CALL xios_orchidee_send_field('flx_apinen'   , flx_apinen)
1490    CALL xios_orchidee_send_field('flx_bpinen'   , flx_bpinen)
1491    CALL xios_orchidee_send_field('flx_limonen'  ,flx_limonen)
1492    CALL xios_orchidee_send_field('flx_myrcen'   , flx_myrcen)
1493    CALL xios_orchidee_send_field('flx_sabinen'  ,flx_sabinen)
1494    CALL xios_orchidee_send_field('flx_camphen'  ,flx_camphen)
1495    CALL xios_orchidee_send_field('flx_3caren'   , flx_3caren)
1496    CALL xios_orchidee_send_field('flx_tbocimen' ,flx_tbocimen)
1497    CALL xios_orchidee_send_field('flx_othermono',flx_othermono)
1498    CALL xios_orchidee_send_field('flx_sesquiter',flx_sesquiter)
1499    CALL xios_orchidee_send_field("CRF",CRF)
1500    CALL xios_orchidee_send_field('fco2', fco2)
1501
1502    IF ( ok_radcanopy ) THEN
1503       CALL xios_orchidee_send_field("PARdf",PARdf)
1504       CALL xios_orchidee_send_field("PARdr",PARdr)
1505       
1506       IF (ok_multilayer) THEN
1507          CALL xios_orchidee_send_field("PARsuntab",PARsuntab)
1508          CALL xios_orchidee_send_field("PARshtab",PARshtab)
1509       ELSE
1510          CALL xios_orchidee_send_field("PARsun",PARsun)
1511          CALL xios_orchidee_send_field("PARsh",PARsh)
1512          CALL xios_orchidee_send_field("laisun",laisun)
1513          CALL xios_orchidee_send_field("laish",laish)
1514       ENDIF
1515    ENDIF
1516
1517    IF ( ok_bbgfertil_Nox ) THEN
1518       CALL xios_orchidee_send_field("flx_co2_bbg_year",flx_co2_bbg_year)
1519    END IF
1520
1521    IF ( ok_cropsfertil_Nox ) THEN
1522       CALL xios_orchidee_send_field("N_qt_WRICE_year",N_qt_WRICE_year)
1523       CALL xios_orchidee_send_field("N_qt_OTHER_year",N_qt_OTHER_year)
1524    END IF
1525   
1526
1527    ! Write output with IOIPSL
1528    IF ( .NOT. almaoutput ) THEN
1529
1530       CALL histwrite_p(hist_id, 'PAR', kjit, PAR, kjpindex, index)
1531       IF ( ok_radcanopy ) THEN
1532          CALL histwrite_p(hist_id, 'laisun', kjit, laisun, kjpindex*nvm, indexveg)
1533          CALL histwrite_p(hist_id, 'laish', kjit, laish, kjpindex*nvm, indexveg)
1534          CALL histwrite_p(hist_id, 'Fdf', kjit, Fdf, kjpindex, index)
1535          IF (ok_multilayer) THEN
1536             CALL histwrite_p(hist_id, 'PARsuntab', kjit, PARsuntab, kjpindex*(nlai+1), indexlai)
1537             CALL histwrite_p(hist_id, 'PARshtab', kjit, PARshtab, kjpindex*(nlai+1), indexlai)
1538          ELSE
1539             CALL histwrite_p(hist_id, 'PARsun', kjit, PARsun, kjpindex*nvm, indexveg)
1540             CALL histwrite_p(hist_id, 'PARsh', kjit, PARsh, kjpindex*nvm, indexveg)
1541          END IF
1542          CALL histwrite_p(hist_id, 'coszang', kjit, coszang, kjpindex, index)
1543          CALL histwrite_p(hist_id, 'PARdf', kjit, PARdf, kjpindex, index)
1544          CALL histwrite_p(hist_id, 'PARdr', kjit, PARdr, kjpindex, index)
1545          CALL histwrite_p(hist_id, 'Trans', kjit, Trans, kjpindex, index)
1546       END IF
1547       CALL histwrite_p(hist_id, 'flx_fertil_no', kjit, flx_fertil_no, kjpindex*nvm, indexveg)
1548       CALL histwrite_p(hist_id, 'CRF', kjit, CRF, kjpindex*nvm, indexveg)
1549       CALL histwrite_p(hist_id, 'fco2', kjit, fco2, kjpindex*nvm, indexveg)
1550
1551       IF ( ok_bbgfertil_Nox ) THEN
1552          CALL histwrite_p(hist_id, 'flx_co2_bbg_year', 1, flx_co2_bbg_year, kjpindex, index)
1553       ENDIF
1554       IF ( ok_cropsfertil_Nox ) THEN
1555          CALL histwrite_p(hist_id, 'N_qt_WRICE_year', 1, N_qt_WRICE_year, kjpindex, index)
1556          CALL histwrite_p(hist_id, 'N_qt_OTHER_year', 1, N_qt_OTHER_year, kjpindex, index)
1557       ENDIF
1558       CALL histwrite_p(hist_id, 'flx_iso', kjit, flx_iso, kjpindex*nvm, indexveg)
1559       CALL histwrite_p(hist_id, 'flx_mono', kjit, flx_mono, kjpindex*nvm, indexveg)
1560       CALL histwrite_p(hist_id, 'flx_apinen', kjit, flx_apinen, kjpindex*nvm, indexveg)
1561       CALL histwrite_p(hist_id, 'flx_bpinen', kjit, flx_bpinen, kjpindex*nvm, indexveg)
1562       CALL histwrite_p(hist_id, 'flx_limonen', kjit, flx_limonen, kjpindex*nvm, indexveg)
1563       CALL histwrite_p(hist_id, 'flx_myrcen', kjit, flx_myrcen, kjpindex*nvm, indexveg)
1564       CALL histwrite_p(hist_id, 'flx_sabinen', kjit, flx_sabinen, kjpindex*nvm, indexveg)
1565       CALL histwrite_p(hist_id, 'flx_camphen', kjit, flx_camphen, kjpindex*nvm, indexveg)
1566       CALL histwrite_p(hist_id, 'flx_3caren', kjit, flx_3caren, kjpindex*nvm, indexveg)
1567       CALL histwrite_p(hist_id, 'flx_tbocimen', kjit, flx_tbocimen, kjpindex*nvm, indexveg)
1568       CALL histwrite_p(hist_id, 'flx_othermono', kjit, flx_othermono, kjpindex*nvm, indexveg)
1569       CALL histwrite_p(hist_id, 'flx_sesquiter', kjit, flx_sesquiter, kjpindex*nvm, indexveg)
1570       CALL histwrite_p(hist_id, 'flx_ORVOC', kjit, flx_ORVOC, kjpindex*nvm, indexveg)
1571       CALL histwrite_p(hist_id, 'flx_MBO', kjit, flx_MBO, kjpindex*nvm, indexveg)
1572       CALL histwrite_p(hist_id, 'flx_methanol', kjit, flx_methanol, kjpindex*nvm, indexveg)
1573       CALL histwrite_p(hist_id, 'flx_acetone', kjit, flx_acetone, kjpindex*nvm, indexveg)
1574       CALL histwrite_p(hist_id, 'flx_acetal', kjit, flx_acetal, kjpindex*nvm, indexveg)
1575       CALL histwrite_p(hist_id, 'flx_formal', kjit, flx_formal, kjpindex*nvm, indexveg)
1576       CALL histwrite_p(hist_id, 'flx_acetic', kjit, flx_acetic, kjpindex*nvm, indexveg)
1577       CALL histwrite_p(hist_id, 'flx_formic', kjit, flx_formic, kjpindex*nvm, indexveg)
1578       CALL histwrite_p(hist_id, 'flx_no_soil', kjit, flx_no_soil, kjpindex*nvm, indexveg)
1579       CALL histwrite_p(hist_id, 'flx_no', kjit, flx_no, kjpindex*nvm, indexveg)
1580       
1581       IF ( hist2_id > 0 ) THEN
1582          CALL histwrite_p(hist2_id, 'PAR', kjit, PAR, kjpindex, index)
1583          IF ( ok_radcanopy ) THEN
1584             CALL histwrite_p(hist2_id, 'PARsun', kjit, PARsun, kjpindex*nvm, indexveg)
1585             CALL histwrite_p(hist2_id, 'PARsh', kjit, PARsh, kjpindex*nvm, indexveg)
1586             CALL histwrite_p(hist2_id, 'laisun', kjit, laisun, kjpindex*nvm, indexveg)
1587             CALL histwrite_p(hist2_id, 'laish', kjit, laish, kjpindex*nvm, indexveg)
1588          ENDIF
1589          CALL histwrite_p(hist2_id, 'flx_fertil_no', kjit, flx_fertil_no, kjpindex*nvm, indexveg)
1590          CALL histwrite_p(hist2_id, 'CRF', kjit, CRF, kjpindex*nvm, indexveg)
1591          IF ( ok_bbgfertil_Nox ) THEN
1592             CALL histwrite_p(hist2_id, 'flx_co2_bbg_year', 1, flx_co2_bbg_year, kjpindex, index)
1593          ENDIF
1594          IF ( ok_cropsfertil_Nox ) THEN
1595             CALL histwrite_p(hist2_id, 'N_qt_WRICE_year', 1, N_qt_WRICE_year, kjpindex, index)
1596             CALL histwrite_p(hist2_id, 'N_qt_OTHER_year', 1, N_qt_OTHER_year, kjpindex, index)
1597          ENDIF
1598          CALL histwrite_p(hist2_id, 'flx_iso', kjit, flx_iso, kjpindex*nvm, indexveg)
1599          CALL histwrite_p(hist2_id, 'flx_mono', kjit, flx_mono, kjpindex*nvm, indexveg)
1600          CALL histwrite_p(hist2_id, 'flx_apinen', kjit, flx_apinen, kjpindex*nvm, indexveg)
1601          CALL histwrite_p(hist2_id, 'flx_bpinen', kjit, flx_bpinen, kjpindex*nvm, indexveg)
1602          CALL histwrite_p(hist2_id, 'flx_limonen', kjit, flx_limonen, kjpindex*nvm, indexveg)
1603          CALL histwrite_p(hist2_id, 'flx_myrcen', kjit, flx_myrcen, kjpindex*nvm, indexveg)
1604          CALL histwrite_p(hist2_id, 'flx_sabinen', kjit, flx_sabinen, kjpindex*nvm, indexveg)
1605          CALL histwrite_p(hist2_id, 'flx_camphen', kjit, flx_camphen, kjpindex*nvm, indexveg)
1606          CALL histwrite_p(hist2_id, 'flx_3caren', kjit, flx_3caren, kjpindex*nvm, indexveg)
1607          CALL histwrite_p(hist2_id, 'flx_tbocimen', kjit, flx_tbocimen, kjpindex*nvm, indexveg)
1608          CALL histwrite_p(hist2_id, 'flx_othermono', kjit, flx_othermono, kjpindex*nvm, indexveg)
1609          CALL histwrite_p(hist2_id, 'flx_sesquiter', kjit, flx_sesquiter, kjpindex*nvm, indexveg)
1610          CALL histwrite_p(hist2_id, 'flx_ORVOC', kjit, flx_ORVOC, kjpindex*nvm, indexveg)
1611          CALL histwrite_p(hist2_id, 'flx_MBO', kjit, flx_MBO, kjpindex*nvm, indexveg)
1612          CALL histwrite_p(hist2_id, 'flx_methanol', kjit, flx_methanol, kjpindex*nvm, indexveg)
1613          CALL histwrite_p(hist2_id, 'flx_acetone', kjit, flx_acetone, kjpindex*nvm, indexveg)
1614          CALL histwrite_p(hist2_id, 'flx_acetal', kjit, flx_acetal, kjpindex*nvm, indexveg)
1615          CALL histwrite_p(hist2_id, 'flx_formal', kjit, flx_formal, kjpindex*nvm, indexveg)
1616          CALL histwrite_p(hist2_id, 'flx_acetic', kjit, flx_acetic, kjpindex*nvm, indexveg)
1617          CALL histwrite_p(hist2_id, 'flx_formic', kjit, flx_formic, kjpindex*nvm, indexveg)
1618          CALL histwrite_p(hist2_id, 'flx_no_soil', kjit, flx_no_soil, kjpindex*nvm, indexveg)
1619          CALL histwrite_p(hist2_id, 'flx_no', kjit, flx_no, kjpindex*nvm, indexveg)
1620       ENDIF
1621    ENDIF
1622
1623    IF (printlev>=3) WRITE(numout,*) 'OK chemistry_bvoc'
1624
1625  END SUBROUTINE chemistry_bvoc
1626
1627!! ================================================================================================================================
1628!! SUBROUTINE   : chemistry_flux_interface
1629!!
1630!>\BRIEF         This subroutine will give to the interface between inca model and orchidee model in sechiba all the flux ask by inca
1631!!
1632!! DESCRIPTION  :  This subroutine allow the transfer of fluxes between surface and atmospheric chemistry. It is called from sechiba
1633!!
1634!! RECENT CHANGE(S): None
1635!!
1636!! MAIN OUTPUT VARIABLE(S): ::
1637!!
1638!! REFERENCE(S) : None
1639!!
1640!! FLOWCHART    : None
1641!_ ================================================================================================================================
1642
1643 SUBROUTINE chemistry_flux_interface( field_out_names, fields_out, field_in_names, fields_in)
1644
1645     !
1646     ! Optional arguments
1647     !
1648     ! Names and fields for emission variables : to be transport by Orchidee to Inca
1649     CHARACTER(LEN=*),DIMENSION(:), OPTIONAL, INTENT(IN) :: field_out_names
1650     REAL(r_std),DIMENSION(:,:,:), OPTIONAL, INTENT(OUT) :: fields_out
1651     !
1652     ! Names and fields for deposit variables : to be transport from chemistry model by INCA to ORCHIDEE.
1653     CHARACTER(LEN=*),DIMENSION(:), OPTIONAL, INTENT(IN) :: field_in_names
1654     REAL(r_std),DIMENSION(:,:), OPTIONAL, INTENT(IN)    :: fields_in
1655     !
1656     ! Number of fields to give (nb_fields_out) or get from (nb_fields_in) INCA :
1657     INTEGER(i_std), SAVE   :: nb_fields_out, nb_fields_in
1658!$OMP THREADPRIVATE(nb_fields_out, nb_fields_in)
1659
1660     ! Id of fields to give (nb_fields_out) or get from (nb_fields_in) INCA :
1661     INTEGER(i_std)  :: i_fields_out, i_fields_in
1662
1663     IF (l_first_chemistry_inca) THEN
1664
1665        ! il faut verifier que ok_bvoc (chemistry_ok_bvoc) est bien active sinon on arrete tout
1666        if (.not.ok_bvoc) then
1667          CALL ipslerr_p (3,'chemistry_inca', &
1668            &          'you need to activate chemistry_ok_bvoc in orchidee.def',&
1669            &          'This model won''t be able to continue.', &
1670            &          '')
1671        endif
1672
1673        ! Prepare fieds out/in for interface with INCA.
1674        IF (PRESENT(field_out_names)) THEN
1675           nb_fields_out=SIZE(field_out_names)
1676        ELSE
1677           nb_fields_out=0
1678        ENDIF
1679
1680        IF (PRESENT(field_in_names)) THEN
1681           nb_fields_in=SIZE(field_in_names)
1682        ELSE
1683           nb_fields_in=0
1684        ENDIF
1685        l_first_chemistry_inca = .FALSE.
1686
1687     ENDIF
1688
1689
1690
1691     IF (ok_bvoc) THEN 
1692        ! Fields for deposit variables : to be transport from chemistry model by INCA to ORCHIDEE.
1693        DO i_fields_in=1,nb_fields_in
1694           SELECT CASE(TRIM(field_in_names(i_fields_in)))
1695           CASE DEFAULT 
1696              CALL ipslerr_p (3,'chemistry_inca', &
1697                   &          'You ask in INCA an unknown field '//TRIM(field_in_names(i_fields_in))//&
1698                   &          ' to give to ORCHIDEE for this specific version.',&
1699                   &          'This model won''t be able to continue.', &
1700                   &          '(check your tracer parameters in INCA)')
1701           END SELECT
1702        ENDDO
1703       
1704        ! Fields for Biogenic emissions : to be transport by Orchidee to Inca
1705        DO i_fields_out=1,nb_fields_out
1706           SELECT CASE(TRIM(field_out_names(i_fields_out)))
1707           CASE("flx_iso") 
1708              fields_out(:,:,i_fields_out)=flx_iso(:,:)
1709           CASE("flx_mono") 
1710              fields_out(:,:,i_fields_out)=flx_mono(:,:)
1711           CASE("flx_ORVOC") 
1712              fields_out(:,:,i_fields_out)=flx_ORVOC(:,:)
1713           CASE("flx_MBO") 
1714              fields_out(:,:,i_fields_out)=flx_MBO(:,:)
1715           CASE("flx_methanol") 
1716              fields_out(:,:,i_fields_out)=flx_methanol(:,:)
1717           CASE("flx_acetone") 
1718              fields_out(:,:,i_fields_out)=flx_acetone(:,:)
1719           CASE("flx_acetal") 
1720              fields_out(:,:,i_fields_out)=flx_acetal(:,:)
1721           CASE("flx_formal") 
1722              fields_out(:,:,i_fields_out)=flx_formal(:,:)
1723           CASE("flx_acetic") 
1724              fields_out(:,:,i_fields_out)=flx_acetic(:,:)
1725           CASE("flx_formic") 
1726              fields_out(:,:,i_fields_out)=flx_formic(:,:)
1727           CASE("flx_no_soil") 
1728              fields_out(:,:,i_fields_out)=flx_no_soil(:,:)
1729           CASE("flx_nox") 
1730              fields_out(:,:,i_fields_out)=flx_no(:,:)
1731           CASE("flx_fertil_no") 
1732              fields_out(:,:,i_fields_out)=flx_fertil_no(:,:)
1733           CASE("flx_apinen")
1734              fields_out(:,:,i_fields_out)=flx_apinen(:,:)
1735           CASE("flx_bpinen")
1736              fields_out(:,:,i_fields_out)=flx_bpinen(:,:)
1737           CASE("flx_limonen")
1738              fields_out(:,:,i_fields_out)=flx_limonen(:,:)
1739           CASE("flx_myrcen")
1740              fields_out(:,:,i_fields_out)=flx_myrcen(:,:)
1741           CASE("flx_sabinen")
1742              fields_out(:,:,i_fields_out)=flx_sabinen(:,:)
1743           CASE("flx_camphen")
1744              fields_out(:,:,i_fields_out)=flx_camphen(:,:)
1745           CASE("flx_3caren")
1746              fields_out(:,:,i_fields_out)=flx_3caren(:,:)
1747           CASE("flx_tbocimen")
1748              fields_out(:,:,i_fields_out)=flx_tbocimen(:,:)
1749           CASE("flx_othermono")
1750              fields_out(:,:,i_fields_out)=flx_othermono(:,:)
1751           CASE("flx_sesquiter")
1752              fields_out(:,:,i_fields_out)=flx_sesquiter(:,:)
1753             
1754           CASE DEFAULT 
1755              CALL ipslerr_p (3,'chemistry_inca', &
1756                   &          'You ask from INCA an unknown field '//TRIM(field_out_names(i_fields_out))//&
1757                   &          ' to ORCHIDEE for this specific version.',&
1758                   &          'This model won''t be able to continue.', &
1759                   &          '(check your tracer parameters in INCA)')
1760           END SELECT
1761        ENDDO
1762       
1763     ENDIF
1764   END SUBROUTINE chemistry_flux_interface
1765
1766!! ================================================================================================================================
1767!! SUBROUTINE   : chemistry_clear
1768!!
1769!>\BRIEF         Clear chemistry module
1770!!
1771!! DESCRIPTION  :  Deallocate memory and reset initialization variables to there original values
1772!!
1773!_ ================================================================================================================================
1774   SUBROUTINE chemistry_clear
1775
1776     !! 1. Initialize as for first run
1777     l_first_chemistry_inca = .TRUE.
1778     
1779     !! 2. Deallocate dynamic variables
1780     IF (ALLOCATED(pulse)) DEALLOCATE (pulse)
1781     IF (ALLOCATED (ok_siesta)) DEALLOCATE (ok_siesta) 
1782     IF (ALLOCATED (allow_pulse)) DEALLOCATE (allow_pulse)
1783     IF (ALLOCATED (pulseday)) DEALLOCATE (pulseday)
1784     IF (ALLOCATED (siestaday)) DEALLOCATE (siestaday)
1785     IF (ALLOCATED (pulselim)) DEALLOCATE (pulselim)
1786     IF (ALLOCATED (siestalim)) DEALLOCATE (siestalim)
1787     IF (ALLOCATED (area2)) DEALLOCATE (area2)
1788     IF (ALLOCATED (N_qt_WRICE_year)) DEALLOCATE (N_qt_WRICE_year)
1789     IF (ALLOCATED (N_qt_OTHER_year)) DEALLOCATE (N_qt_OTHER_year)
1790     IF (ALLOCATED (flx_iso)) DEALLOCATE (flx_iso)
1791     IF (ALLOCATED (flx_mono)) DEALLOCATE (flx_mono)
1792     IF (ALLOCATED (flx_ORVOC)) DEALLOCATE (flx_ORVOC)
1793     IF (ALLOCATED (flx_MBO)) DEALLOCATE (flx_MBO)
1794     IF (ALLOCATED (flx_methanol)) DEALLOCATE (flx_methanol)
1795     IF (ALLOCATED (flx_acetone)) DEALLOCATE (flx_acetone)
1796     IF (ALLOCATED (flx_acetal)) DEALLOCATE (flx_acetal)
1797     IF (ALLOCATED (flx_formal)) DEALLOCATE (flx_formal)
1798     IF (ALLOCATED (flx_acetic)) DEALLOCATE (flx_acetic)
1799     IF (ALLOCATED (flx_formic)) DEALLOCATE (flx_formic)
1800     IF (ALLOCATED (flx_no_soil)) DEALLOCATE (flx_no_soil)
1801     IF (ALLOCATED (flx_no)) DEALLOCATE (flx_no)
1802     IF (ALLOCATED (flx_fertil_no)) DEALLOCATE (flx_fertil_no)
1803     IF (ALLOCATED (flx_apinen)) DEALLOCATE (flx_apinen)
1804     IF (ALLOCATED (flx_bpinen)) DEALLOCATE (flx_bpinen)
1805     IF (ALLOCATED (flx_limonen)) DEALLOCATE (flx_limonen)
1806     IF (ALLOCATED (flx_myrcen)) DEALLOCATE (flx_myrcen)
1807     IF (ALLOCATED (flx_sabinen)) DEALLOCATE (flx_sabinen)
1808     IF (ALLOCATED (flx_camphen)) DEALLOCATE (flx_camphen)
1809     IF (ALLOCATED (flx_3caren)) DEALLOCATE (flx_3caren)
1810     IF (ALLOCATED (flx_tbocimen)) DEALLOCATE (flx_tbocimen)
1811     IF (ALLOCATED (flx_othermono)) DEALLOCATE (flx_othermono)
1812     IF (ALLOCATED (flx_sesquiter)) DEALLOCATE (flx_sesquiter)
1813     IF (ALLOCATED (CRF)) DEALLOCATE (CRF)
1814     IF (ALLOCATED (flx_co2_bbg_year)) DEALLOCATE (flx_co2_bbg_year)
1815
1816   END SUBROUTINE chemistry_clear
1817   
1818END MODULE chemistry
Note: See TracBrowser for help on using the repository browser.