/[MITgcm]/MITgcm_contrib/jscott/igsm/src_chem/chemmeta.F
ViewVC logotype

Annotation of /MITgcm_contrib/jscott/igsm/src_chem/chemmeta.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.1 - (hide annotations) (download)
Thu Sep 17 17:40:32 2009 UTC (15 years, 10 months ago) by jscott
Branch: MAIN
CVS Tags: HEAD
chem module archive

1 jscott 1.1
2     #include "ctrparam.h"
3    
4     ! ============================================================
5     !
6     ! CHEMMETA.F: Interface between CliChem and META Models.
7     !
8     ! ------------------------------------------------------------
9     !
10     ! Author: Chien Wang
11     ! MIT Joint Program on Science and Policy
12     ! of Global Change
13     !
14     ! ----------------------------------------------------------
15     !
16     ! Revision History:
17     !
18     ! When Who What
19     ! ---- ---------- -------
20     ! 062999 Chien Wang using time evolution data
21     ! for urban partition
22     ! 120799 Chien Wang use real temperature in meta
23     ! 052200 Chien Wang use urban daily emission data
24     ! 080200 Chien Wang repack based on CliChem3 & add cpp
25     ! 051804 Chien Wang back to the v58
26     !
27     ! ==========================================================
28    
29     ! ===================
30     subroutine chemmeta
31     ! ===================
32    
33     parameter (ktop = 2)
34    
35     #include "chem_para"
36     #include "chem_const1"
37    
38     #include "chem_com"
39     #include "chem_meta"
40     #include "BD2G04.COM"
41    
42     common U,V,T,P,Q
43    
44     real Temp
45     real tmp(meta_nvar), conv0, conv, x11(ktop), xxx
46     real r_so2, r_co, r_nox, r_voc
47     real ymass_no, ymass_no2, ymass_o3, ymass_hno3,
48     & ymass_n2o5,ymass_co, ymass_ch2o
49     real yflux_no, yflux_no2, yflux_o3, yflux_hno3,
50     & yflux_n2o5,yflux_co, yflux_ch2o
51     real urban_area,rural_area,total_area
52    
53     integer ind_lat(nlat), id_lat, jid
54    
55     ! --------------------------------------------
56     ! rlati: |lat| in degree (0:65)
57     ! rtemp: deviation from normal temperature (-10:10)
58     ! rclou: tenth of mean cloud coverage (0:10)
59     ! rmixi: maximum mixing layer top in meter (200:2000)
60     ! rtime: residence time 200km/U in second (21600:259200)
61     ! rso2: emission of SO2 in kg/km^2/day
62     ! rco: emission of SO2 in kg/km^2/day
63     ! rnox: emission of SO2 in kg/km^2/day
64     ! rvoc: deviation from total daily VOC emission (-0.7:0.7)
65     ! raqino
66     ! raqinoo
67     ! raqivoc
68     ! raqiozo
69     ! raqisox
70     ! results(meta_nvar)
71     !
72     ! --- Order of results and others:
73     ! ---
74     ! --- 1: NO mass
75     ! --- 2: NO flux
76     ! --- 3: NO2 mass
77     ! --- 4: NO2 flux
78     ! --- 5: O3 mass
79     ! --- 6: O3 flux
80     ! --- 7: HONO flux
81     ! --- 8: HNO3 flux
82     ! --- 9: N2O5 flux
83     ! --- 10: CO mass
84     ! --- 11: CO flux
85     ! --- 12: HCHO mass
86     ! --- 13: HCHO flux
87     ! --- 14: ALD2 mass
88     ! --- 15: MEK mass
89     ! --- 16: PAN flux
90     ! --- 17: ALKA mass
91     ! --- 18: ETHE mass
92     ! --- 19: ALKE mass
93     ! --- 20: TOLU mass
94     ! --- 21: AROM mass
95     ! --- 22: SO2 mass
96     ! --- 23: SO2 flux
97     ! --- 24: SO3 mass
98     ! --- 25: SO3 flux
99     ! --- 26: O3 max
100     ! --- 27: O3 peak hour
101     ! --- Daily averaged mass
102     ! --- 28: NO
103     ! --- 29: NO2
104     ! --- 30: O3
105     ! --- 31: HONO
106     ! --- 32: HNO3
107     ! --- 33: HNO4
108     ! --- 34: N2O5
109     ! --- 35: NO3
110     ! --- 36: HO2
111     ! --- 37: CO
112     ! --- 38: HCHO
113     ! --- 39: ALD2
114     ! --- 40: MEK
115     ! --- 41: MGLY
116     ! --- 42: PAN
117     ! --- 43: RO2
118     ! --- 44: MCO3
119     ! --- 45: ALKN
120     ! --- 46: ALKA
121     ! --- 47: ETHE
122     ! --- 48: ALKE
123     ! --- 49: TOLU
124     ! --- 50: AROM
125     ! --- 51: DIAL
126     ! --- 52: CRES
127     ! --- 53: NPHE
128     ! --- 54: H2O2
129     ! --- 55: MEOH
130     ! --- 56: ETOH
131     ! --- 57: SO2
132     ! --- 58: SO3
133     ! ----------------------------------------------------
134     !
135     #if ( defined CPL_CHEM ) && ( defined CPL_META )
136    
137     ! --- All metamodel calls and calculations are applied
138     ! --- to latitudes ranged from -39 to 63 degree
139     ! --- or j=8,20 in GACM grid index, though arrays
140     ! --- are still indexed from 1 to nlat.
141     id_lat = 0
142     do j=1,nlat
143     ind_lat(j) = 0
144     end do
145    
146     #if ( N_LAT == 24 )
147     do j=8,20
148     #endif
149     #if ( N_LAT == 46 )
150     do j=14,39
151     #endif
152     if ( n_total_urban(j,myyear) .ne. 0 ) then
153     id_lat = id_lat + 1
154     ind_lat(id_lat) = j
155     endif
156     end do
157    
158     do 10 jid = 1,id_lat
159     j = ind_lat(jid)
160    
161     do ntype = 1,3
162     do iii = 1,meta_nvar
163     results_meta(iii,ntype,j) = 0.0
164     end do
165     end do
166    
167     cldcvr = 0.0
168     do k=2,6
169     xxx = chem_cldss(1,j,k) + chem_cldmc(1,j,k)
170     & - chem_cldss(1,j,k) * chem_cldmc(1,j,k)
171     ! if(xxx.gt.1.0) xxx = 1.0
172     if(xxx.gt.0.9) xxx = 0.9
173     if(xxx.lt.0.0) xxx = 0.0
174     if(xxx.gt.cldcvr)cldcvr = xxx
175     end do
176    
177     rtemp(j) = 0.0
178    
179     ! --- cloud coverage in tenth
180     rclou(j) = cldcvr*10.0
181    
182     ! --- m, top of layer 2
183     rmixi(j) = 1500.0
184    
185     ! --- 21600 < time < 259200, fixed size of 200 km
186     rtime(j) = 2.e5/max(0.771605, abs(pvv(1,j,1)))
187     if(rtime(j).lt. 21600.0) rtime(j) = 21600.0
188     if(rtime(j).gt.259200.0) rtime(j) = 259200.0
189    
190     urban_area = float(n_total_urban(j,myyear))*4.e10
191     total_area = 1./dxyp(j)
192     urban_area = urban_area*total_area
193     rural_area = 1.0 - urban_area
194     if (rural_area .le. 0.0) then
195     rural_area = 0.0
196     urban_area = 1.0
197     end if
198    
199     tmass = 0.0 !Total air mass in kg
200     do k=1,ktop
201     tmass = tmass + airmass(1,j,k)
202     enddo
203     tmass = 1./tmass
204    
205     ymass_no = 0.0
206     ymass_no2 = 0.0
207     ymass_o3 = 0.0
208     ymass_hno3 = 0.0
209     ymass_n2o5 = 0.0
210     ymass_co = 0.0
211     ymass_ch2o = 0.0
212     yflux_no = 0.0
213     yflux_no2 = 0.0
214     yflux_o3 = 0.0
215     yflux_hno3 = 0.0
216     yflux_n2o5 = 0.0
217     yflux_co = 0.0
218     yflux_ch2o = 0.0
219    
220     ! --- convert daily emission for a 95x95 km^2 "core"
221     ! from 10^-9 kg to kg/km^2
222     ! conv0 = 1.e-9/(95x95)/n
223     !
224     conv0 = 1.10803e-13
225     & /(float(n_total_urban(j,myyear)))
226    
227     do 20 ntype=1,3 ! 3 different types
228    
229     if (n_urban(ntype,j,myyear).ne.0) then
230    
231     ! --- decide the emission strength of
232     ! --- different types of cities
233     if (n_total_urban(j,myyear).lt.4)then
234     conv = conv0*urban_beta_1(ntype)
235     else if (n_total_urban(j,myyear).lt.20)then
236     conv = conv0*urban_beta_2(ntype)
237     else
238     conv = conv0*urban_beta_3(ntype)
239     end if
240    
241     ! r_so2 = edailyso2(1,j,myyear)*alpha_so2(j)
242     r_so2 = edailyusox(1,j,myyear)
243     & * conv
244    
245     ! r_co = edailyco (1,j,myyear)*alpha_co (j,myyear)
246     r_co = edailyuco (1,j,myyear)
247     & * conv
248    
249     ! r_nox = edailynox(1,j,myyear)*alpha_nox(j,myyear)
250     r_nox = edailyunox(1,j,myyear)
251     & * conv
252    
253     ! r_voc = 0.0
254     r_voc = edailyunmv(1,j,myyear)
255     & * conv
256    
257     Temp = T(1,j,1)*airpress(1)**0.286
258    
259     ! --- jday =julian day [1,365]
260     xxx = float(jday)
261    
262     call metamodel( Temp, j_date,
263     & rlati(j),rtemp(j),rclou(j),
264     & rmixi(j),rtime(j),
265     & r_so2, r_co, r_nox, r_voc,
266     & raqino (ntype,j),raqinoo(ntype,j),
267     & raqivoc(ntype,j),raqiozo(ntype,j),
268     & raqisox(ntype,j),tmp)
269    
270     !
271     ! if(myyear.eq.1.and.mymonth.eq.8)then
272     ! print *,"ntype = ",ntype, "j = ",j
273     ! print *,"AQINO = ",raqino(ntype,j),"AQINO2 = ",raqinoo(ntype,j)
274     ! print *,"AQIVOC = ",raqivoc(ntype,j),"AQIOZO = ",raqiozo(ntype,j)
275     ! print *,"AQISOX = ",raqisox(ntype,j)
276     ! endif
277     !
278    
279     ! --- convert mass and flux from kg/km^2 to kg
280     do iii=1,25
281     results_meta(iii,ntype,j)=
282     & tmp(iii)*n_urban(ntype,j,myyear)*4.e4
283     & *( 1.0 + sin(3.1415926
284     & *(xxx - xc_meta(iii))/w_meta(iii))
285     & /c_meta(iii) )
286     &
287     end do
288     results_meta(26,ntype,j) = tmp(26)
289     & *( 1.0 + sin(3.1415926
290     & *(xxx - xc_meta(26))/w_meta(26))
291     & /c_meta(26) )
292     results_meta(27,ntype,j) = tmp(27)
293    
294     do iii=28,meta_nvar
295     results_meta(iii,ntype,j)=
296     & tmp(iii)*n_urban(ntype,j,myyear)*4.e4
297     & *( 1.0 + sin(3.1415926
298     & *(xxx - xc_meta(iii))/w_meta(iii))/c_meta(iii) )
299     end do
300    
301    
302     ! --- all results should be positive definite
303     do iii=1,meta_nvar
304     if(results_meta(iii,ntype,j).le.0.0)
305     & results_meta(iii,ntype,j) = 0.0
306     end do
307    
308     ! --- convert flux to kg (mass is already in kg)
309     ! Note: CO and NO fluxes have been included
310     ! in chememission.F, they should not be recounted here
311     ! Note also: ymass mixing with the grid model is no longer
312     ! needed so that both meta and grid calculates its own
313     ! concentration, only connection is the yflux
314     ! This has been tested via eppa02 May 2004.
315     ! Chien Wang 062304
316     !
317     ! ymass_no = ymass_no
318     ! & + results_meta(1,ntype,j)
319     ! ymass_no2 = ymass_no2
320     ! & + results_meta(3,ntype,j)
321     yflux_no2 = yflux_no2
322     & + results_meta(4,ntype,j)
323     ! ymass_o3 = ymass_o3
324     ! & + results_meta(5,ntype,j)
325     yflux_o3 = yflux_o3
326     & + results_meta(6,ntype,j)
327     yflux_hno3 = yflux_hno3
328     & + results_meta(8,ntype,j)
329     yflux_n2o5 = yflux_n2o5
330     & + results_meta(9,ntype,j)
331     ! ymass_co = ymass_co
332     ! & + results_meta(10,ntype,j)
333     ! ymass_ch2o = ymass_ch2o
334     ! & + results_meta(12,ntype,j)
335     yflux_ch2o = yflux_ch2o
336     & + results_meta(13,ntype,j)
337     end if
338    
339     20 continue
340    
341     ! ---
342     ! --- incorperating meta results into mixing ratios:
343     ! ---
344     ! --- NO
345     do k=1,ktop
346     x11(k) = xno (1,j,k)
347     enddo
348     call chemmeta_mass(1,j,ktop,tmass,
349     & urban_area,rural_area,
350     & ymass_no,yflux_no,x11)
351     do k=1,ktop
352     xno(1,j,k) = x11(k)
353     enddo
354    
355     ! --- NO2
356     do k=1,ktop
357     x11(k) = xno2(1,j,k)
358     enddo
359     call chemmeta_mass(1,j,ktop,tmass,
360     & urban_area,rural_area,
361     & ymass_no2,yflux_no2,x11)
362     do k=1,ktop
363     xno2(1,j,k) = x11(k)
364     enddo
365    
366     ! --- O3
367     do k=1,ktop
368     x11(k) = o3 (1,j,k)
369     enddo
370     call chemmeta_mass(1,j,ktop,tmass,
371     & urban_area,rural_area,
372     & ymass_o3,yflux_o3,x11)
373     do k=1,ktop
374     o3 (1,j,k) = x11(k)
375     enddo
376    
377     ! --- HNO3
378     do k=1,ktop
379     x11(k) = hno3 (1,j,k)
380     enddo
381     call chemmeta_mass(1,j,ktop,tmass,
382     & urban_area,rural_area,
383     & ymass_hno3,yflux_hno3,x11)
384     do k=1,ktop
385     hno3(1,j,k) = x11(k)
386     enddo
387    
388     ! --- N2O5
389     do k=1,ktop
390     x11(k) = xn2o5(1,j,k)
391     enddo
392     call chemmeta_mass(1,j,ktop,tmass,
393     & urban_area,rural_area,
394     & ymass_n2o5,yflux_n2o5,x11)
395     do k=1,ktop
396     xn2o5(1,j,k) = x11(k)
397     enddo
398    
399     ! --- CO
400     do k=1,ktop
401     x11(k) = co(1,j,k)
402     enddo
403     call chemmeta_mass(1,j,ktop,tmass,
404     & urban_area,rural_area,
405     & ymass_co,yflux_co,x11)
406     do k=1,ktop
407     co(1,j,k) = x11(k)
408     enddo
409    
410     ! --- HCHO
411     do k=1,ktop
412     x11(k) = ch2o(1,j,k)
413     enddo
414     call chemmeta_mass(1,j,ktop,tmass,
415     & urban_area,rural_area,
416     & ymass_ch2o,yflux_ch2o,x11)
417     do k=1,ktop
418     ch2o(1,j,k) = x11(k)
419     enddo
420    
421     ! ===
422     ! === convert mass into mole fraction in ppb
423     ! ===
424     conv0 = tmass/urban_area*28.97296245*1.e9
425     do ntype=1,3
426     if(n_urban(ntype,j,myyear).gt.0)then
427     conv = conv0*float(n_total_urban(j,myyear))
428     & /float(n_urban(ntype,j,myyear))
429     ! --- 1: NO mass
430     results_meta(1,ntype,j) =
431     & results_meta(1,ntype,j)
432     & /awNO*conv
433     ! --- 3: NO2 mass
434     results_meta(3,ntype,j) =
435     & results_meta(3,ntype,j)
436     & /awNO2*conv
437     ! --- 5: O3 mass
438     results_meta(5,ntype,j) =
439     & results_meta(5,ntype,j)
440     & /awO3*conv
441     ! --- 10: CO mass
442     results_meta(10,ntype,j) =
443     & results_meta(10,ntype,j)
444     & /awCO*conv
445     ! --- 12: HCHO mass
446     results_meta(12,ntype,j) =
447     & results_meta(12,ntype,j)
448     & /awCH2O*conv
449     ! --- 14: ALD2 mass
450     results_meta(14,ntype,j) =
451     & results_meta(14,ntype,j)
452     & /awALD2*conv
453     ! --- 15: MEK mass
454     results_meta(15,ntype,j) =
455     & results_meta(15,ntype,j)
456     & /awMEK*conv
457     ! --- 17: ALKA mass
458     results_meta(17,ntype,j) =
459     & results_meta(17,ntype,j)
460     & /awALKA*conv
461     ! --- 18: ETHE mass
462     results_meta(18,ntype,j) =
463     & results_meta(18,ntype,j)
464     & /awETHE*conv
465     ! --- 19: ALKE mass
466     results_meta(19,ntype,j) =
467     & results_meta(19,ntype,j)
468     & /awALKE*conv
469     ! --- 20: TOLU mass
470     results_meta(20,ntype,j) =
471     & results_meta(20,ntype,j)
472     & /awTOLU*conv
473     ! --- 21: AROM mass
474     results_meta(21,ntype,j) =
475     & results_meta(21,ntype,j)
476     & /awAROM*conv
477     ! --- 22: SO2 mass
478     results_meta(22,ntype,j) =
479     & results_meta(22,ntype,j)
480     & /awSO2*conv
481     ! --- 24: SO3 mass
482     results_meta(24,ntype,j) =
483     & results_meta(24,ntype,j)
484     & /awSO3*conv
485     ! --- 28: NO daily-mean mass
486     results_meta(28,ntype,j) =
487     & results_meta(28,ntype,j)
488     & /awNO*conv
489     ! --- 29: NO2 daily-mean mass
490     results_meta(29,ntype,j) =
491     & results_meta(29,ntype,j)
492     & /awNO2*conv
493     ! --- 30: O3 daily-mean mass
494     results_meta(30,ntype,j) =
495     & results_meta(30,ntype,j)
496     & /awO3*conv
497     ! --- 31: HONO daily-mean mass
498     results_meta(31,ntype,j) =
499     & results_meta(31,ntype,j)
500     & /awHONO*conv
501     ! --- 32: HNO3 daily-mean mass
502     results_meta(32,ntype,j) =
503     & results_meta(32,ntype,j)
504     & /awHNO3*conv
505     ! --- 33: HNO4 daily-mean mass
506     results_meta(33,ntype,j) =
507     & results_meta(33,ntype,j)
508     & /awHNO4*conv
509     ! --- 34: N2O5 daily-mean mass
510     results_meta(34,ntype,j) =
511     & results_meta(34,ntype,j)
512     & /awN2O5*conv
513     ! --- 35: NO3 daily-mean mass
514     results_meta(35,ntype,j) =
515     & results_meta(35,ntype,j)
516     & /awNO3*conv
517     ! --- 36: HO2 daily-mean mass
518     results_meta(36,ntype,j) =
519     & results_meta(36,ntype,j)
520     & /awHO2*conv
521     ! --- 37: CO daily-mean mass
522     results_meta(37,ntype,j) =
523     & results_meta(37,ntype,j)
524     & /awCO*conv
525     ! --- 38: HCHO daily-mean mass
526     results_meta(38,ntype,j) =
527     & results_meta(38,ntype,j)
528     & /awCH2O*conv
529     ! --- 39: ALD2 daily-mean mass
530     results_meta(39,ntype,j) =
531     & results_meta(39,ntype,j)
532     & /awALD2*conv
533     ! --- 40: MEK daily-mean mass
534     results_meta(40,ntype,j) =
535     & results_meta(40,ntype,j)
536     & /awMEK*conv
537     ! --- 42: PAN daily-mean mass
538     results_meta(42,ntype,j) =
539     & results_meta(42,ntype,j)
540     & /awPAN*conv
541     ! --- 46: ALKA daily-mean mass
542     results_meta(46,ntype,j) =
543     & results_meta(46,ntype,j)
544     & /awALKA*conv
545     ! --- 47: ETHE daily-mean mass
546     results_meta(47,ntype,j) =
547     & results_meta(47,ntype,j)
548     & /awETHE*conv
549     ! --- 48: ALKE daily-mean mass
550     results_meta(48,ntype,j) =
551     & results_meta(48,ntype,j)
552     & /awALKE*conv
553     ! --- 49: TOLU daily-mean mass
554     results_meta(49,ntype,j) =
555     & results_meta(49,ntype,j)
556     & /awTOLU*conv
557     ! --- 50: AROM daily-mean mass
558     results_meta(50,ntype,j) =
559     & results_meta(50,ntype,j)
560     & /awAROM*conv
561     ! --- 54: H2O2 daily-mean mass
562     results_meta(54,ntype,j) =
563     & results_meta(54,ntype,j)
564     & /awH2O2*conv
565     ! --- 57: SO2 daily-mean mass
566     results_meta(57,ntype,j) =
567     & results_meta(57,ntype,j)
568     & /awSO2*conv
569     ! --- 58: SO3 daily-mean mass
570     results_meta(58,ntype,j) =
571     & results_meta(58,ntype,j)
572     & /awSO3*conv
573     else
574     results_meta(1, ntype,j) = 0.0
575     results_meta(3, ntype,j) = 0.0
576     results_meta(5, ntype,j) = 0.0
577     results_meta(10,ntype,j) = 0.0
578     results_meta(12,ntype,j) = 0.0
579     results_meta(14,ntype,j) = 0.0
580     results_meta(15,ntype,j) = 0.0
581     results_meta(17,ntype,j) = 0.0
582     results_meta(18,ntype,j) = 0.0
583     results_meta(19,ntype,j) = 0.0
584     results_meta(20,ntype,j) = 0.0
585     results_meta(21,ntype,j) = 0.0
586     results_meta(22,ntype,j) = 0.0
587     results_meta(24,ntype,j) = 0.0
588     results_meta(28,ntype,j) = 0.0
589     results_meta(29,ntype,j) = 0.0
590     results_meta(30,ntype,j) = 0.0
591     results_meta(31,ntype,j) = 0.0
592     results_meta(32,ntype,j) = 0.0
593     results_meta(33,ntype,j) = 0.0
594     results_meta(34,ntype,j) = 0.0
595     results_meta(35,ntype,j) = 0.0
596     results_meta(36,ntype,j) = 0.0
597     results_meta(37,ntype,j) = 0.0
598     results_meta(38,ntype,j) = 0.0
599     results_meta(39,ntype,j) = 0.0
600     results_meta(40,ntype,j) = 0.0
601     results_meta(42,ntype,j) = 0.0
602     results_meta(46,ntype,j) = 0.0
603     results_meta(47,ntype,j) = 0.0
604     results_meta(48,ntype,j) = 0.0
605     results_meta(49,ntype,j) = 0.0
606     results_meta(50,ntype,j) = 0.0
607     results_meta(54,ntype,j) = 0.0
608     results_meta(57,ntype,j) = 0.0
609     results_meta(58,ntype,j) = 0.0
610     endif
611     end do
612    
613     10 continue
614    
615     do j=1,nlat
616     do ntype=1,3
617     do i=1,meta_nvar
618     results_mon(i,ntype,j) = results_mon (i,ntype,j)
619     & + results_meta(i,ntype,j)
620     end do
621     end do
622     end do
623    
624     nstep_meta = nstep_meta + 1
625    
626     #endif
627    
628     return
629     end
630    
631    
632     ! ===============================================
633     subroutine chemmeta_mass(i,j,ktop,tmass1,
634     & urban_area,rural_area,
635     & ymass, yflux, x11)
636     ! ===============================================
637    
638     ! --------------------------------------------------------
639     ! A subroutine for recalculating zonal mean mixing ratrios
640     ! by incorperating GACM and META results
641     ! --------------------------------------------------------
642    
643     #include "chem_para"
644     #include "chem_com"
645    
646     #include "chem_meta"
647    
648     #include "BD2G04.COM"
649    
650     dimension x11(ktop)
651     real urban_area, rural_area, xmass, xmix
652    
653     #if ( defined CPL_CHEM ) && ( defined CPL_META )
654    
655     xmass = 0.0 !rural tracer mass in 10^-9 kg
656     do k=1,ktop
657     xmass = xmass
658     & + airmass(i,j,k)*x11(k)
659     end do
660    
661     ! === PM scheme
662     ! xmix = ( rural_area*xmass +
663     !! & (urban_area*ymass + yflux)*1.e9 )
664     ! & (ymass + yflux)*1.e9 )
665     ! & * tmass1 !ppbm
666     ! === FM scheme
667     xmix = ( xmass +
668     & (ymass + yflux)*1.e9 )
669     & * tmass1 !ppbm
670    
671     do k=1,ktop
672     x11(k) = xmix
673     end do
674    
675     #endif
676    
677     return
678     end
679    
680     ! ====================
681     Block Data Meta_data
682     ! ====================
683    
684     #include "chem_para"
685     #include "chem_meta"
686    
687     #if ( defined CPL_CHEM ) && ( defined CPL_META )
688    
689     #if ( N_LAT == 24 )
690     data rlati/90.0,82.2,74.3,66.5,58.7,50.9,
691     & 43.0,35.2,27.4,19.6,11.7, 3.9,
692     & 3.9,11.7,19.6,27.4,35.2,43.0,
693     & 50.9,58.7,66.5,74.3,82.2,90.0/
694    
695    
696     data results_mon/4176*0.0/
697    
698     data raqino /72*0.1/
699     data raqinoo/72*0.1/
700     data raqivoc/72*0.1/
701     data raqiozo/72*0.1/
702     data raqisox/72*0.1/
703     #endif
704    
705     #if ( N_LAT == 46 )
706     data rlati
707     & /
708     & 90.0, 86.0, 82.0, 78.0, 74.0,
709     & 70.0, 66.0, 62.0, 58.0, 54.0,
710     & 50.0, 46.0, 42.0, 38.0, 34.0,
711     & 30.0, 26.0, 22.0, 18.0, 14.0,
712     & 10.0, 6.0, 2.0, 2.0, 6.0,
713     & 10.0, 14.0, 18.0, 22.0, 26.0,
714     & 30.0, 34.0, 38.0, 42.0, 46.0,
715     & 50.0, 54.0, 58.0, 62.0, 66.0,
716     & 70.0, 74.0, 78.0, 82.0, 86.0,
717     & 90.0
718     & /
719    
720     data results_mon/8004*0.0/
721    
722     data raqino /138*0.1/
723     data raqinoo/138*0.1/
724     data raqivoc/138*0.1/
725     data raqiozo/138*0.1/
726     data raqisox/138*0.1/
727     #endif
728    
729     data nstep_meta/0/
730    
731     data xc_meta/ -86.4, -88.4,-117.6,
732     & -111.8, 71.2, 81.1,
733     & 198.9, 82.7,-101.0,
734     & 86.6, 89.7, 95.7,
735     & 104.6,-126.0, 47.9,
736     & -74.5,-114.3,-124.8,
737     & -106.5,-121.6,-115.6,
738     & -108.7,-102.3, 73.8,
739     & 85.7, 76.7, 0.0,
740     & -84.4,-112.5, 81.9,
741     & 6*0.0,
742     & 97.9, 99.4,20*0.0/
743    
744     data w_meta /183.6,184.3,184.8,
745     & 184.2,183.9,184.0,
746     & 183.6,183.1,184.9,
747     & 185.7,181.0,182.9,
748     & 183.9,184.1,189.3,
749     & 183.8,184.1,184.9,
750     & 183.0,184.6,182.9,
751     & 183.1,184.6,184.0,
752     & 182.1,184.2, 0.0,
753     & 183.3,183.4,183.3,
754     & 6* 0.0,
755     & 184.7,183.1,20*0.0/
756    
757     data a_meta / 0.015,0.153,0.288,
758     & 0.466,8.040,9.880,
759     & 0.007,0.797,0.014,
760     & 0.886,1.016,0.154,
761     & 0.235,0.013,0.044,
762     & 0.323,0.188,0.007,
763     & 0.004,0.028,0.009,
764     & 0.042,0.052,0.053,
765     & 0.080,0.006, 0.0,
766     & 0.141,0.242,6.485,
767     & 6*0.0,
768     & 0.496,0.184,20*0.0/
769    
770     data c_meta / 11.4, -0.8, 4.0,
771     & 4.5, 3.6, 3.9,
772     & 10.5, 4.2, 1.1,
773     & 79.0, 87.0, 11.2,
774     & 7.6, 6.5, 10.3,
775     & 2.6, 5.3, 6.7,
776     & 12.4, 5.7, 12.8,
777     & 15.5, 10.1, 2.8,
778     & 2.0, 3.1, 0.0,
779     & 10.2, 8.8, 4.1,
780     & 6*0.0,
781     & 227.5, 7.6,20*0.0/
782    
783     data urban_beta_1/1.0, 0.0, 0.0/
784     data urban_beta_2/0.9, 1.3, 0.0/
785     data urban_beta_3/0.8, 1.25, 3.0/
786    
787     #endif
788    
789     end
790    
791    
792    

  ViewVC Help
Powered by ViewVC 1.1.22