1 MODULE module_bioemi_simple
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
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)
16 SUBROUTINE bio_emissions(id,ktau,dtstep,DX, &
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 ids,ide, jds,jde, kds,kde, &
22 ims,ime, jms,jme, kms,kme, &
23 its,ite, jts,jte, kts,kte )
25 USE module_state_description
27 INTEGER, INTENT(IN ) :: id,julday, ne_area, &
28 ids,ide, jds,jde, kds,kde, &
29 ims,ime, jms,jme, kms,kme, &
30 its,ite, jts,jte, kts,kte
31 INTEGER, INTENT(IN ) :: &
33 REAL, DIMENSION( ims:ime, kms:kme, jms:jme, num_moist ), &
35 REAL, DIMENSION( ims:ime, kms:kme, jms:jme, num_chem ), &
36 INTENT(INOUT ) :: chem
37 REAL, DIMENSION( ims:ime, jms:jme, ne_area ), &
38 INTENT(INOUT ) :: e_bio
39 REAL, DIMENSION( ims:ime , kms:kme , jms:jme ) , &
46 INTEGER,DIMENSION( ims:ime , jms:jme ) , &
49 REAL, DIMENSION( ims:ime , jms:jme ) , &
58 REAL, INTENT(IN ) :: &
60 !--- deposition and emissions stuff
62 TYPE(grid_config_rec_type), INTENT(IN ) :: config_flags
67 ! INTEGER, PARAMETER :: nlu = 25, &
68 ! nseason = 1, nseasons = 2
69 ! REAL :: aefiso(nlu), aefmter(nlu), aefovoc(nlu), aef_n(nlu)
70 REAL :: emiss_bio(ne_area) !wig, 1-May-2007: switched to ne_area from numgas to make more general
71 LOGICAL :: highnh3, rainflag, vegflag, wetflag
72 CHARACTER (4) :: luse_typ
75 REAL :: clwchem,eiso,eisoc,emter,emterc,eovoc,eovocc,e_n,e_nn, &
76 pa,rad, rhchem, ta, ustar, vegfrac, vocsc, xtimin, z1,zntt
77 INTEGER :: i,j,iland, iprt, iseason, n, nr, ipr,jpr,nvr
80 ! .. Intrinsic Functions ..
84 ! print *,'luse_typ,iswater',luse_typ,iswater_temp
86 if(julday.lt.90.or.julday.gt.270)then
88 CALL wrf_debug(100,'setting iseason in bio_emi to 2')
92 ! test program to test chemics stuff in 1-d
94 ! first prepare for biogenic emissions
96 CALL bioemiin(iseason,luse_typ,vegflag)
102 vegfrac = vegfra(i,j)
103 pa = .01*p_phy(i,kts,j)
104 clwchem = moist(i,kts,j,p_qc)
107 z1 = z_at_w(i,kts+1,j)-z_at_w(i,kts,j)
109 ! Set logical default values
114 if(moist(i,kts,j,p_qr).gt.0.)rainflag = .true.
115 ! if(raincv(i,kts,j).gt.0. .and. rainncv(i,kts,j).gt.0. )rainflag = .true.
117 ! qvs = 380.*exp(17.27*(tair-273.)/(tair-36.))/pressure
118 rhchem = MIN( 100.,100. * moist(i,kts,j,p_qv) / &
119 (3.80*exp(17.27*(t_phy(i,kts,j)-273.)/(t_phy(i,kts,j)-36.))/pa))
120 rhchem = max(rhchem,5.)
121 if (rhchem >= 95.) wetflag = .true.
122 ! print *,chem(i,kts,j,p_nh3),chem(i,kts,j,p_so2)
123 if(chem(i,kts,j,p_nh3).gt.2.*chem(i,kts,j,p_so2))highnh3 = .true.
125 !--- biogenic emissions
127 CALL biogen(iland,ta,rad,eiso,emter,eovoc,e_n,vocsc,eisoc,emterc,eovocc, &
128 e_nn,pa,luse_typ,iseason,vegflag)
129 ! if(i.eq.5.and.j.eq.5)then
131 ! print *,ta,rad,vocsc,pa,luse_typ,aefiso,aefovoc,aefmter, &
132 ! aef_n,ixxxlu,vegflag,isice_temp,iswater_temp
133 ! PRINT *, eiso, emter, eovoc, e_n, eisoc, eovocc
136 ! PRINT *, eiso, emter, eovoc, e_n, eisoc, eovocc
137 CALL biosplit(iland,eiso,emter,eovoc,e_n,emiss_bio,ne_area,vegfrac, &
138 config_flags, luse_typ,vegflag)
139 ! PRINT *, 'emiss_bio(liso) emiss_bio(lald) emiss_bio(lhcho) ', &
141 ! PRINT *, emiss_bio(liso), emiss_bio(lald), emiss_bio(lhcho), &
144 e_bio(i,j,n) = emiss_bio(n)
145 ! if(i.eq.5.and.j.eq.5)print *,emiss_bio(n)
148 END SUBROUTINE bio_emissions
149 ! **********************************************************************
150 ! ********************** SUBROUTINE BIOEMIIN **************************
151 ! **********************************************************************
152 SUBROUTINE bioemiin(isn,mminlu,vegflag)
153 !**********************************************************************
154 ! THIS SUBROUTINE INITIALIZES THE EMISSION FACTORS
155 ! AND THE SIMPLIFIED LANDUSE SCHEME
156 ! FOR THE BIOGENIC EMISSION AND DEPOSITION SUBROUTINES
157 ! WRITTEN BY: WINFRIED SEIDL (MARCH 2000)
160 !**********************************************************************
161 !**********************************************************************
162 ! REFERENCES FOR EMISSION FACTORS:
163 ! (S+R) T. Schoenemeyer and K. Richter
164 ! (S95) D. Simpson, A. Guenther, C. N. Hewitt, and R. Steinbrecher
165 ! J. Geophysical Research 100D (1995), 22875-22890
166 ! (G94) A. Guenther, P. Zimmerman and M. Wildermuth
167 ! Atmospheric Environment 28 (1994), 1197-1210
168 ! (Z88) P. R. Zimmerman, J. P. Greenberg, and C. E. Westberg
169 ! J. Geophysical Research 93D (1988), 1407-1416
170 ! (K88) W. A. Kaplan, S. C. Wofsy, M. Keller, and J. M. da Costa
171 ! J. Geophysical Research 93D (1988), 1389-1395
172 ! (K94) L. F. Klinger, P. R. Zimmermann, J. P. Greenberg, L. E. Hei
174 ! J. Geophysical Research 99D (1994), 1469-1494
175 ! ---------------------------------------------------------
176 ! PCU/NCAR landuse categories:
177 ! 1 Highrise urban area
178 ! 2 Agricultural land
179 ! 3 Grassland, rangeland
181 ! 5 Coniferous forest
182 ! 6 Mixed forest (including wetland)
184 ! 8 Wet rangeland, nonforested wetland
188 ! 12 Tropical forest land
190 ! ---------------------------------------------------------
191 ! USGS landuse categories:
192 ! 1 Urban and built-up land
193 ! 2 Dryland cropland and pasture
194 ! 3 Irrigated cropland and pasture
195 ! 4 Mix. dry/irrg. cropland and pasture
196 ! 5 Cropland/grassland mosaic
197 ! 6 Cropland/woodland mosaic
200 ! 9 Mixed shrubland/grassland
202 ! 11 Deciduous broadleaf forest
203 ! 12 Deciduous needleleaf forest
204 ! 13 Evergreen broadleaf forest
205 ! 14 Evergreen needleleaf forest
208 ! 17 Herbaceous wetland
210 ! 19 Barren or sparsely vegetated
211 ! 20 Herbaceous Tundra
214 ! 23 Bare Ground Tundra
217 ! ---------------------------------------------------------
218 ! SiB landuse categories:
219 ! 1 Evergreen broadleaf trees
220 ! 2 Broadleaf deciduous trees
221 ! 3 Deciduous and evergreen trees
222 ! 4 Evergreen needleleaf trees
223 ! 5 Deciduous needleleaf trees
224 ! 6 Ground cover with trees and shrubs
225 ! 7 Ground cover only
226 ! 8 Broadleaf shrub with Perennial ground cover
227 ! 9 Broadleaf shrub with bare soil
228 ! 10 Groundcover with dwarf trees and shrubs
230 ! 12 Agriculture or C3 grassland
231 ! 13 Persistent Wetland
232 ! 14 Dry coastal complexes
234 ! 16 Ice cap and glacier
236 !--------------------------------------------------------------
237 ! .. Scalar Arguments ..
239 CHARACTER (4) :: mminlu
242 ! .. Array Arguments ..
243 ! REAL :: aefiso(nlu), aefmter(nlu), aefovoc(nlu), aef_n(nlu)
244 ! INTEGER :: ixxxlu(nlu)
246 ! .. Local Scalars ..
250 !**********************************************************************
251 ! Emission Factors for Isoprene in ug C/(m*m*h)
252 ! PRINT *, 'mminlu = ', mminlu
253 IF (mminlu=='OLD ') THEN
268 ! wetland, emission unknown
276 ! tropical forest (Z88)
281 IF (mminlu=='USGS') THEN
290 ! half agriculture/grassland assumed
292 ! half agriculture/deciduous assumed
314 ! wetland emission unknown
316 ! mixed forest assumed
320 ! tundra (K94) assumed
322 ! tundra (K94) assumed
324 ! tundra (K94) assumed
333 IF (mminlu=='SiB ') THEN
358 ! wetland, emission unknown
369 ! ---------------------------------------------------------
370 ! Emission Factors for Monoterpenes in ug C/(m*m*h)
372 IF (mminlu=='OLD ') THEN
387 ! wetland, emission unknown
395 ! tropical forest (Z88)
400 IF (mminlu=='USGS') THEN
409 ! half agriculture/grassland assumed
411 ! half agriculture/deciduous assumed
433 ! wetland emission unknown
435 ! mixed forest assumed
439 ! tundra (K94) assumed
441 ! tundra (K94) assumed
443 ! tundra (K94) assumed
452 IF (mminlu=='SiB ') THEN
477 ! wetland, emission unknown
488 ! ---------------------------------------------------------
489 ! Emission Factors for Other VOCs in ug C/(m*m*h)
491 IF (mminlu=='OLD ') THEN
506 ! wetland, emission unknown
514 ! tropical forest (Z88)
519 IF (mminlu=='USGS') THEN
528 ! half agriculture/grassland assumed
530 ! half agriculture/deciduous assumed
552 ! wetland emission unknown
554 ! mixed forest assumed
558 ! tundra (K94) assumed
560 ! tundra (K94) assumed
562 ! tundra (K94) assumed
571 IF (mminlu=='SiB ') THEN
596 ! wetland, emission unknown
607 ! ---------------------------------------------------------
608 ! Emission Factors for Nitrogen in ng N /(m*m*sec)
610 IF (mminlu=='OLD ') THEN
625 ! wetland, emission unknown
633 ! tropical forest (Z88)
638 IF (mminlu=='USGS') THEN
647 ! half agriculture/grassland assumed
649 ! half agriculture/deciduous assumed
671 ! wetland emission unknown
673 ! mixed forest assumed
677 ! tundra (K94) assumed
679 ! tundra (K94) assumed
681 ! tundra (K94) assumed
690 IF (mminlu=='SiB ') THEN
701 ! natural vegetation assumed
705 ! natural vegetation assumed
707 ! natural vegetation assumed
709 ! natural vegetation assumed
715 ! wetland, emission unknown
726 ! *********************************************************
728 ! Simplified landuse scheme for deposition and biogenic emission
730 ! (ISWATER and ISICE are already defined elsewhere,
731 ! therefore water and ice are not considered here)
733 ! 1 urban or bare soil
737 ! 5 coniferous and mixed forest
738 ! 6 other natural landuse categories
741 IF (mminlu=='OLD ') THEN
756 IF (mminlu=='USGS') THEN
783 IF (mminlu=='SiB ') THEN
804 !**********************************************************************
805 ! Calculation of seasonal dependence of emissions
806 !**********************************************************************
807 ! (if the season is variable during the model run,
808 ! this section should be placed in the beginning of subroutine BIOGEN)
809 !**********************************************************************
812 IF (mminlu=='OLD ') THEN
828 aefmter(6) = 1001./2.
838 IF (mminlu=='USGS') THEN
839 ! DOES VEGETATION FRACTION EXIST?
843 ! SUM=SUM+VEGFRC(I,J)
852 IF (( .NOT. vegflag) .AND. (isn==2)) THEN
853 ! IF ((.NOT.VEGFLAG)) THEN
854 ! VEGETATION FRACTION DOES NOT EXIST,
855 ! CORRECTION FOR WINTER SEASON
862 ! half agriculture/grassland assumed
864 ! half agriculture/deciduous assumed
866 ! deciduous broadleaf
868 ! deciduous needleleaf
871 aefiso(15) = 5775./2.
872 ! mixed forest assumed
873 aefiso(18) = 5775./2.
886 ! half agriculture/grassland assumed
888 ! half agriculture/deciduous assumed
890 ! deciduous broadleaf
892 ! deciduous needleleaf
895 aefmter(15) = 1001./2.
896 ! mixed forest assumed
897 aefmter(18) = 1001./2.
904 ! half agriculture/grassland assumed
906 ! half agriculture/deciduous assumed
908 ! deciduous broadleaf
910 ! deciduous needleleaf
913 aefovoc(15) = 924./2.
914 ! mixed forest assumed
915 aefovoc(18) = 924./2.
919 IF (mminlu=='SiB ') THEN
949 END SUBROUTINE bioemiin
950 ! **********************************************************************
951 ! *********************** SUBROUTINE BIOGEN **************************
952 ! **********************************************************************
953 SUBROUTINE biogen(iland,ta,rad,eiso,emter,eovoc,e_n,vocsc,eisoc,emterc, &
954 eovocc,e_nn,pa,mminlu,isn,vegflag)
956 ! THIS PROGRAMM COMPUTES THE ACTUAL BIOGENIC EMISSION RATE FOR
957 ! ISOPRENE, MONTERPENES, OTHER ORGANIC COMPOUNDS, AND NITROGEN FOR
958 ! EACH GRID CELL DEPENDING ON TEMPERATURE AND GLOBAL RADIATION
959 !***********************************************************************
960 ! PROGRAM DEVELOPED BY:- THOMAS SCHOENEMEYER (5 JANUARY 1995)
961 ! MODIFIED BY: - THOMAS SCHOENEMEYER (21 AUGUST 1996)
963 ! NACH SIMPSON ET AL.
964 ! - WINFRIED SEIDL (JUNE 1997)
965 ! ADAPTATION FOR USE IN MM5
966 ! - WINFRIED SEIDL (MARCH 2000)
967 ! MODIFICATION FOR MM5 VERSION 3
968 ! - Georg Grell (March 2002) for f90 and WRF
969 !***********************************************************************
970 !...PROGRAM VARIABLES...
971 ! ILAND - Land use category
972 ! TA - Air temperature in K
973 ! RAD - Solare global radiation in W/m2
974 ! EISO - Emission von Isopren in ppm*m/min
975 ! EMTER - Emission von Monoterpenen in ppm*m/min
976 ! EOVOC - Emission sonstiger fluechtiger Kohlenwasserstoffe
978 ! E_N - Emission von Stickstoff in ppm*m/min
979 ! AEFISO(NLU) - Emissionsfaktor fuer Isopren fuer die Land-
980 ! nutzungsart K, standardisiert auf 303 K und
981 ! voller Sonneneinstrahlung in ug C /(m*m*h)
982 ! AEFOVOC(NLU)- Emissionsfaktor fuer sonstige fluechtige
983 ! Kohlenwasserstoffe in ug C /(m*m*h)
984 ! AEFMTER(NLU)- Emissionsfaktor fuer MONOTERPENE
986 ! AEF_N(NLU) - Emissionsfaktor fuer Stickstoff
988 ! ECF_ISO - dimensionsloser Korrekturfaktor fuer Isopren,
989 ! abhaengig von Temperatur und Strahlung
990 ! ECF_OVOC dimensionsloser Korrekturfaktor fuer die
991 ! sonstigen fluechtigen Kohlenwasserstoffe
992 ! ECF_MTER dimensionsloser Korrekturfaktor fuer die
994 ! ECF_N - dimensionsloser Korrekturfaktor fuer
996 ! .. Scalar Arguments ..
997 REAL :: eiso, eisoc, emter, emterc, eovoc, eovocc, e_n, e_nn, pa, rad, &
999 INTEGER :: iland, isn
1001 CHARACTER (4) :: mminlu
1003 ! .. Array Arguments ..
1004 ! REAL :: aefiso(nlu), aefmter(nlu), aefovoc(nlu), aef_n(nlu)
1005 ! INTEGER :: ixxxlu(nlu)
1007 ! .. Local Scalars ..
1008 REAL :: alpha, beta, cl, cl1, coniso, conn, conovoc, conter, ct, ct1, &
1009 ct2, ecf_iso, ecf_mter, ecf_n, ecf_ovoc, par, r, rat, tm, ts, tsoil
1011 ! .. Intrinsic Functions ..
1014 ! empirischer Koeffizient
1016 ! empirischer Koeffizient
1018 ! Gaskonstante in J/(K*mol)
1020 ! empirischer Koeffizient in J/mol
1022 ! empirischer Koeffizient in J/mol
1024 ! empirischer Koeffizient in K
1026 ! faktoren bestimmt werden
1028 ! Standardtemperatur bei der Emissions-
1030 !**********************************************************************
1031 !**********************************************************************
1032 ! Temperature and Radiation Dependent Correction Factors
1034 !**********************************************************************
1035 !**********************************************************************
1038 ! *****************************************************************
1039 ! Forest land use categories
1041 ! empirischer TemperaturKoeffizient
1042 IF ((ixxxlu(iland)==4) .OR. (ixxxlu(iland)==5)) THEN
1043 ! ! = photosynthetisch aktive Strahlung;
1045 ! ! Umrechnungsfaktor: 2.0 uE/J (beruecksich
1046 ! auch, dass PAR ein kleinerer Wellenlaeng
1047 ! bereich ist als die Globalstrahlung.
1048 ! Langholz und Haeckl, 1985, Met. Rundscha
1050 ! PAR flux in Mikromol je m**2 und s
1051 cl = alpha*cl1*par/sqrt(1+alpha*alpha*par*par)
1052 ct = exp(ct1*(ta-ts)/(r*ts*ta))/(1+exp(ct2*(ta-tm)/(r*ts*ta)))
1055 ! Korrekturfaktor fuer Isopr
1056 ecf_mter = exp(beta*(ta-ts)) ! Korrekturfaktor fuer MTER
1058 ! Korrekturfaktor fuer OVOC
1059 tsoil = 0.84*(ta-273.15) + 3.6
1060 ecf_n = exp(0.071*tsoil)
1061 ! Korrekturfaktor fuer N
1064 ! *****************************************************************
1065 ! Agricultural land use category
1067 IF (ixxxlu(iland)==2) THEN
1068 ecf_iso = exp(0.1*(ta-30.-273.15)) ! vgl. Hahn et al.
1072 tsoil = 0.72*(ta-273.15) + 5.8
1073 ecf_n = exp(0.071*tsoil)
1076 ! *****************************************************************
1077 ! Grassland and natural nonforested land use categories
1079 IF ((ixxxlu(iland)==3) .OR. (ixxxlu(iland)==6)) THEN
1080 ecf_iso = exp(0.1*(ta-30.-273.15)) ! vgl. Hahn et al.
1084 tsoil = 0.66*(ta-273.15) + 8.8
1085 ecf_n = exp(0.071*tsoil)
1088 ! *****************************************************************
1089 ! Non-emitting land use categories
1091 IF ((ixxxlu(iland)==1) .OR. (iland==iswater_temp) .OR. (iland==isice_temp)) THEN
1097 !**********************************************************************
1098 !**********************************************************************
1099 ! Calculation of Emissions
1100 !**********************************************************************
1101 !**********************************************************************
1103 ! CONVERSION FROM MICROGRAM C/M2/H TO PPM*M/MIN
1104 ! CORRECTION TERM FOR TEMP(K) AND PRESSURE
1105 ! K = (T/P) *R)/(MW*60)
1106 ! R = 8.3143E-2 m3 mbar/(K mole)
1109 ! *****************************************************************
1112 coniso = rat*2.3095E-5
1113 eisoc = aefiso(iland)*ecf_iso
1116 ! *****************************************************************
1119 conter = rat*1.1548E-5
1120 emterc = aefmter(iland)*ecf_mter
1121 emter = conter*emterc
1123 ! *****************************************************************
1126 ! as 3-hexenyl-acetate (C=96g/mole)
1128 conovoc = rat*1.4435E-5
1129 eovocc = aefovoc(iland)*ecf_ovoc
1130 eovoc = conovoc*eovocc
1131 ! *****************************************************************
1134 vocsc = eisoc + emterc + eovocc
1136 ! *****************************************************************
1139 ! CONVERSION FROM NANOGRAM N/M2/SEC TO PPM*M/MIN
1140 ! CORRECTION TERM FOR TEMP(K) AND PRESSURE
1142 ! INPUT TO THE MODEL ASSUMED AS NO
1143 ! K = (T/P) *R*60)/(MW*1000)
1144 ! R = 8.3143E-2 m3 mbar/(K mole)
1146 conn = rat*3.5633E-4
1147 e_nn = aef_n(iland)*ecf_n
1151 END SUBROUTINE biogen
1152 ! **********************************************************************
1153 ! *********************** SUBROUTINE BIOSPLIT *************************
1154 ! **********************************************************************
1155 SUBROUTINE biosplit(iland,eiso,emter,eovoc,e_n,emiss_bio,ne_area, &
1157 config_flags, mminlu,vegflag)
1158 ! THIS PROGRAMM SPLITS THE BIOGENIC EMISSION RATES FOR
1159 ! MONOTERPENES AND OTHER ORGANIC COMPOUNDS INTO THE
1160 ! COMPOUND CLASSES OF THE CHEMISTRY MODEL
1161 ! --- VERSION FOR RADM2 AND RACM CHEMISTRY ---
1162 !***********************************************************************
1163 ! PROGRAM DEVELOPED BY:- WINFRIED SEIDL (JULY 1997)
1164 ! MODIFIED BY: - WINFRIED SEIDL (JULY 1998)
1165 ! FOR RACM-CHEMISTRY
1166 ! - WINFRIED SEIDL (MARCH 2000)
1168 !***********************************************************************
1169 !...PROGRAM VARIABLES...
1170 ! ILAND - Land use category
1171 ! EISO - Emission von Isopren in ppm*m/min
1172 ! EMTER - Emission von Monoterpenen in ppm*m/min
1173 ! EOVOC - Emission sonstiger fluechtiger Kohlenwasserstoffe
1175 ! E_N - Emission von Stickstoff in ppm*m/min
1176 !***********************************************************************
1178 ! The split of the monoterpenes and the other VOCs into RADM clas
1179 ! is mostly rather uncertain. Every plant species emitts a differ
1180 ! mix of chemical substances. So e.g. different types of deciduou
1181 ! trees show totally different emissions. By taking the MM5
1182 ! land use categories, the kind of biogenic emissions can be
1183 ! estimated only roughly. Especially for the other VOCs little
1184 ! is known, so the splits presented here have to be regarded as
1185 ! a preliminary assumption.
1186 ! Some literature on this field:
1187 ! Arey et al., J. Geophys. Res. 96D (1991), 9329-9336
1188 ! Arey et al., Atmospheric Environment 25A (1991), 1063-1075
1189 ! Koenig et al., Atmospheric Environment 29 (1995), 861-874
1190 ! Isidorov et al., Atmospheric Environment 19 (1985), 1-8
1191 ! Martin et al., Abstract Air & Waste Management Association''s
1192 ! 90th Annual Meeting & Exhibition, Toronto 1997, Paper 97-RP139.
1193 ! Winer et al., Final Report 1983, California Air Resources Bord,
1194 ! Contract No. AO-056-32
1195 ! For the RADM 2 chemistry, most of the monoterpenes are grouped
1196 ! into the OLI class
1197 ! (Middleton et al., Atmospheric Environment 24A (1990), 1107-113
1198 ! with a few exceptions:
1199 ! ISO -- myrcene, ocimene
1201 ! For the RACM chemistry, the monoterpenes are split
1202 ! between the API, LIM, ISO and XYL classes:
1203 ! API -- a-pinene, b-pinene, D3-carene, sabinene, camphene,
1204 ! 1,8-cineole, a-terpineole, thujene
1205 ! LIM -- limonene, terpinene, phellandrene, terpinolene
1206 ! ISO -- myrcene, ocimene
1208 ! The other VOCs are grouped according to Middleton et al. (1990)
1209 !***********************************************************************
1210 USE module_configure
1211 USE module_state_description
1213 TYPE(grid_config_rec_type), INTENT(IN ) :: config_flags
1216 ! .. Scalar Arguments ..
1217 REAL :: eiso, emter, eovoc, e_n, vegfrc
1218 INTEGER :: iland, ne_area
1219 ! INTEGER :: lald, lhc3, lhc5, lhc8, lhcho, liso, lket, lno, &
1220 ! loli, lolt, lora1, lora2, lxyl
1222 ! .. Array Arguments ..
1223 REAL :: emiss_bio(ne_area)
1224 ! INTEGER :: ixxxlu(nlu)
1226 ! .. Local Scalars ..
1228 CHARACTER (4) :: mminlu
1230 ! *****************************************************************
1231 ! Correction for vegetation fraction
1232 IF ((mminlu=='USGS') .AND. (vegflag)) THEN
1233 eiso = eiso*vegfrc/100.
1234 emter = emter*vegfrc/100.
1235 eovoc = eovoc*vegfrc/100.
1238 ! *****************************************************************
1241 emiss_bio(liso) = eiso
1242 emiss_bio(lno) = emiss_bio(lno) + e_n
1244 if (config_flags%chem_opt == CB05_SORG_AQ_KPP .OR. &
1245 config_flags%chem_opt == CB05_SORG_VBS_AQ_KPP ) then
1247 emiss_bio(ltpan) = emter ! Use tpan to represent terpene
1249 ! *****************************************************************
1252 IF (ixxxlu(iland)==2) THEN
1253 emiss_bio(lhc5) = emiss_bio(lhc5) + 0.16*eovoc
1254 emiss_bio(lhc8) = emiss_bio(lhc8) + 0.27*eovoc
1255 emiss_bio(lolt) = emiss_bio(lolt) + 0.05*eovoc
1256 emiss_bio(loli) = emiss_bio(loli) + 0.37*eovoc
1257 emiss_bio(lket) = emiss_bio(lket) + 0.03*eovoc
1258 emiss_bio(lald) = emiss_bio(lald) + 0.12*eovoc
1261 ! *****************************************************************
1264 IF (ixxxlu(iland)==3) THEN
1265 emiss_bio(lhc5) = emiss_bio(lhc5) + 0.09*eovoc
1266 emiss_bio(lolt) = emiss_bio(lolt) + 0.07*eovoc
1267 emiss_bio(loli) = emiss_bio(loli) + 0.51*eovoc
1268 emiss_bio(lket) = emiss_bio(lket) + 0.15*eovoc
1269 emiss_bio(lald) = emiss_bio(lald) + 0.18*eovoc
1272 ! *****************************************************************
1275 IF (ixxxlu(iland)==4) THEN
1276 emiss_bio(lhcho) = emiss_bio(lhcho) + 0.19*eovoc
1277 emiss_bio(lald) = emiss_bio(lald) + 0.13*eovoc
1278 emiss_bio(lxyl) = emiss_bio(lxyl) + 0.04*emter
1279 emiss_bio(lhc5) = emiss_bio(lhc5) + 0.03*eovoc
1280 emiss_bio(loli) = emiss_bio(loli) + 0.07*eovoc
1281 emiss_bio(lora1) = emiss_bio(lora1) + 0.23*eovoc
1282 emiss_bio(lora2) = emiss_bio(lora2) + 0.35*eovoc
1285 ! *****************************************************************
1286 ! Coniferous forest and mixed forest
1289 IF (ixxxlu(iland)==5) THEN
1290 emiss_bio(lhcho) = emiss_bio(lhcho) + 0.04*eovoc
1291 emiss_bio(lhcho) = emiss_bio(lhcho) + 0.04*eovoc
1292 emiss_bio(lald) = emiss_bio(lald) + 0.14*eovoc
1293 emiss_bio(lhc3) = emiss_bio(lhc3) + 0.07*eovoc
1294 emiss_bio(lhc5) = emiss_bio(lhc5) + 0.07*eovoc
1295 emiss_bio(lolt) = emiss_bio(lolt) + 0.07*eovoc
1296 emiss_bio(loli) = emiss_bio(loli) + 0.50*eovoc
1297 emiss_bio(lket) = emiss_bio(lket) + 0.03*eovoc
1298 emiss_bio(lora1) = emiss_bio(lora1) + 0.03*eovoc
1299 emiss_bio(lora2) = emiss_bio(lora2) + 0.05*eovoc
1305 ! *****************************************************************
1308 IF (ixxxlu(iland)==2) THEN
1309 emiss_bio(loli) = emiss_bio(loli) + 0.80*emter
1310 emiss_bio(liso) = emiss_bio(liso) + 0.20*emter
1311 emiss_bio(lhc5) = emiss_bio(lhc5) + 0.16*eovoc
1312 emiss_bio(lhc8) = emiss_bio(lhc8) + 0.27*eovoc
1313 emiss_bio(lolt) = emiss_bio(lolt) + 0.05*eovoc
1314 emiss_bio(loli) = emiss_bio(loli) + 0.37*eovoc
1315 emiss_bio(lket) = emiss_bio(lket) + 0.03*eovoc
1316 emiss_bio(lald) = emiss_bio(lald) + 0.12*eovoc
1319 ! *****************************************************************
1322 IF (ixxxlu(iland)==3) THEN
1323 emiss_bio(loli) = emiss_bio(loli) + 0.98*emter
1324 emiss_bio(liso) = emiss_bio(liso) + 0.02*emter
1325 emiss_bio(lhc5) = emiss_bio(lhc5) + 0.09*eovoc
1326 emiss_bio(lolt) = emiss_bio(lolt) + 0.07*eovoc
1327 emiss_bio(loli) = emiss_bio(loli) + 0.51*eovoc
1328 emiss_bio(lket) = emiss_bio(lket) + 0.15*eovoc
1329 emiss_bio(lald) = emiss_bio(lald) + 0.18*eovoc
1332 ! *****************************************************************
1335 IF (ixxxlu(iland)==4) THEN
1336 emiss_bio(loli) = emiss_bio(loli) + 0.94*emter
1337 emiss_bio(liso) = emiss_bio(liso) + 0.02*emter
1338 emiss_bio(lhcho) = emiss_bio(lhcho) + 0.19*eovoc
1339 emiss_bio(lald) = emiss_bio(lald) + 0.13*eovoc
1340 emiss_bio(lxyl) = emiss_bio(lxyl) + 0.04*emter
1341 emiss_bio(lhc5) = emiss_bio(lhc5) + 0.03*eovoc
1342 emiss_bio(loli) = emiss_bio(loli) + 0.07*eovoc
1343 emiss_bio(lora1) = emiss_bio(lora1) + 0.23*eovoc
1344 emiss_bio(lora2) = emiss_bio(lora2) + 0.35*eovoc
1347 ! *****************************************************************
1348 ! Coniferous forest and mixed forest
1351 IF (ixxxlu(iland)==5) THEN
1352 emiss_bio(loli) = emiss_bio(loli) + 0.85*emter
1353 emiss_bio(liso) = emiss_bio(liso) + 0.15*emter
1354 emiss_bio(lhcho) = emiss_bio(lhcho) + 0.04*eovoc
1355 emiss_bio(lald) = emiss_bio(lald) + 0.14*eovoc
1356 emiss_bio(lhc3) = emiss_bio(lhc3) + 0.07*eovoc
1357 emiss_bio(lhc5) = emiss_bio(lhc5) + 0.07*eovoc
1358 emiss_bio(lolt) = emiss_bio(lolt) + 0.07*eovoc
1359 emiss_bio(loli) = emiss_bio(loli) + 0.50*eovoc
1360 emiss_bio(lket) = emiss_bio(lket) + 0.03*eovoc
1361 emiss_bio(lora1) = emiss_bio(lora1) + 0.03*eovoc
1362 emiss_bio(lora2) = emiss_bio(lora2) + 0.05*eovoc
1365 ! *****************************************************************
1366 ! Tropical forest (not available in SiB and USGS)
1368 IF ((mminlu=='OLD ') .AND. (iland==12)) THEN
1369 emiss_bio(loli) = emiss_bio(loli) + emter
1374 END SUBROUTINE biosplit
1376 END MODULE module_bioemi_simple