module_bioemi_simple.F

References to this file elsewhere.
1 MODULE module_bioemi_simple
2 ! ..
3 ! make sure that whatever you put in here agrees with dry_dep_simple
4 ! and met model luse stuff. This should be improved, but currently,
5 ! there is only usgs in wrf
6 !
7   USE module_data_radm2
8       INTEGER, PARAMETER ::  nlu = 25,  &
9         iswater_temp = 16,isice_temp = 24
10       REAL :: aefiso(nlu), aefmter(nlu), aefovoc(nlu), aef_n(nlu)
11       CHARACTER (4),PARAMETER :: mminlu_loc = 'USGS'
12       INTEGER :: ixxxlu(nlu)
13 
14 
15     CONTAINS
16       SUBROUTINE bio_emissions(id,ktau,dtstep,DX,                         &
17                config_flags,                                              &
18                gmt,julday,t_phy,moist,p8w,t8w,                            &
19                e_bio,p_phy,chem,rho_phy,dz8w,ne_area,                     &
20                ivgtyp,gsw,vegfra,rmol,ust,znt,xlat,xlong,z_at_w,          &
21                numgas,                                                    &
22                ids,ide, jds,jde, kds,kde,                                 &
23                ims,ime, jms,jme, kms,kme,                                 &
24                its,ite, jts,jte, kts,kte                                  )
25   USE module_configure
26   USE module_state_description
27   IMPLICIT NONE
28    INTEGER,      INTENT(IN   ) :: id,julday, ne_area,                     &
29                                   ids,ide, jds,jde, kds,kde,              &
30                                   ims,ime, jms,jme, kms,kme,              &
31                                   its,ite, jts,jte, kts,kte,numgas
32    INTEGER,      INTENT(IN   ) ::                                         &
33                                   ktau
34    REAL, DIMENSION( ims:ime, kms:kme, jms:jme, num_moist ),               &
35          INTENT(IN ) ::                                   moist
36    REAL, DIMENSION( ims:ime, kms:kme, jms:jme, num_chem ),                &
37          INTENT(INOUT ) ::                                   chem
38    REAL, DIMENSION( ims:ime, jms:jme, ne_area ),                          &
39          INTENT(INOUT ) ::                               e_bio
40    REAL,  DIMENSION( ims:ime , kms:kme , jms:jme )         ,              &
41           INTENT(IN   ) ::                                                &
42                                                       t_phy,              &
43                                                       p_phy,              &
44                                                       dz8w,               &
45                                               t8w,p8w,z_at_w ,            &
46                                                     rho_phy
47    INTEGER,DIMENSION( ims:ime , jms:jme )                  ,              &
48           INTENT(IN   ) ::                                                &
49                                                      ivgtyp
50    REAL,  DIMENSION( ims:ime , jms:jme )                   ,              &
51           INTENT(IN   ) ::                                                &
52                                                      gsw,                 &
53                                                   vegfra,                 &
54                                                      rmol,                &
55                                                      ust,                 &
56                                                      xlat,                &
57                                                      xlong,               &
58                                                      znt
59       REAL,      INTENT(IN   ) ::                                         &
60                              dtstep,dx,gmt
61 !--- deposition and emissions stuff
62 ! .. Parameters ..
63    TYPE(grid_config_rec_type),  INTENT(IN   )    :: config_flags
64 
65 ! ..
66 ! .. Local Arrays ..
67 ! .. Parameters ..
68 !     INTEGER, PARAMETER ::  nlu = 25,  &
69 !       nseason = 1, nseasons = 2
70 !     REAL :: aefiso(nlu), aefmter(nlu), aefovoc(nlu), aef_n(nlu),  &
71 !       emiss_bio(numgas)
72       REAL :: emiss_bio(numgas)
73       LOGICAL :: highnh3, rainflag, vegflag, wetflag
74       CHARACTER (4) :: luse_typ
75 ! ..
76 ! .. Local Scalars ..
77       REAL ::  clwchem,eiso,eisoc,emter,emterc,eovoc,eovocc,e_n,e_nn,  &
78         pa,rad, rhchem, ta, ustar, vegfrac, vocsc, xtimin, z1,zntt
79       INTEGER :: i,j,iland, iprt, iseason, n, nr, ipr,jpr,nvr
80 
81 
82 ! .. Intrinsic Functions ..
83       INTRINSIC max, min
84 !
85       luse_typ=mminlu_loc
86 !     print *,'luse_typ,iswater',luse_typ,iswater_temp
87       iseason=1
88       if(julday.lt.90.or.julday.gt.270)then
89         iseason=2
90         CALL wrf_debug(100,'setting iseason in bio_emi to 2')
91       endif
92         
93                          
94 !  test program to test chemics stuff in 1-d                   
95                          
96 !     first prepare for biogenic emissions                      
97                          
98       CALL bioemiin(iseason,luse_typ,vegflag) 
99       do 100 j=jts,jte  
100       do 100 i=its,ite  
101       iland = ivgtyp(i,j)
102       ta = t_phy(i,kts,j)      
103       rad = gsw(i,j)
104       vegfrac = vegfra(i,j)
105       pa = .01*p_phy(i,kts,j)
106       clwchem = moist(i,kts,j,p_qc)
107       ustar = ust(i,j) 
108       zntt = znt(i,j)                                                 
109       z1 = z_at_w(i,kts+1,j)-z_at_w(i,kts,j)                          
110                                                                       
111 !     Set logical default values                                      
112       rainflag = .FALSE.                                              
113       wetflag = .FALSE.                                               
114       highnh3 = .FALSE.                                               
115                                                                       
116       if(moist(i,kts,j,p_qr).gt.0.)rainflag = .true.                  
117 !     if(raincv(i,kts,j).gt.0. .and. rainncv(i,kts,j).gt.0. )rainflag = .true.      
118                                                                       
119 !     qvs  = 380.*exp(17.27*(tair-273.)/(tair-36.))/pressure          
120       rhchem = MIN( 100.,100. * moist(i,kts,j,p_qv) / &               
121                (3.80*exp(17.27*(t_phy(i,kts,j)-273.)/(t_phy(i,kts,j)-36.))/pa))     
122       rhchem = max(rhchem,5.)
123       if (rhchem >= 95.) wetflag = .true.                             
124 !     print *,chem(i,kts,j,p_nh3),chem(i,kts,j,p_so2)
125       if(chem(i,kts,j,p_nh3).gt.2.*chem(i,kts,j,p_so2))highnh3 = .true.
126       iseason = 1                                                     
127 !--- biogenic emissions
128       emiss_bio=0.
129       CALL biogen(iland,ta,rad,eiso,emter,eovoc,e_n,vocsc,eisoc,emterc,eovocc, &
130         e_nn,pa,luse_typ,iseason,vegflag)
131 !     if(i.eq.5.and.j.eq.5)then
132 !         print *,iland
133 !         print *,ta,rad,vocsc,pa,luse_typ,aefiso,aefovoc,aefmter, &
134 !                aef_n,ixxxlu,vegflag,isice_temp,iswater_temp
135 !         PRINT *, eiso, emter, eovoc, e_n, eisoc, eovocc
136 !     endif
137 
138 !     PRINT *, eiso, emter, eovoc, e_n, eisoc, eovocc                 
139       CALL biosplit(iland,eiso,emter,eovoc,e_n,emiss_bio,numgas,vegfrac, &
140         luse_typ,vegflag)
141 !     PRINT *, 'emiss_bio(liso)  emiss_bio(lald)  emiss_bio(lhcho) ', &
142 !       ' emiss_bio(lhc3)'
143 !     PRINT *, emiss_bio(liso), emiss_bio(lald), emiss_bio(lhcho), &
144 !       emiss_bio(lhc3)
145       DO n = 1, numgas-2
146         e_bio(i,j,n) = emiss_bio(n)
147 !       if(i.eq.5.and.j.eq.5)print *,emiss_bio(n)
148       END DO
149  100  continue
150 END SUBROUTINE bio_emissions
151 ! **********************************************************************
152 ! **********************  SUBROUTINE BIOEMIIN **************************
153 ! **********************************************************************
154       SUBROUTINE bioemiin(isn,mminlu,vegflag)
155 !**********************************************************************
156 !     THIS SUBROUTINE INITIALIZES THE EMISSION FACTORS
157 !     AND THE SIMPLIFIED LANDUSE SCHEME
158 !     FOR THE BIOGENIC EMISSION AND DEPOSITION SUBROUTINES
159 !     WRITTEN BY: WINFRIED SEIDL (MARCH 2000)
160 !     CALLED BY:
161 !     CALLS:      -
162 !**********************************************************************
163 !**********************************************************************
164 !     REFERENCES FOR EMISSION FACTORS:
165 !     (S+R)  T. Schoenemeyer and K. Richter
166 !     (S95)  D. Simpson, A. Guenther, C. N. Hewitt, and R. Steinbrecher
167 !            J. Geophysical Research 100D (1995), 22875-22890
168 !     (G94)  A. Guenther, P. Zimmerman and M. Wildermuth
169 !            Atmospheric Environment 28 (1994), 1197-1210
170 !     (Z88)  P. R. Zimmerman, J. P. Greenberg, and C. E. Westberg
171 !            J. Geophysical Research 93D (1988), 1407-1416
172 !     (K88)  W. A. Kaplan, S. C. Wofsy, M. Keller, and J. M. da Costa
173 !            J. Geophysical Research 93D (1988), 1389-1395
174 !     (K94)  L. F. Klinger, P. R. Zimmermann, J. P. Greenberg, L. E. Hei
175 !            and A. B. Guenther
176 !            J. Geophysical Research 99D (1994), 1469-1494
177 !     ---------------------------------------------------------
178 !     PCU/NCAR landuse categories:
179 !        1 Highrise urban area
180 !        2 Agricultural land
181 !        3 Grassland, rangeland
182 !        4 Deciduous forest
183 !        5 Coniferous forest
184 !        6 Mixed forest (including wetland)
185 !        7 Water
186 !        8 Wet rangeland, nonforested wetland
187 !        9 Desert
188 !       10 Tundra
189 !       11 Permanent ice
190 !       12 Tropical  forest land
191 !       13 Savannah
192 !     ---------------------------------------------------------
193 !     USGS landuse categories:
194 !        1 Urban and built-up land
195 !        2 Dryland cropland and pasture
196 !        3 Irrigated cropland and pasture
197 !        4 Mix. dry/irrg. cropland and pasture
198 !        5 Cropland/grassland mosaic
199 !        6 Cropland/woodland mosaic
200 !        7 Grassland
201 !        8 Shrubland
202 !        9 Mixed shrubland/grassland
203 !       10 Savanna
204 !       11 Deciduous broadleaf forest
205 !       12 Deciduous needleleaf forest
206 !       13 Evergreen broadleaf forest
207 !       14 Evergreen needleleaf forest
208 !       15 Mixed Forest
209 !       16 Water Bodies
210 !       17 Herbaceous wetland
211 !       18 Wooded wetland
212 !       19 Barren or sparsely vegetated
213 !       20 Herbaceous Tundra
214 !       21 Wooded Tundra
215 !       22 Mixed Tundra
216 !       23 Bare Ground Tundra
217 !       24 Snow or Ice
218 !       25 No data
219 !     ---------------------------------------------------------
220 !     SiB landuse categories:
221 !        1 Evergreen broadleaf trees
222 !        2 Broadleaf deciduous trees
223 !        3 Deciduous and evergreen trees
224 !        4 Evergreen needleleaf trees
225 !        5 Deciduous needleleaf trees
226 !        6 Ground cover with trees and shrubs
227 !        7 Ground cover only
228 !        8 Broadleaf shrub with Perennial ground cover
229 !        9 Broadleaf shrub with bare soil
230 !       10 Groundcover with dwarf trees and shrubs
231 !       11 Bare soil
232 !       12 Agriculture or C3 grassland
233 !       13 Persistent Wetland
234 !       14 Dry coastal complexes
235 !       15 Water
236 !       16 Ice cap and glacier
237 !       17 No data
238 !--------------------------------------------------------------
239 ! .. Scalar Arguments ..
240         LOGICAL :: vegflag
241         CHARACTER (4) :: mminlu
242         INTEGER :: isn
243 ! ..
244 ! .. Array Arguments ..
245 !       REAL :: aefiso(nlu), aefmter(nlu), aefovoc(nlu), aef_n(nlu)
246 !       INTEGER :: ixxxlu(nlu)
247 ! ..
248 ! .. Local Scalars ..
249 !       INTEGER :: nseas
250         INTEGER :: sum
251 ! ..
252 !**********************************************************************
253 !     Emission Factors for Isoprene in ug C/(m*m*h)
254 !       PRINT *, 'mminlu = ', mminlu
255         IF (mminlu=='OLD ') THEN
256 ! urban                                 
257           aefiso(1) = 0.
258 ! agriculture (S+R)                     
259           aefiso(2) = 8.
260 ! grassland (S+R)                       
261           aefiso(3) = 0.
262 ! deciduous (G94)                       
263           aefiso(4) = 4400.
264 ! coniferous (G94)                      
265           aefiso(5) = 780.
266 ! mixed forest (G94)                    
267           aefiso(6) = 5775.
268 ! water                                 
269           aefiso(7) = 0.
270 ! wetland, emission unknown             
271           aefiso(8) = 0.
272 ! desert                                
273           aefiso(9) = 0.
274 ! tundra (K94)                          
275           aefiso(10) = 70.
276 ! ice                                   
277           aefiso(11) = 0.
278 ! tropical forest (Z88)                 
279           aefiso(12) = 3100.
280 ! savanna (Z88)                         
281           aefiso(13) = 0
282         END IF
283         IF (mminlu=='USGS') THEN
284 ! urban                                 
285           aefiso(1) = 0.
286 ! agriculture (S+R)                     
287           aefiso(2) = 8.
288 ! agriculture (S+R)                     
289           aefiso(3) = 8.
290 ! agriculture (S+R)                     
291           aefiso(4) = 8.
292 ! half agriculture/grassland assumed    
293           aefiso(5) = 4.
294 ! half agriculture/deciduous assumed    
295           aefiso(6) = 2204.
296 ! grassland (S+R)                       
297           aefiso(7) = 0.
298 ! grassland assumed                     
299           aefiso(8) = 0.
300 ! grassland assumed                     
301           aefiso(9) = 0.
302 ! savanna (Z88)                         
303           aefiso(10) = 0.
304 ! deciduous (G94)                       
305           aefiso(11) = 4400.
306 ! coniferous (G94)                      
307           aefiso(12) = 780.
308 ! deciduous (G94)                       
309           aefiso(13) = 4400.
310 ! coniferous (G94)                      
311           aefiso(14) = 780.
312 ! mixed forest (G94)                    
313           aefiso(15) = 5775.
314 ! water                                 
315           aefiso(16) = 0.
316 ! wetland emission unknown              
317           aefiso(17) = 0.
318 ! mixed forest assumed                  
319           aefiso(18) = 5775.
320 ! barren                                
321           aefiso(19) = 0.
322 ! tundra (K94) assumed                  
323           aefiso(20) = 70.
324 ! tundra (K94) assumed                  
325           aefiso(21) = 70.
326 ! tundra (K94) assumed                  
327           aefiso(22) = 70.
328 ! barren tundra                         
329           aefiso(23) = 0.
330 ! ice                                   
331           aefiso(24) = 0.
332 ! no data                               
333           aefiso(25) = 0.
334         END IF
335         IF (mminlu=='SiB ') THEN
336 ! deciduous (G94)                       
337           aefiso(1) = 4400.
338 ! deciduous (G94)                       
339           aefiso(2) = 4400.
340 ! deciduous (G94)                       
341           aefiso(3) = 4400.
342 ! coniferous (G94)                      
343           aefiso(4) = 780.
344 ! coniferous (G94)                      
345           aefiso(5) = 780.
346 ! grassland assumed                     
347           aefiso(6) = 0.
348 ! grassland assumed                     
349           aefiso(7) = 0.
350 ! grassland assumed                     
351           aefiso(8) = 0.
352 ! grassland assumed                     
353           aefiso(9) = 0.
354 ! grassland assumed                     
355           aefiso(10) = 0.
356 ! bare soil                             
357           aefiso(11) = 0.
358 ! agriculture (S+R)                     
359           aefiso(12) = 8.
360 ! wetland, emission unknown             
361           aefiso(13) = 0.
362 ! dry, coastal                          
363           aefiso(14) = 0.
364 ! water                                 
365           aefiso(15) = 0.
366 ! ice                                   
367           aefiso(16) = 0.
368 ! no data                               
369           aefiso(17) = 0.
370         END IF
371 !     ---------------------------------------------------------
372 !     Emission Factors for Monoterpenes in ug C/(m*m*h)
373 
374         IF (mminlu=='OLD ') THEN
375 ! urban                                 
376           aefmter(1) = 0.
377 ! agriculture (S+R)                     
378           aefmter(2) = 20.
379 ! grassland (S+R)                       
380           aefmter(3) = 20.
381 ! deciduous (G94)                       
382           aefmter(4) = 385.
383 ! coniferous (G94)                      
384           aefmter(5) = 1380.
385 ! mixed forest (G94)                    
386           aefmter(6) = 1001.
387 ! water                                 
388           aefmter(7) = 0.
389 ! wetland, emission unknown             
390           aefmter(8) = 0.
391 ! desert                                
392           aefmter(9) = 0.
393 ! tundra (K94)                          
394           aefmter(10) = 0.
395 ! ice                                   
396           aefmter(11) = 0.
397 ! tropical forest (Z88)                 
398           aefmter(12) = 270.
399 ! savanna (Z88)                         
400           aefmter(13) = 0
401         END IF
402         IF (mminlu=='USGS') THEN
403 ! urban                                 
404           aefmter(1) = 0.
405 ! agriculture (S+R)                     
406           aefmter(2) = 20.
407 ! agriculture (S+R)                     
408           aefmter(3) = 20.
409 ! agriculture (S+R)                     
410           aefmter(4) = 20.
411 ! half agriculture/grassland assumed    
412           aefmter(5) = 20.
413 ! half agriculture/deciduous assumed    
414           aefmter(6) = 202.5
415 ! grassland (S+R)                       
416           aefmter(7) = 20.
417 ! grassland assumed                     
418           aefmter(8) = 20.
419 ! grassland assumed                     
420           aefmter(9) = 20.
421 ! savanna (Z88)                         
422           aefmter(10) = 0
423 ! deciduous (G94)                       
424           aefmter(11) = 385.
425 ! coniferous (G94)                      
426           aefmter(12) = 1380.
427 ! deciduous (G94)                       
428           aefmter(13) = 385.
429 ! coniferous (G94)                      
430           aefmter(14) = 1380.
431 ! mixed forest (G94)                    
432           aefmter(15) = 1001.
433 ! water                                 
434           aefmter(16) = 0.
435 ! wetland emission unknown              
436           aefmter(17) = 0.
437 ! mixed forest assumed                  
438           aefmter(18) = 1001.
439 ! barren                                
440           aefmter(19) = 0.
441 ! tundra (K94) assumed                  
442           aefmter(20) = 0.
443 ! tundra (K94) assumed                  
444           aefmter(21) = 0.
445 ! tundra (K94) assumed                  
446           aefmter(22) = 0.
447 ! barren tundra                         
448           aefmter(23) = 0.
449 ! ice                                   
450           aefmter(24) = 0.
451 ! no data                               
452           aefmter(25) = 0.
453         END IF
454         IF (mminlu=='SiB ') THEN
455 ! deciduous (G94)                       
456           aefmter(1) = 385.
457 ! deciduous (G94)                       
458           aefmter(2) = 385.
459 ! deciduous (G94)                       
460           aefmter(3) = 385.
461 ! coniferous (G94)                      
462           aefmter(4) = 1380.
463 ! coniferous (G94)                      
464           aefmter(5) = 1380.
465 ! grassland assumed                     
466           aefmter(6) = 20.
467 ! grassland assumed                     
468           aefmter(7) = 20.
469 ! grassland assumed                     
470           aefmter(8) = 20.
471 ! grassland assumed                     
472           aefmter(9) = 20.
473 ! grassland assumed                     
474           aefmter(10) = 20.
475 ! bare soil                             
476           aefmter(11) = 0.
477 ! agriculture (S+R)                     
478           aefmter(12) = 20.
479 ! wetland, emission unknown             
480           aefmter(13) = 0.
481 ! dry, coastal                          
482           aefmter(14) = 0.
483 ! water                                 
484           aefmter(15) = 0.
485 ! ice                                   
486           aefmter(16) = 0.
487 ! no data                               
488           aefmter(17) = 0.
489         END IF
490 !     ---------------------------------------------------------
491 !     Emission Factors for Other VOCs in ug C/(m*m*h)
492 
493         IF (mminlu=='OLD ') THEN
494 ! urban                                 
495           aefovoc(1) = 0.
496 ! agriculture (S+R)                     
497           aefovoc(2) = 12.
498 ! grassland (S+R)                       
499           aefovoc(3) = 80.
500 ! deciduous (G94)                       
501           aefovoc(4) = 715.
502 ! coniferous (G94)                      
503           aefovoc(5) = 840.
504 ! mixed forest (G94)                    
505           aefovoc(6) = 924.
506 ! water                                 
507           aefovoc(7) = 0.
508 ! wetland, emission unknown             
509           aefovoc(8) = 0.
510 ! desert                                
511           aefovoc(9) = 0.
512 ! tundra (K94)                          
513           aefovoc(10) = 0.
514 ! ice                                   
515           aefovoc(11) = 0.
516 ! tropical forest (Z88)                 
517           aefovoc(12) = 0.
518 ! savanna (Z88)                         
519           aefovoc(13) = 0
520         END IF
521         IF (mminlu=='USGS') THEN
522 ! urban                                 
523           aefovoc(1) = 0.
524 ! agriculture (S+R)                     
525           aefovoc(2) = 12.
526 ! agriculture (S+R)                     
527           aefovoc(3) = 12.
528 ! agriculture (S+R)                     
529           aefovoc(4) = 12.
530 ! half agriculture/grassland assumed    
531           aefovoc(5) = 46.
532 ! half agriculture/deciduous assumed    
533           aefovoc(6) = 363.5
534 ! grassland (S+R)                       
535           aefovoc(7) = 80.
536 ! grassland assumed                     
537           aefovoc(8) = 80.
538 ! grassland assumed                     
539           aefovoc(9) = 80.
540 ! savanna (Z88)                         
541           aefovoc(10) = 0
542 ! deciduous (G94)                       
543           aefovoc(11) = 715.
544 ! coniferous (G94)                      
545           aefovoc(12) = 840.
546 ! deciduous (G94)                       
547           aefovoc(13) = 715.
548 ! coniferous (G94)                      
549           aefovoc(14) = 840.
550 ! mixed forest (G94)                    
551           aefovoc(15) = 924.
552 ! water                                 
553           aefovoc(16) = 0.
554 ! wetland emission unknown              
555           aefovoc(17) = 0.
556 ! mixed forest assumed                  
557           aefovoc(18) = 924.
558 ! barren                                
559           aefovoc(19) = 0.
560 ! tundra (K94) assumed                  
561           aefovoc(20) = 0.
562 ! tundra (K94) assumed                  
563           aefovoc(21) = 0.
564 ! tundra (K94) assumed                  
565           aefovoc(22) = 0.
566 ! barren tundra                         
567           aefovoc(23) = 0.
568 ! ice                                   
569           aefovoc(24) = 0.
570 ! no data                               
571           aefovoc(25) = 0.
572         END IF
573         IF (mminlu=='SiB ') THEN
574 ! deciduous (G94)                       
575           aefovoc(1) = 715.
576 ! deciduous (G94)                       
577           aefovoc(2) = 715.
578 ! deciduous (G94)                       
579           aefovoc(3) = 715.
580 ! coniferous (G94)                      
581           aefovoc(4) = 840.
582 ! coniferous (G94)                      
583           aefovoc(5) = 840.
584 ! grassland assumed                     
585           aefovoc(6) = 80.
586 ! grassland assumed                     
587           aefovoc(7) = 80.
588 ! grassland assumed                     
589           aefovoc(8) = 80.
590 ! grassland assumed                     
591           aefovoc(9) = 80.
592 ! grassland assumed                     
593           aefovoc(10) = 80.
594 ! bare soil                             
595           aefovoc(11) = 0.
596 ! agriculture (S+R)                     
597           aefovoc(12) = 12.
598 ! wetland, emission unknown             
599           aefovoc(13) = 0.
600 ! dry, coastal                          
601           aefovoc(14) = 0.
602 ! water                                 
603           aefovoc(15) = 0.
604 ! ice                                   
605           aefovoc(16) = 0.
606 ! no data                               
607           aefovoc(17) = 0.
608         END IF
609 !     ---------------------------------------------------------
610 !     Emission Factors for Nitrogen in ng N /(m*m*sec)
611 
612         IF (mminlu=='OLD ') THEN
613 ! urban                                 
614           aef_n(1) = 0.
615 ! agriculture (S+R)                     
616           aef_n(2) = 9.
617 ! grassland (S+R)                       
618           aef_n(3) = 0.9
619 ! deciduous (G94)                       
620           aef_n(4) = 0.07
621 ! coniferous (G94)                      
622           aef_n(5) = 0.07
623 ! mixed forest (G94)                    
624           aef_n(6) = 0.07
625 ! water                                 
626           aef_n(7) = 0.
627 ! wetland, emission unknown             
628           aef_n(8) = 0.
629 ! desert                                
630           aef_n(9) = 0.
631 ! tundra (K94)                          
632           aef_n(10) = 0.
633 ! ice                                   
634           aef_n(11) = 0.
635 ! tropical forest (Z88)                 
636           aef_n(12) = 1.78
637 ! savanna (Z88)                         
638           aef_n(13) = 0
639         END IF
640         IF (mminlu=='USGS') THEN
641 ! urban                                 
642           aef_n(1) = 0.
643 ! agriculture (S+R)                     
644           aef_n(2) = 9.
645 ! agriculture (S+R)                     
646           aef_n(3) = 9.
647 ! agriculture (S+R)                     
648           aef_n(4) = 9.
649 ! half agriculture/grassland assumed    
650           aef_n(5) = 4.95
651 ! half agriculture/deciduous assumed    
652           aef_n(6) = 4.535
653 ! grassland (S+R)                       
654           aef_n(7) = 0.9
655 ! grassland assumed                     
656           aef_n(8) = 0.07
657 ! grassland assumed                     
658           aef_n(9) = 0.07
659 ! savanna (Z88)                         
660           aef_n(10) = 0.
661 ! deciduous (G94)                       
662           aef_n(11) = 0.07
663 ! coniferous (G94)                      
664           aef_n(12) = 0.07
665 ! deciduous (G94)                       
666           aef_n(13) = 0.07
667 ! coniferous (G94)                      
668           aef_n(14) = 0.07
669 ! mixed forest (G94)                    
670           aef_n(15) = 0.07
671 ! water                                 
672           aef_n(16) = 0.
673 ! wetland emission unknown              
674           aef_n(17) = 0.
675 ! mixed forest assumed                  
676           aef_n(18) = 0.07
677 ! barren                                
678           aef_n(19) = 0.
679 ! tundra (K94) assumed                  
680           aef_n(20) = 0.
681 ! tundra (K94) assumed                  
682           aef_n(21) = 0.
683 ! tundra (K94) assumed                  
684           aef_n(22) = 0.
685 ! barren tundra                         
686           aef_n(23) = 0.
687 ! ice                                   
688           aef_n(24) = 0.
689 ! no data                               
690           aef_n(25) = 0.
691         END IF
692         IF (mminlu=='SiB ') THEN
693 ! deciduous (G94)                       
694           aef_n(1) = 0.07
695 ! deciduous (G94)                       
696           aef_n(2) = 0.07
697 ! deciduous (G94)                       
698           aef_n(3) = 0.07
699 ! coniferous (G94)                      
700           aef_n(4) = 0.07
701 ! coniferous (G94)                      
702           aef_n(5) = 0.07
703 ! natural vegetation assumed            
704           aef_n(6) = 0.07
705 ! grassland assumed                     
706           aef_n(7) = 0.9
707 ! natural vegetation assumed            
708           aef_n(8) = 0.07
709 ! natural vegetation assumed            
710           aef_n(9) = 0.07
711 ! natural vegetation assumed            
712           aef_n(10) = 0.07
713 ! bare soil                             
714           aef_n(11) = 0.
715 ! agriculture (S+R)                     
716           aef_n(12) = 9.
717 ! wetland, emission unknown             
718           aef_n(13) = 0.
719 ! dry, coastal                          
720           aef_n(14) = 0.
721 ! water                                 
722           aef_n(15) = 0.
723 ! ice                                   
724           aef_n(16) = 0.
725 ! no data                               
726           aef_n(17) = 0.
727         END IF
728 !     *********************************************************
729 
730 !     Simplified landuse scheme for deposition and biogenic emission
731 !     subroutines
732 !     (ISWATER and ISICE are already defined elsewhere,
733 !     therefore water and ice are not considered here)
734 
735 !     1 urban or bare soil
736 !     2 agricultural
737 !     3 grassland
738 !     4 deciduous forest
739 !     5 coniferous and mixed forest
740 !     6 other natural landuse categories
741 
742 
743         IF (mminlu=='OLD ') THEN
744           ixxxlu(1) = 1
745           ixxxlu(2) = 2
746           ixxxlu(3) = 3
747           ixxxlu(4) = 4
748           ixxxlu(5) = 5
749           ixxxlu(6) = 5
750           ixxxlu(7) = 0
751           ixxxlu(8) = 6
752           ixxxlu(9) = 1
753           ixxxlu(10) = 6
754           ixxxlu(11) = 0
755           ixxxlu(12) = 4
756           ixxxlu(13) = 6
757         END IF
758         IF (mminlu=='USGS') THEN
759           ixxxlu(1) = 1
760           ixxxlu(2) = 2
761           ixxxlu(3) = 2
762           ixxxlu(4) = 2
763           ixxxlu(5) = 2
764           ixxxlu(6) = 4
765           ixxxlu(7) = 3
766           ixxxlu(8) = 6
767           ixxxlu(9) = 3
768           ixxxlu(10) = 6
769           ixxxlu(11) = 4
770           ixxxlu(12) = 5
771           ixxxlu(13) = 4
772           ixxxlu(14) = 5
773           ixxxlu(15) = 5
774           ixxxlu(16) = 0
775           ixxxlu(17) = 6
776           ixxxlu(18) = 4
777           ixxxlu(19) = 1
778           ixxxlu(20) = 6
779           ixxxlu(21) = 4
780           ixxxlu(22) = 6
781           ixxxlu(23) = 1
782           ixxxlu(24) = 0
783           ixxxlu(25) = 1
784         END IF
785         IF (mminlu=='SiB ') THEN
786           ixxxlu(1) = 4
787           ixxxlu(2) = 4
788           ixxxlu(3) = 4
789           ixxxlu(4) = 5
790           ixxxlu(5) = 5
791           ixxxlu(6) = 6
792           ixxxlu(7) = 3
793           ixxxlu(8) = 6
794           ixxxlu(9) = 6
795           ixxxlu(10) = 6
796           ixxxlu(11) = 1
797           ixxxlu(12) = 2
798           ixxxlu(13) = 6
799           ixxxlu(14) = 1
800           ixxxlu(15) = 0
801           ixxxlu(16) = 0
802           ixxxlu(17) = 1
803         END IF
804 
805 
806 !**********************************************************************
807 ! Calculation of seasonal dependence of emissions
808 !**********************************************************************
809 ! (if the season is variable during the model run,
810 ! this section should be placed in the beginning of subroutine BIOGEN)
811 !**********************************************************************
812 
813 
814         IF (mminlu=='OLD ') THEN
815 ! WINTER                              
816           IF (isn==2) THEN
817 ! agriculture                         
818             aefiso(2) = 0.
819 ! deciduous                           
820             aefiso(4) = 0.
821 ! mixed forest                        
822             aefiso(6) = 5775./2.
823 ! tundra                              
824             aefiso(10) = 0.
825 ! agriculture                         
826             aefmter(2) = 0.
827 ! deciduous                           
828             aefmter(4) = 0.
829 ! mixed forest                        
830             aefmter(6) = 1001./2.
831 ! agriculture                         
832             aefovoc(2) = 0.
833 ! deciduous                           
834             aefovoc(4) = 0.
835 ! mixed forest                        
836             aefovoc(6) = 924./2.
837           END IF
838         END IF
839 
840         IF (mminlu=='USGS') THEN
841 !       DOES VEGETATION FRACTION EXIST?
842           sum = 0.
843 !       DO J=1,jl-1
844 !         DO I=1,il-1
845 !           SUM=SUM+VEGFRC(I,J)
846 !         END DO
847 !       END DO
848           IF (sum>1) THEN
849             vegflag = .TRUE.
850           ELSE
851             vegflag = .FALSE.
852           END IF
853 !         VEGFLAG=.FALSE.
854           IF (( .NOT. vegflag) .AND. (isn==2)) THEN
855 !       IF ((.NOT.VEGFLAG)) THEN
856 !         VEGETATION FRACTION DOES NOT EXIST,
857 !         CORRECTION FOR WINTER SEASON
858 ! agriculture                         
859             aefiso(2) = 0.
860 ! agriculture                         
861             aefiso(3) = 0.
862 ! agriculture                         
863             aefiso(4) = 0.
864 ! half agriculture/grassland assumed  
865             aefiso(5) = 0.
866 ! half agriculture/deciduous assumed  
867             aefiso(6) = 0.
868 ! deciduous broadleaf                 
869             aefiso(11) = 0.
870 ! deciduous needleleaf                
871             aefiso(12) = 0.
872 ! mixed forest                        
873             aefiso(15) = 5775./2.
874 ! mixed forest assumed                
875             aefiso(18) = 5775./2.
876 ! tundra                              
877             aefiso(20) = 0.
878 ! tundra                              
879             aefiso(21) = 0.
880 ! tundra                              
881             aefiso(22) = 0.
882 ! agriculture                         
883             aefmter(2) = 0.
884 ! agriculture                         
885             aefmter(3) = 0.
886 ! agriculture                         
887             aefmter(4) = 0.
888 ! half agriculture/grassland assumed  
889             aefmter(5) = 10.
890 ! half agriculture/deciduous assumed  
891             aefmter(6) = 0.
892 ! deciduous broadleaf                 
893             aefmter(11) = 0.
894 ! deciduous needleleaf                
895             aefmter(12) = 0.
896 ! mixed forest                        
897             aefmter(15) = 1001./2.
898 ! mixed forest assumed                
899             aefmter(18) = 1001./2.
900 ! agriculture                         
901             aefovoc(2) = 0.
902 ! agriculture                         
903             aefovoc(3) = 0.
904 ! agriculture                         
905             aefovoc(4) = 0.
906 ! half agriculture/grassland assumed  
907             aefovoc(5) = 40.
908 ! half agriculture/deciduous assumed  
909             aefovoc(6) = 0.
910 ! deciduous broadleaf                 
911             aefovoc(11) = 0.
912 ! deciduous needleleaf                
913             aefovoc(12) = 0.
914 ! mixed forest                        
915             aefovoc(15) = 924./2.
916 ! mixed forest assumed                
917             aefovoc(18) = 924./2.
918           END IF
919         END IF
920 
921         IF (mminlu=='SiB ') THEN
922 ! WINTER                              
923           IF (isn==2) THEN
924 ! deciduous                           
925             aefiso(1) = 0.
926 ! deciduous                           
927             aefiso(2) = 0.
928 ! deciduous                           
929             aefiso(3) = 0.
930 ! agriculture                         
931             aefiso(12) = 0.
932 ! deciduous                           
933             aefmter(1) = 0.
934 ! deciduous                           
935             aefmter(2) = 0.
936 ! deciduous                           
937             aefmter(3) = 0.
938 ! agriculture                         
939             aefmter(12) = 0.
940 ! deciduous                           
941             aefovoc(1) = 0.
942 ! deciduous                           
943             aefovoc(2) = 0.
944 ! deciduous                           
945             aefovoc(3) = 0.
946 ! agriculture                         
947             aefovoc(12) = 0.
948           END IF
949         END IF
950 
951       END SUBROUTINE bioemiin
952 ! **********************************************************************
953 ! ***********************  SUBROUTINE BIOGEN  **************************
954 ! **********************************************************************
955       SUBROUTINE biogen(iland,ta,rad,eiso,emter,eovoc,e_n,vocsc,eisoc,emterc, &
956           eovocc,e_nn,pa,mminlu,isn,vegflag)
957 
958 !     THIS PROGRAMM COMPUTES THE ACTUAL BIOGENIC EMISSION RATE FOR
959 !     ISOPRENE, MONTERPENES, OTHER ORGANIC COMPOUNDS, AND NITROGEN FOR
960 !     EACH GRID CELL DEPENDING ON TEMPERATURE AND GLOBAL RADIATION
961 !***********************************************************************
962 !     PROGRAM DEVELOPED BY:- THOMAS SCHOENEMEYER  (5 JANUARY 1995)
963 !     MODIFIED BY:         - THOMAS SCHOENEMEYER (21 AUGUST 1996)
964 !                            UND KLAUS RICHTER
965 !                            NACH SIMPSON ET AL.
966 !                          - WINFRIED SEIDL (JUNE 1997)
967 !                            ADAPTATION FOR USE IN MM5
968 !                          - WINFRIED SEIDL (MARCH 2000)
969 !                            MODIFICATION FOR MM5 VERSION 3
970 !                          - Georg Grell (March 2002) for f90 and WRF
971 !***********************************************************************
972 !...PROGRAM VARIABLES...
973 !        ILAND      - Land use category
974 !        TA         - Air temperature in K
975 !        RAD        - Solare global radiation in W/m2
976 !        EISO       - Emission von Isopren in ppm*m/min
977 !        EMTER      - Emission von Monoterpenen in ppm*m/min
978 !        EOVOC      - Emission sonstiger fluechtiger Kohlenwasserstoffe
979 !                      in ppm*m/min
980 !        E_N        - Emission von Stickstoff in ppm*m/min
981 !        AEFISO(NLU) - Emissionsfaktor fuer Isopren fuer die Land-
982 !                      nutzungsart K, standardisiert auf 303 K und
983 !                      voller Sonneneinstrahlung in ug C /(m*m*h)
984 !        AEFOVOC(NLU)- Emissionsfaktor fuer sonstige fluechtige
985 !                      Kohlenwasserstoffe in ug C /(m*m*h)
986 !        AEFMTER(NLU)- Emissionsfaktor fuer MONOTERPENE
987 !                      in ug C /(m*m*h)
988 !        AEF_N(NLU)  - Emissionsfaktor fuer Stickstoff
989 !                      in ng N /(m*m*sec)
990 !        ECF_ISO    - dimensionsloser Korrekturfaktor fuer Isopren,
991 !                      abhaengig von Temperatur und Strahlung
992 !        ECF_OVOC     dimensionsloser Korrekturfaktor fuer die
993 !                      sonstigen fluechtigen Kohlenwasserstoffe
994 !        ECF_MTER     dimensionsloser Korrekturfaktor fuer die
995 !                      MONOTERPENE
996 !        ECF_N      - dimensionsloser Korrekturfaktor fuer
997 !                      Stickstoff
998 ! .. Scalar Arguments ..
999         REAL :: eiso, eisoc, emter, emterc, eovoc, eovocc, e_n, e_nn, pa, rad, &
1000           ta, vocsc
1001         INTEGER :: iland, isn
1002         LOGICAL :: vegflag
1003         CHARACTER (4) :: mminlu
1004 ! ..
1005 ! .. Array Arguments ..
1006 !       REAL :: aefiso(nlu), aefmter(nlu), aefovoc(nlu), aef_n(nlu)
1007 !       INTEGER :: ixxxlu(nlu)
1008 ! ..
1009 ! .. Local Scalars ..
1010         REAL :: alpha, beta, cl, cl1, coniso, conn, conovoc, conter, ct, ct1, &
1011           ct2, ecf_iso, ecf_mter, ecf_n, ecf_ovoc, par, r, rat, tm, ts, tsoil
1012 ! ..
1013 ! .. Intrinsic Functions ..
1014         INTRINSIC exp, sqrt
1015 ! ..
1016 ! empirischer Koeffizient                     
1017         alpha = 0.0027
1018 ! empirischer Koeffizient                     
1019         cl1 = 1.066
1020 ! Gaskonstante in J/(K*mol)                   
1021         r = 8.314
1022 ! empirischer Koeffizient in J/mol            
1023         ct1 = 95000
1024 ! empirischer Koeffizient in J/mol            
1025         ct2 = 230000
1026 ! empirischer Koeffizient in K                
1027         tm = 314.
1028 ! faktoren bestimmt werden
1029         ts = 303.
1030 ! Standardtemperatur bei der Emissions-       
1031         beta = 0.09
1032 !**********************************************************************
1033 !**********************************************************************
1034 !  Temperature and Radiation Dependent Correction Factors
1035 !  for Emissions
1036 !**********************************************************************
1037 !**********************************************************************
1038 
1039 
1040 !     *****************************************************************
1041 !     Forest land use categories
1042 
1043 ! empirischer TemperaturKoeffizient           
1044         IF ((ixxxlu(iland)==4) .OR. (ixxxlu(iland)==5)) THEN
1045 !                             ! = photosynthetisch aktive Strahlung;
1046           par = 2.0*rad
1047 !                             ! Umrechnungsfaktor: 2.0 uE/J (beruecksich
1048 ! auch, dass PAR ein kleinerer Wellenlaeng
1049 ! bereich ist als die Globalstrahlung.
1050 ! Langholz und Haeckl, 1985, Met. Rundscha
1051 
1052 ! PAR flux in Mikromol je m**2 und s      
1053           cl = alpha*cl1*par/sqrt(1+alpha*alpha*par*par)
1054           ct = exp(ct1*(ta-ts)/(r*ts*ta))/(1+exp(ct2*(ta-tm)/(r*ts*ta)))
1055 
1056           ecf_iso = cl*ct
1057 ! Korrekturfaktor fuer Isopr
1058           ecf_mter = exp(beta*(ta-ts)) ! Korrekturfaktor fuer MTER 
1059           ecf_ovoc = ecf_mter
1060 ! Korrekturfaktor fuer OVOC 
1061           tsoil = 0.84*(ta-273.15) + 3.6
1062           ecf_n = exp(0.071*tsoil)
1063 ! Korrekturfaktor fuer N    
1064         END IF
1065 
1066 !     *****************************************************************
1067 !     Agricultural land use category
1068 
1069         IF (ixxxlu(iland)==2) THEN
1070           ecf_iso = exp(0.1*(ta-30.-273.15)) ! vgl. Hahn et al. 
1071           ecf_mter = ecf_iso
1072           ecf_ovoc = ecf_iso
1073 
1074           tsoil = 0.72*(ta-273.15) + 5.8
1075           ecf_n = exp(0.071*tsoil)
1076         END IF
1077 
1078 !     *****************************************************************
1079 !     Grassland and natural nonforested land use categories
1080 
1081         IF ((ixxxlu(iland)==3) .OR. (ixxxlu(iland)==6)) THEN
1082           ecf_iso = exp(0.1*(ta-30.-273.15)) ! vgl. Hahn et al. 
1083           ecf_mter = ecf_iso
1084           ecf_ovoc = ecf_iso
1085 
1086           tsoil = 0.66*(ta-273.15) + 8.8
1087           ecf_n = exp(0.071*tsoil)
1088         END IF
1089 
1090 !     *****************************************************************
1091 !     Non-emitting land use categories
1092 
1093         IF ((ixxxlu(iland)==1) .OR. (iland==iswater_temp) .OR. (iland==isice_temp)) THEN
1094           ecf_iso = 0.
1095           ecf_mter = 0.
1096           ecf_ovoc = 0.
1097           ecf_n = 0.
1098         END IF
1099 !**********************************************************************
1100 !**********************************************************************
1101 !  Calculation of Emissions
1102 !**********************************************************************
1103 !**********************************************************************
1104 
1105 !       CONVERSION FROM MICROGRAM C/M2/H TO PPM*M/MIN
1106 !       CORRECTION TERM FOR TEMP(K)  AND PRESSURE
1107 !       K = (T/P) *R)/(MW*60)
1108 !       R = 8.3143E-2 m3 mbar/(K mole)
1109 
1110         rat = ta/pa
1111 !     *****************************************************************
1112 !     Isopren:
1113 
1114         coniso = rat*2.3095E-5
1115         eisoc = aefiso(iland)*ecf_iso
1116         eiso = coniso*eisoc
1117 
1118 !     *****************************************************************
1119 !     Monoterpenes:
1120 
1121         conter = rat*1.1548E-5
1122         emterc = aefmter(iland)*ecf_mter
1123         emter = conter*emterc
1124 
1125 !     *****************************************************************
1126 !     Other VOCs:
1127 
1128 !     as 3-hexenyl-acetate (C=96g/mole)
1129 
1130         conovoc = rat*1.4435E-5
1131         eovocc = aefovoc(iland)*ecf_ovoc
1132         eovoc = conovoc*eovocc
1133 !     *****************************************************************
1134 !     SUM OF ALL VOCS
1135 
1136         vocsc = eisoc + emterc + eovocc
1137 
1138 !     *****************************************************************
1139 !     Nitrogen:
1140 
1141 !       CONVERSION FROM NANOGRAM N/M2/SEC TO PPM*M/MIN
1142 !       CORRECTION TERM FOR TEMP(K)  AND PRESSURE
1143 !       INVENTORY AS N
1144 !       INPUT TO THE MODEL ASSUMED AS NO
1145 !       K = (T/P) *R*60)/(MW*1000)
1146 !       R = 8.3143E-2 m3 mbar/(K mole)
1147 
1148         conn = rat*3.5633E-4
1149         e_nn = aef_n(iland)*ecf_n
1150         e_n = conn*e_nn
1151 
1152 
1153       END SUBROUTINE biogen
1154 ! **********************************************************************
1155 ! ***********************  SUBROUTINE BIOSPLIT *************************
1156 ! **********************************************************************
1157       SUBROUTINE biosplit(iland,eiso,emter,eovoc,e_n,emiss_bio,numgas, &
1158           vegfrc,mminlu,vegflag)
1159 !     THIS PROGRAMM SPLITS THE BIOGENIC EMISSION RATES FOR
1160 !     MONOTERPENES AND OTHER ORGANIC COMPOUNDS INTO THE
1161 !     COMPOUND CLASSES OF THE CHEMISTRY MODEL
1162 !     --- VERSION FOR RADM2 AND RACM CHEMISTRY ---
1163 !***********************************************************************
1164 !     PROGRAM DEVELOPED BY:- WINFRIED SEIDL  (JULY 1997)
1165 !     MODIFIED BY:         - WINFRIED SEIDL  (JULY 1998)
1166 !                            FOR RACM-CHEMISTRY
1167 !                          - WINFRIED SEIDL  (MARCH 2000)
1168 !                            FOR MM5 VERSION 3
1169 !***********************************************************************
1170 !...PROGRAM VARIABLES...
1171 !        ILAND      - Land use category
1172 !        EISO       - Emission von Isopren in ppm*m/min
1173 !        EMTER      - Emission von Monoterpenen in ppm*m/min
1174 !        EOVOC      - Emission sonstiger fluechtiger Kohlenwasserstoffe
1175 !                      in ppm*m/min
1176 !        E_N        - Emission von Stickstoff in ppm*m/min
1177 !***********************************************************************
1178 !...Comments...
1179 !        The split of the monoterpenes and the other VOCs into RADM clas
1180 !        is mostly rather uncertain. Every plant species emitts a differ
1181 !        mix of chemical substances. So e.g. different types of deciduou
1182 !        trees show totally different emissions. By taking the MM5
1183 !        land use categories, the kind of biogenic emissions can be
1184 !        estimated only roughly. Especially for the other VOCs little
1185 !        is known, so the splits presented here have to be regarded as
1186 !        a preliminary assumption.
1187 !        Some literature on this field:
1188 !        Arey et al., J. Geophys. Res. 96D (1991), 9329-9336
1189 !        Arey et al., Atmospheric Environment 25A (1991), 1063-1075
1190 !        Koenig et al., Atmospheric Environment 29 (1995), 861-874
1191 !        Isidorov et al., Atmospheric Environment 19 (1985), 1-8
1192 !        Martin et al., Abstract Air & Waste Management Association''s
1193 !        90th Annual Meeting & Exhibition, Toronto 1997, Paper 97-RP139.
1194 !        Winer et al., Final Report 1983, California Air Resources Bord,
1195 !        Contract No. AO-056-32
1196 !        For the RADM 2 chemistry, most of the monoterpenes are grouped
1197 !        into the OLI class
1198 !        (Middleton et al., Atmospheric Environment 24A (1990), 1107-113
1199 !        with a few exceptions:
1200 !        ISO -- myrcene, ocimene
1201 !        XYL -- p-cymene
1202 !        For the RACM chemistry, the monoterpenes are split
1203 !        between the API, LIM, ISO and XYL classes:
1204 !        API -- a-pinene, b-pinene, D3-carene, sabinene, camphene,
1205 !               1,8-cineole, a-terpineole, thujene
1206 !        LIM -- limonene, terpinene, phellandrene, terpinolene
1207 !        ISO -- myrcene, ocimene
1208 !        XYL -- p-cymene
1209 !        The other VOCs are grouped according to Middleton et al. (1990)
1210 !***********************************************************************
1211 ! .. Scalar Arguments ..
1212         REAL :: eiso, emter, eovoc, e_n, vegfrc
1213         INTEGER :: iland, numgas
1214 !       INTEGER :: lald, lhc3, lhc5, lhc8, lhcho, liso, lket, lno, &
1215 !         loli, lolt, lora1, lora2, lxyl
1216 ! ..
1217 ! .. Array Arguments ..
1218         REAL :: emiss_bio(numgas)
1219 !       INTEGER :: ixxxlu(nlu)
1220 ! ..
1221 ! .. Local Scalars ..
1222         LOGICAL :: vegflag
1223         CHARACTER (4) :: mminlu
1224 ! ..
1225 !     *****************************************************************
1226 !     Correction for vegetation fraction
1227         IF ((mminlu=='USGS') .AND. (vegflag)) THEN
1228           eiso = eiso*vegfrc/100.
1229           emter = emter*vegfrc/100.
1230           eovoc = eovoc*vegfrc/100.
1231         END IF
1232 
1233 !     *****************************************************************
1234 !     Isoprene and NO
1235 
1236         emiss_bio(liso) = eiso
1237         emiss_bio(lno) = emiss_bio(lno) + e_n
1238 
1239 !     *****************************************************************
1240 !     Agricultural land
1241 
1242         IF (ixxxlu(iland)==2) THEN
1243           emiss_bio(loli) = emiss_bio(loli) + 0.80*emter
1244           emiss_bio(liso) = emiss_bio(liso) + 0.20*emter
1245           emiss_bio(lhc5) = emiss_bio(lhc5) + 0.16*eovoc
1246           emiss_bio(lhc8) = emiss_bio(lhc8) + 0.27*eovoc
1247           emiss_bio(lolt) = emiss_bio(lolt) + 0.05*eovoc
1248           emiss_bio(loli) = emiss_bio(loli) + 0.37*eovoc
1249           emiss_bio(lket) = emiss_bio(lket) + 0.03*eovoc
1250           emiss_bio(lald) = emiss_bio(lald) + 0.12*eovoc
1251         END IF
1252 
1253 !     *****************************************************************
1254 !     Grassland
1255 
1256         IF (ixxxlu(iland)==3) THEN
1257           emiss_bio(loli) = emiss_bio(loli) + 0.98*emter
1258           emiss_bio(liso) = emiss_bio(liso) + 0.02*emter
1259           emiss_bio(lhc5) = emiss_bio(lhc5) + 0.09*eovoc
1260           emiss_bio(lolt) = emiss_bio(lolt) + 0.07*eovoc
1261           emiss_bio(loli) = emiss_bio(loli) + 0.51*eovoc
1262           emiss_bio(lket) = emiss_bio(lket) + 0.15*eovoc
1263           emiss_bio(lald) = emiss_bio(lald) + 0.18*eovoc
1264         END IF
1265 
1266 !     *****************************************************************
1267 !     Deciduous forest
1268 
1269         IF (ixxxlu(iland)==4) THEN
1270           emiss_bio(loli) = emiss_bio(loli) + 0.94*emter
1271           emiss_bio(liso) = emiss_bio(liso) + 0.02*emter
1272           emiss_bio(lhcho) = emiss_bio(lhcho) + 0.19*eovoc
1273           emiss_bio(lald) = emiss_bio(lald) + 0.13*eovoc
1274           emiss_bio(lxyl) = emiss_bio(lxyl) + 0.04*emter
1275           emiss_bio(lhc5) = emiss_bio(lhc5) + 0.03*eovoc
1276           emiss_bio(loli) = emiss_bio(loli) + 0.07*eovoc
1277           emiss_bio(lora1) = emiss_bio(lora1) + 0.23*eovoc
1278           emiss_bio(lora2) = emiss_bio(lora2) + 0.35*eovoc
1279         END IF
1280 
1281 !     *****************************************************************
1282 !     Coniferous forest and mixed forest
1283 
1284 
1285         IF (ixxxlu(iland)==5) THEN
1286           emiss_bio(loli) = emiss_bio(loli) + 0.85*emter
1287           emiss_bio(liso) = emiss_bio(liso) + 0.15*emter
1288           emiss_bio(lhcho) = emiss_bio(lhcho) + 0.04*eovoc
1289           emiss_bio(lald) = emiss_bio(lald) + 0.14*eovoc
1290           emiss_bio(lhc3) = emiss_bio(lhc3) + 0.07*eovoc
1291           emiss_bio(lhc5) = emiss_bio(lhc5) + 0.07*eovoc
1292           emiss_bio(lolt) = emiss_bio(lolt) + 0.07*eovoc
1293           emiss_bio(loli) = emiss_bio(loli) + 0.50*eovoc
1294           emiss_bio(lket) = emiss_bio(lket) + 0.03*eovoc
1295           emiss_bio(lora1) = emiss_bio(lora1) + 0.03*eovoc
1296           emiss_bio(lora2) = emiss_bio(lora2) + 0.05*eovoc
1297         END IF
1298 
1299 !     *****************************************************************
1300 !     Tropical forest (not available in SiB and USGS)
1301 
1302         IF ((mminlu=='OLD ') .AND. (iland==12)) THEN
1303           emiss_bio(loli) = emiss_bio(loli) + emter
1304         END IF
1305 
1306       END SUBROUTINE biosplit
1307 
1308     END MODULE module_bioemi_simple