/[MITgcm]/MITgcm/pkg/fizhi/fizhi_lwrad.F
ViewVC logotype

Annotation of /MITgcm/pkg/fizhi/fizhi_lwrad.F

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


Revision 1.16 - (hide annotations) (download)
Tue Aug 10 15:13:47 2004 UTC (19 years, 11 months ago) by molod
Branch: MAIN
Changes since 1.15: +11 -7 lines
Debugging

1 molod 1.16 C $Header: /u/gcmpack/MITgcm/pkg/fizhi/fizhi_lwrad.F,v 1.15 2004/08/04 22:23:43 molod Exp $
2 molod 1.1 C $Name: $
3    
4 molod 1.10 #include "FIZHI_OPTIONS.h"
5 molod 1.5 subroutine lwrio (nymd,nhms,bi,bj,istrip,npcs,low_level,mid_level,
6 molod 1.12 . im,jm,lm,
7 molod 1.5 . pz,plz,plze,dpres,pkht,pkz,tz,qz,oz,
8     . co2,cfc11,cfc12,cfc22,methane,n2o,emissivity,
9 molod 1.1 . tgz,radlwg,st4,dst4,
10     . dtradlw,dlwdtg,dtradlwc,lwgclr,
11 molod 1.12 . ptop,nlwcld,cldlw,clwmo,nlwlz,lwlz,
12 molod 1.2 . lpnt,imstturb,qliqave,fccave,landtype)
13 molod 1.1
14     implicit none
15 molod 1.2 #ifdef ALLOW_DIAGNOSTICS
16 molod 1.8 #include "SIZE.h"
17     #include "diagnostics_SIZE.h"
18 molod 1.6 #include "diagnostics.h"
19 molod 1.2 #endif
20 molod 1.1
21     c Input Variables
22     c ---------------
23 molod 1.3 integer nymd,nhms,istrip,npcs,bi,bj
24 molod 1.4 integer mid_level,low_level
25 molod 1.1 integer im,jm,lm
26 molod 1.10 _RL ptop
27     _RL pz(im,jm),plz(im,jm,lm),plze(im,jm,lm+1)
28     _RL dpres(im,jm,lm),pkht(im,jm,lm+1),pkz(im,jm,lm)
29     _RL tz(im,jm,lm),qz(im,jm,lm),oz(im,jm,lm)
30     _RL co2,cfc11,cfc12,cfc22,methane(lm),n2o(lm)
31     _RL emissivity(im,jm,10)
32     _RL tgz(im,jm),radlwg(im,jm),st4(im,jm),dst4(im,jm)
33     _RL dtradlw(im,jm,lm),dlwdtg (im,jm,lm)
34     _RL dtradlwc(im,jm,lm),lwgclr(im,jm)
35 molod 1.5 integer nlwcld,nlwlz
36 molod 1.10 _RL cldlw(im,jm,lm),clwmo(im,jm,lm),lwlz(im,jm,lm)
37 molod 1.5 logical lpnt
38     integer imstturb
39 molod 1.10 _RL qliqave(im,jm,lm),fccave(im,jm,lm)
40 molod 1.5 integer landtype(im,jm)
41 molod 1.1
42     c Local Variables
43     c ---------------
44     integer i,j,l,n,nn
45    
46 molod 1.10 _RL cldtot (im,jm,lm)
47     _RL cldmxo (im,jm,lm)
48 molod 1.5
49 molod 1.10 _RL pl(istrip,lm)
50     _RL pk(istrip,lm)
51     _RL pke(istrip,lm)
52     _RL ple(istrip,lm+1)
53    
54     _RL ADELPL(ISTRIP,lm)
55     _RL dtrad(istrip,lm),dtradc(istrip,lm)
56     _RL OZL(ISTRIP,lm),TZL(ISTRIP,lm)
57     _RL SHZL(ISTRIP,lm),CLRO(ISTRIP,lm)
58     _RL CLMO(ISTRIP,lm)
59     _RL flx(ISTRIP,lm+1),flxclr(ISTRIP,lm+1)
60     _RL cldlz(istrip,lm)
61     _RL dfdts(istrip,lm+1),dtdtg(istrip,lm)
62    
63     _RL emiss(istrip,10)
64     _RL taual(istrip,lm,10)
65     _RL ssaal(istrip,lm,10)
66     _RL asyal(istrip,lm,10)
67     _RL cwc(istrip,lm,3)
68     _RL reff(istrip,lm,3)
69     _RL tauc(istrip,lm,3)
70 molod 1.5
71 molod 1.10 _RL SGMT4(ISTRIP),TSURF(ISTRIP),dsgmt4(ISTRIP)
72 molod 1.5 integer lwi(istrip)
73    
74 molod 1.10 _RL getcon,secday,convrt
75 molod 1.5
76     logical high, trace, cldwater
77     data high /.true./
78     data trace /.true./
79 molod 1.1 data cldwater /.false./
80    
81     C **********************************************************************
82     C **** INITIALIZATION ****
83     C **********************************************************************
84    
85     SECDAY = GETCON('SDAY')
86     CONVRT = GETCON('GRAVITY') / ( 100.0 * GETCON('CP') )
87    
88     c Adjust cloud fractions and cloud liquid water due to moist turbulence
89     c ---------------------------------------------------------------------
90     if(imstturb.ne.0) then
91     do L =1,lm
92     do j =1,jm
93     do i =1,im
94     cldtot(i,j,L)=min(1.0,max(cldlw(i,j,L),fccave(i,j,L)/imstturb))
95     cldmxo(i,j,L) = min( 1.0 , clwmo(i,j,L) )
96     lwlz(i,j,L) = lwlz(i,j,L) + qliqave(i,j,L)/imstturb
97     enddo
98     enddo
99     enddo
100     else
101     do L =1,lm
102     do j =1,jm
103     do i =1,im
104     cldtot(i,j,L) = min( 1.0,cldlw(i,j,L) )
105     cldmxo(i,j,L) = min( 1.0,clwmo(i,j,L) )
106     enddo
107     enddo
108     enddo
109     endif
110    
111     C***********************************************************************
112     C **** LOOP OVER STRIPS ****
113     C **********************************************************************
114    
115     DO 1000 NN=1,NPCS
116    
117     C **********************************************************************
118     C **** VARIABLE INITIALIZATION ****
119     C **********************************************************************
120    
121     CALL STRIP (OZ,OZL ,im*jm,ISTRIP,lm ,NN)
122     CALL STRIP (PLZE,ple ,im*jm,ISTRIP,lm+1 ,NN)
123     CALL STRIP (PLZ ,pl ,im*jm,ISTRIP,lm ,NN)
124     CALL STRIP (PKZ ,pk ,im*jm,ISTRIP,lm ,NN)
125     CALL STRIP (PKHT,pke ,im*jm,ISTRIP,lm ,NN)
126     CALL STRIP (TZ,TZL ,im*jm,ISTRIP,lm ,NN)
127     CALL STRIP (qz,SHZL ,im*jm,ISTRIP,lm ,NN)
128     CALL STRIP (cldtot,CLRO ,im*jm,ISTRIP,lm ,NN)
129     CALL STRIP (cldmxo,CLMO ,im*jm,ISTRIP,lm ,NN)
130     CALL STRIP (lwlz,cldlz ,im*jm,ISTRIP,lm ,NN)
131     CALL STRIP (tgz,tsurf ,im*jm,ISTRIP,1 ,NN)
132    
133     CALL STRIP (emissivity,emiss,im*jm,ISTRIP,10,NN)
134    
135     call stripitint (landtype,lwi,im*jm,im*jm,istrip,1,nn)
136    
137     DO I = 1,ISTRIP*lm
138     ADELPL(I,1) = convrt / ( ple(I,2)-ple(I,1) )
139     ENDDO
140    
141     C Compute Clouds
142     C --------------
143     IF(NLWCLD.NE.0)THEN
144     DO L = 1,lm
145     DO I = 1,ISTRIP
146     CLRO(I,L) = min( 1.0,clro(i,L) )
147     CLMO(I,L) = min( 1.0,clmo(i,L) )
148     ENDDO
149     ENDDO
150     ENDIF
151    
152     DO L = 1,lm
153     DO I = 1,ISTRIP
154     TZL(I,L) = TZL(I,L)*pk(I,L)
155     ENDDO
156     ENDDO
157     DO I = 1,ISTRIP
158     C To reduce longwave heating in lowest model layer
159     TZL(I,lm) = ( 2*tzl(i,lm)+tsurf(i) )/3.0
160     ENDDO
161    
162     C Compute Optical Thicknesses
163     C ---------------------------
164     call opthk ( tzl,pl,ple,cldlz,clro,clmo,lwi,istrip,1,lm,tauc )
165    
166     do n = 1,3
167     do L = 1,lm
168     do i = 1,istrip
169     tauc(i,L,n) = tauc(i,L,n)*0.75
170     enddo
171     enddo
172     enddo
173    
174     C Set the optical thickness, single scattering albedo and assymetry factor
175     C for aerosols equal to zero to omit the contribution of aerosols
176     c-------------------------------------------------------------------------
177     do n = 1,10
178     do L = 1,lm
179     do i = 1,istrip
180     taual(i,L,n) = 0.
181     ssaal(i,L,n) = 0.
182     asyal(i,L,n) = 0.
183     enddo
184     enddo
185     enddo
186    
187     C Set cwc and reff to zero - when cldwater is .false.
188     c----------------------------------------------------
189     do n = 1,3
190     do L = 1,lm
191     do i = 1,istrip
192     cwc(i,L,n) = 0.
193     reff(i,L,n) = 0.
194     enddo
195     enddo
196     enddo
197    
198     C **********************************************************************
199     C **** CALL M-D Chou RADIATION ****
200     C **********************************************************************
201    
202     call irrad ( istrip,1,1,lm,ple,tzl,shzl,ozl,tsurf,co2,
203     . n2o,methane,cfc11,cfc12,cfc22,emiss,
204     . cldwater,cwc,tauc,reff,clro,mid_level,low_level,
205     . taual,ssaal,asyal,
206     . high,trace,flx,flxclr,dfdts,sgmt4 )
207    
208     C **********************************************************************
209     C **** HEATING RATES ****
210     C **********************************************************************
211    
212     do L = 1,lm
213     do i = 1,istrip
214     dtrad(i,L) = ( flx(i,L)- flx(i,L+1))*adelpl(i,L)
215     dtdtg(i,L) = ( dfdts(i,L)- dfdts(i,L+1))*adelpl(i,L)
216     dtradc(i,L) = (flxclr(i,L)-flxclr(i,L+1))*adelpl(i,L)
217     enddo
218     enddo
219    
220     C **********************************************************************
221     C **** NET UPWARD LONGWAVE FLUX (W/M**2) ****
222     C **********************************************************************
223    
224     DO I = 1,ISTRIP
225     flx (i,1) = -flx (i,1)
226     flxclr(i,1) = -flxclr(i,1)
227     flx (i,lm+1) = -flx (i,lm+1)
228     flxclr(i,lm+1) = -flxclr(i,lm+1)
229     sgmt4(i) = - sgmt4(i)
230     dsgmt4(i) = - dfdts(i,lm+1)
231     ENDDO
232    
233     CALL PASTE ( flx (1,lm+1),RADLWG,ISTRIP,im*jm,1,NN )
234     CALL PASTE ( flxclr(1,lm+1),LWGCLR,ISTRIP,im*jm,1,NN )
235    
236     CALL PASTE ( sgmt4, st4,ISTRIP,im*jm,1,NN )
237     CALL PASTE ( dsgmt4,dst4,ISTRIP,im*jm,1,NN )
238    
239     C **********************************************************************
240     C **** PASTE AND BUMP SOME DIAGNOSTICS ****
241     C **********************************************************************
242    
243 molod 1.16 c IF(IOLR.GT.0)CALL PSTBMP(flx(1,1),QDIAG(1,1,IOLR,bi,bj),ISTRIP,
244     c . im*jm, 1,NN)
245     c IF(IOLRCLR.GT.0)CALL PSTBMP(flxclr(1,1),QDIAG(1,1,IOLRCLR,bi,bj),
246     c . ISTRIP,im*jm,1,NN)
247     c IF(IOZLW.GT.0)CALL PSTBMP(OZL(1,1),QDIAG(1,1,IOZLW,bi,bj),ISTRIP,
248     c . im*jm,lm,NN)
249 molod 1.1
250     C **********************************************************************
251     C **** TENDENCY UPDATES ****
252     C **********************************************************************
253    
254     DO L = 1,lm
255     DO I = 1,ISTRIP
256     DTRAD (I,L) = ( ple(i,lm+1)-PTOP ) * DTRAD (I,L)/pk(I,L)
257     DTRADC(I,L) = ( ple(i,lm+1)-PTOP ) * DTRADC(I,L)/pk(I,L)
258     dtdtg(I,L) = ( ple(i,lm+1)-PTOP ) * dtdtg (I,L)/pk(I,L)
259     ENDDO
260     ENDDO
261     CALL PASTE ( DTRAD ,DTRADLW ,ISTRIP,im*jm,lm,NN )
262     CALL PASTE ( DTRADC,DTRADLWC,ISTRIP,im*jm,lm,NN )
263     CALL PASTE ( dtdtg ,dlwdtg ,ISTRIP,im*jm,lm,NN )
264    
265     1000 CONTINUE
266    
267     C **********************************************************************
268     C **** BUMP DIAGNOSTICS ****
269     C **********************************************************************
270    
271     if(itgrlw.ne.0) then
272     do j = 1,jm
273     do i = 1,im
274 molod 1.3 qdiag(i,j,itgrlw,bi,bj) = qdiag(i,j,itgrlw,bi,bj) + tgz(i,j)
275 molod 1.1 enddo
276     enddo
277     endif
278    
279     if (itlw.ne.0) then
280     do L = 1,lm
281     do j = 1,jm
282     do i = 1,im
283 molod 1.3 qdiag(i,j,itlw+L-1,bi,bj) = qdiag(i,j,itlw+L-1,bi,bj) +
284     . tz(i,j,L)*pkz(i,j,L)
285 molod 1.1 enddo
286     enddo
287     enddo
288     endif
289    
290     if (ishrad.ne.0) then
291     do L = 1,lm
292     do j = 1,jm
293     do i = 1,im
294 molod 1.3 qdiag(i,j,ishrad+L-1,bi,bj) = qdiag(i,j,ishrad+L-1,bi,bj) +
295     . qz(i,j,L)*1000
296 molod 1.1 enddo
297     enddo
298     enddo
299     endif
300    
301    
302     C **********************************************************************
303     C **** Increment Diagnostics Counters and Zero-Out Cloud Info ****
304     C **********************************************************************
305    
306 molod 1.16 #ifdef ALLOW_DIAGNOSTICS
307     if ( (bi.eq.1) .and. (bj.eq.1) ) then
308 molod 1.1 ntlw = ntlw + 1
309     nshrad = nshrad + 1
310     nozlw = nozlw + 1
311     ntgrlw = ntgrlw + 1
312     nolr = nolr + 1
313     nolrclr = nolrclr + 1
314 molod 1.16 endif
315     #endif
316 molod 1.1
317     nlwlz = 0
318     nlwcld = 0
319     imstturb = 0
320    
321     do L = 1,lm
322     do j = 1,jm
323     do i = 1,im
324     fccave(i,j,L) = 0.
325     qliqave(i,j,L) = 0.
326     enddo
327     enddo
328     enddo
329    
330     return
331     end
332     c********************** November 26, 1997 **************************
333    
334     subroutine irrad (m,n,ndim,np,pl,ta,wa,oa,ts,co2,
335     * n2o,ch4,cfc11,cfc12,cfc22,emiss,
336     * cldwater,cwc,taucl,reff,fcld,ict,icb,
337     * taual,ssaal,asyal,
338     * high,trace,flx,flc,dfdts,st4)
339    
340     c***********************************************************************
341     c
342     c Version IR-5 (September, 1998)
343     c
344     c New features of this version are:
345     c (1) The effect of aerosol scattering on LW fluxes is included.
346     c (2) Absorption and scattering of rain drops are included.
347     c
348     c***********************************************************************
349     c
350     c Version IR-4 (October, 1997)
351     c
352     c New features of this version are:
353     c (1) The surface is treated as non-black. The surface
354     c emissivity, emiss, is an input parameter
355     c (2) The effect of cloud scattering on LW fluxes is included
356     c
357     c*********************************************************************
358     c
359     c This routine computes ir fluxes due to water vapor, co2, o3,
360     c trace gases (n2o, ch4, cfc11, cfc12, cfc22, co2-minor),
361     c clouds, and aerosols.
362     c
363     c This is a vectorized code. It computes fluxes simultaneously for
364     c (m x n) soundings, which is a subset of (m x ndim) soundings.
365     c In a global climate model, m and ndim correspond to the numbers of
366     c grid boxes in the zonal and meridional directions, respectively.
367     c
368     c Some detailed descriptions of the radiation routine are given in
369     c Chou and Suarez (1994).
370     c
371     c Ice and liquid cloud particles are allowed to co-exist in any of the
372     c np layers.
373     c
374     c If no information is available for the effective cloud particle size,
375     c reff, default values of 10 micron for liquid water and 75 micron
376     c for ice can be used.
377     c
378     c The maximum-random assumption is applied for cloud overlapping.
379     c clouds are grouped into high, middle, and low clouds separated by the
380     c level indices ict and icb. Within each of the three groups, clouds
381     c are assumed maximally overlapped, and the cloud cover of a group is
382     c the maximum cloud cover of all the layers in the group. clouds among
383     c the three groups are assumed randomly overlapped. The indices ict and
384     c icb correpond approximately to the 400 mb and 700 mb levels.
385     c
386     c Aerosols are allowed to be in any of the np layers. Aerosol optical
387     c properties can be specified as functions of height and spectral band.
388     c
389     c There are options for computing fluxes:
390     c
391     c If cldwater=.true., taucl is computed from cwc and reff as a
392     c function of height and spectral band.
393     c If cldwater=.false., taucl must be given as input to the radiation
394     c routine. It is independent of spectral band.
395     c
396     c If high = .true., transmission functions in the co2, o3, and the
397     c three water vapor bands with strong absorption are computed using
398     c table look-up. cooling rates are computed accurately from the
399     c surface up to 0.01 mb.
400     c If high = .false., transmission functions are computed using the
401     c k-distribution method with linear pressure scaling for all spectral
402     c bands and gases. cooling rates are not calculated accurately for
403     c pressures less than 20 mb. the computation is faster with
404     c high=.false. than with high=.true.
405    
406     c If trace = .true., absorption due to n2o, ch4, cfcs, and the
407     c two minor co2 bands in the window region is included.
408     c If trace = .false., absorption in minor bands is neglected.
409     c
410     c The IR spectrum is divided into nine bands:
411     c
412     c band wavenumber (/cm) absorber
413     c
414     c 1 0 - 340 h2o
415     c 2 340 - 540 h2o
416     c 3 540 - 800 h2o,cont,co2,n2o
417     c 4 800 - 980 h2o,cont
418     c co2,f11,f12,f22
419     c 5 980 - 1100 h2o,cont,o3
420     c co2,f11
421     c 6 1100 - 1215 h2o,cont
422     c n2o,ch4,f12,f22
423     c 7 1215 - 1380 h2o
424     c n2o,ch4
425     c 8 1380 - 1900 h2o
426     c 9 1900 - 3000 h2o
427     c
428     c In addition, a narrow band in the 15 micrometer region is added to
429     c compute flux reduction due to n2o
430     c
431     c 10 540 - 620 h2o,cont,co2,n2o
432     c
433     c Band 3 (540-800/cm) is further divided into 3 sub-bands :
434     c
435     c subband wavenumber (/cm)
436     c
437     c 1 540 - 620
438     c 2 620 - 720
439     c 3 720 - 800
440     c
441     c---- Input parameters units size
442     c
443     c number of soundings in zonal direction (m) n/d 1
444     c number of soundings in meridional direction (n) n/d 1
445     c maximum number of soundings in
446     c meridional direction (ndim>=n) n/d 1
447     c number of atmospheric layers (np) n/d 1
448     c level pressure (pl) mb m*ndim*(np+1)
449     c layer temperature (ta) k m*ndim*np
450     c layer specific humidity (wa) g/g m*ndim*np
451     c layer ozone mixing ratio by mass (oa) g/g m*ndim*np
452     c surface temperature (ts) k m*ndim
453     c co2 mixing ratio by volumn (co2) pppv 1
454     c n2o mixing ratio by volumn (n2o) pppv np
455     c ch4 mixing ratio by volumn (ch4) pppv np
456     c cfc11 mixing ratio by volumn (cfc11) pppv 1
457     c cfc12 mixing ratio by volumn (cfc12) pppv 1
458     c cfc22 mixing ratio by volumn (cfc22) pppv 1
459     c surface emissivity (emiss) fraction m*ndim*10
460     c input option for cloud optical thickness n/d 1
461     c cldwater="true" if cwc is provided
462     c cldwater="false" if taucl is provided
463     c cloud water mixing ratio (cwc) gm/gm m*ndim*np*3
464     c index 1 for ice particles
465     c index 2 for liquid drops
466     c index 3 for rain drops
467     c cloud optical thickness (taucl) n/d m*ndim*np*3
468     c index 1 for ice particles
469     c index 2 for liquid drops
470     c index 3 for rain drops
471     c effective cloud-particle size (reff) micrometer m*ndim*np*3
472     c index 1 for ice particles
473     c index 2 for liquid drops
474     c index 3 for rain drops
475     c cloud amount (fcld) fraction m*ndim*np
476     c level index separating high and middle n/d 1
477     c clouds (ict)
478     c level index separating middle and low n/d 1
479     c clouds (icb)
480     c aerosol optical thickness (taual) n/d m*ndim*np*10
481     c aerosol single-scattering albedo (ssaal) n/d m*ndim*np*10
482     c aerosol asymmetry factor (asyal) n/d m*ndim*np*10
483     c high (see explanation above) 1
484     c trace (see explanation above) 1
485     c
486     c Data used in table look-up for transmittance calculations:
487     c
488     c c1 , c2, c3: for co2 (band 3)
489     c o1 , o2, o3: for o3 (band 5)
490     c h11,h12,h13: for h2o (band 1)
491     c h21,h22,h23: for h2o (band 2)
492     c h81,h82,h83: for h2o (band 8)
493     c
494     c---- output parameters
495     c
496     c net downward flux, all-sky (flx) w/m**2 m*ndim*(np+1)
497     c net downward flux, clear-sky (flc) w/m**2 m*ndim*(np+1)
498     c sensitivity of net downward flux
499     c to surface temperature (dfdts) w/m**2/k m*ndim*(np+1)
500     c emission by the surface (st4) w/m**2 m*ndim
501     c
502     c Notes:
503     c
504     c (1) Water vapor continuum absorption is included in 540-1380 /cm.
505     c (2) Scattering is parameterized for clouds and aerosols.
506     c (3) Diffuse cloud and aerosol transmissions are computed
507     c from exp(-1.66*tau).
508     c (4) If there are no clouds, flx=flc.
509     c (5) plevel(1) is the pressure at the top of the model atmosphere,
510     c and plevel(np+1) is the surface pressure.
511     c (6) Downward flux is positive and upward flux is negative.
512     c (7) dfdts is negative because upward flux is defined as negative.
513     c (8) For questions and coding errors, contact with Ming-Dah Chou,
514     c Code 913, NASA/Goddard Space Flight Center, Greenbelt, MD 20771.
515     c Phone: 301-286-4012, Fax: 301-286-1759,
516     c e-mail: chou@climate.gsfc.nasa.gov
517     c
518     c-----parameters defining the size of the pre-computed tables for transmittance
519     c calculations using table look-up.
520     c
521     c "nx" is the number of intervals in pressure
522     c "no" is the number of intervals in o3 amount
523     c "nc" is the number of intervals in co2 amount
524     c "nh" is the number of intervals in h2o amount
525     c "nt" is the number of copies to be made from the pre-computed
526     c transmittance tables to reduce "memory-bank conflict"
527     c in parallel machines and, hence, enhancing the speed of
528     c computations using table look-up.
529     c If such advantage does not exist, "nt" can be set to 1.
530     c***************************************************************************
531    
532     cfpp$ expand (h2oexps)
533     cfpp$ expand (conexps)
534     cfpp$ expand (co2exps)
535     cfpp$ expand (n2oexps)
536     cfpp$ expand (ch4exps)
537     cfpp$ expand (comexps)
538     cfpp$ expand (cfcexps)
539     cfpp$ expand (b10exps)
540     cfpp$ expand (tablup)
541     cfpp$ expand (h2okdis)
542     cfpp$ expand (co2kdis)
543     cfpp$ expand (n2okdis)
544     cfpp$ expand (ch4kdis)
545     cfpp$ expand (comkdis)
546     cfpp$ expand (cfckdis)
547     cfpp$ expand (b10kdis)
548    
549     implicit none
550     integer nx,no,nc,nh,nt
551     integer i,j,k,ip,iw,it,ib,ik,iq,isb,k1,k2
552     parameter (nx=26,no=21,nc=24,nh=31,nt=7)
553    
554     c---- input parameters ------
555    
556     integer m,n,ndim,np,ict,icb
557 molod 1.10 _RL pl(m,ndim,np+1),ta(m,ndim,np),wa(m,ndim,np),oa(m,ndim,np),
558 molod 1.1 * ts(m,ndim)
559 molod 1.10 _RL co2,n2o(np),ch4(np),cfc11,cfc12,cfc22,emiss(m,ndim,10)
560     _RL cwc(m,ndim,np,3),taucl(m,ndim,np,3),reff(m,ndim,np,3),
561 molod 1.1 * fcld(m,ndim,np)
562 molod 1.10 _RL taual(m,ndim,np,10),ssaal(m,ndim,np,10),asyal(m,ndim,np,10)
563 molod 1.1 logical cldwater,high,trace
564    
565     c---- output parameters ------
566    
567 molod 1.10 _RL flx(m,ndim,np+1),flc(m,ndim,np+1),dfdts(m,ndim,np+1),
568 molod 1.1 * st4(m,ndim)
569    
570     c---- static data -----
571    
572 molod 1.10 _RL cb(5,10)
573     _RL xkw(9),aw(9),bw(9),pm(9),fkw(6,9),gkw(6,3),xke(9)
574     _RL aib(3,10),awb(4,10),aiw(4,10),aww(4,10),aig(4,10),awg(4,10)
575 molod 1.1 integer ne(9),mw(9)
576    
577     c---- temporary arrays -----
578    
579 molod 1.10 _RL pa(m,n,np),dt(m,n,np)
580     _RL sh2o(m,n,np+1),swpre(m,n,np+1),swtem(m,n,np+1)
581     _RL sco3(m,n,np+1),scopre(m,n,np+1),scotem(m,n,np+1)
582     _RL dh2o(m,n,np),dcont(m,n,np),dco2(m,n,np),do3(m,n,np)
583     _RL dn2o(m,n,np),dch4(m,n,np)
584     _RL df11(m,n,np),df12(m,n,np),df22(m,n,np)
585     _RL th2o(m,n,6),tcon(m,n,3),tco2(m,n,6,2)
586     _RL tn2o(m,n,4),tch4(m,n,4),tcom(m,n,2)
587     _RL tf11(m,n),tf12(m,n),tf22(m,n)
588     _RL h2oexp(m,n,np,6),conexp(m,n,np,3),co2exp(m,n,np,6,2)
589     _RL n2oexp(m,n,np,4),ch4exp(m,n,np,4),comexp(m,n,np,2)
590     _RL f11exp(m,n,np), f12exp(m,n,np), f22exp(m,n,np)
591     _RL clr(m,n,0:np+1),fclr(m,n)
592     _RL blayer(m,n,0:np+1),dlayer(m,n,np+1),dbs(m,n)
593     _RL clrlw(m,n),clrmd(m,n),clrhi(m,n)
594     _RL cwp(m,n,np,3)
595     _RL trant(m,n),tranal(m,n),transfc(m,n,np+1),trantcr(m,n,np+1)
596     _RL flxu(m,n,np+1),flxd(m,n,np+1),flcu(m,n,np+1),flcd(m,n,np+1)
597     _RL rflx(m,n,np+1),rflc(m,n,np+1)
598 molod 1.1
599     logical oznbnd,co2bnd,h2otbl,conbnd,n2obnd
600     logical ch4bnd,combnd,f11bnd,f12bnd,f22bnd,b10bnd
601    
602 molod 1.10 _RL c1 (nx,nc,nt),c2 (nx,nc,nt),c3 (nx,nc,nt)
603     _RL o1 (nx,no,nt),o2 (nx,no,nt),o3 (nx,no,nt)
604     _RL h11(nx,nh,nt),h12(nx,nh,nt),h13(nx,nh,nt)
605     _RL h21(nx,nh,nt),h22(nx,nh,nt),h23(nx,nh,nt)
606     _RL h81(nx,nh,nt),h82(nx,nh,nt),h83(nx,nh,nt)
607 molod 1.1
608 molod 1.10 _RL dp,xx,p1,dwe,dpe,a1,b1,fk1,a2,b2,fk2
609     _RL w1,w2,w3,g1,g2,g3,ww,gg,ff,taux,reff1,reff2
610 molod 1.1
611     c-----the following coefficients (equivalent to table 2 of
612     c chou and suarez, 1995) are for computing spectrally
613     c integrated planck fluxes using eq. (22)
614    
615     data cb/
616     1 -2.6844e-1,-8.8994e-2, 1.5676e-3,-2.9349e-6, 2.2233e-9,
617     2 3.7315e+1,-7.4758e-1, 4.6151e-3,-6.3260e-6, 3.5647e-9,
618     3 3.7187e+1,-3.9085e-1,-6.1072e-4, 1.4534e-5,-1.6863e-8,
619     4 -4.1928e+1, 1.0027e+0,-8.5789e-3, 2.9199e-5,-2.5654e-8,
620     5 -4.9163e+1, 9.8457e-1,-7.0968e-3, 2.0478e-5,-1.5514e-8,
621     6 -4.7107e+1, 8.9130e-1,-5.9735e-3, 1.5596e-5,-9.5911e-9,
622     7 -5.4041e+1, 9.5332e-1,-5.7784e-3, 1.2555e-5,-2.9377e-9,
623     8 -6.9233e+0,-1.5878e-1, 3.9160e-3,-2.4496e-5, 4.9301e-8,
624     9 1.1483e+2,-2.2376e+0, 1.6394e-2,-5.3672e-5, 6.6456e-8,
625     * 1.9668e+1,-3.1161e-1, 1.2886e-3, 3.6835e-7,-1.6212e-9/
626    
627     c-----xkw are the absorption coefficients for the first
628     c k-distribution function due to water vapor line absorption
629     c (tables 4 and 7). units are cm**2/g
630    
631     data xkw / 29.55 , 4.167e-1, 1.328e-2, 5.250e-4,
632     * 5.25e-4, 9.369e-3, 4.719e-2, 1.320e-0, 5.250e-4/
633    
634     c-----xke are the absorption coefficients for the first
635     c k-distribution function due to water vapor continuum absorption
636     c (table 6). units are cm**2/g
637    
638     data xke / 0.00, 0.00, 27.40, 15.8,
639     * 9.40, 7.75, 0.0, 0.0, 0.0/
640    
641     c-----mw are the ratios between neighboring absorption coefficients
642     c for water vapor line absorption (tables 4 and 7).
643    
644     data mw /6,6,8,6,6,8,9,6,16/
645    
646     c-----aw and bw (table 3) are the coefficients for temperature scaling
647     c in eq. (25).
648    
649     data aw/ 0.0021, 0.0140, 0.0167, 0.0302,
650     * 0.0307, 0.0195, 0.0152, 0.0008, 0.0096/
651     data bw/ -1.01e-5, 5.57e-5, 8.54e-5, 2.96e-4,
652     * 2.86e-4, 1.108e-4, 7.608e-5, -3.52e-6, 1.64e-5/
653    
654     data pm/ 1.0, 1.0, 1.0, 1.0, 1.0, 0.77, 0.5, 1.0, 1.0/
655    
656     c-----fkw is the planck-weighted k-distribution function due to h2o
657     c line absorption given in table 4 of Chou and Suarez (1995).
658     c the k-distribution function for the third band, fkw(*,3), is not used
659    
660     data fkw / 0.2747,0.2717,0.2752,0.1177,0.0352,0.0255,
661     2 0.1521,0.3974,0.1778,0.1826,0.0374,0.0527,
662     3 6*1.00,
663     4 0.4654,0.2991,0.1343,0.0646,0.0226,0.0140,
664     5 0.5543,0.2723,0.1131,0.0443,0.0160,0.0000,
665     6 0.5955,0.2693,0.0953,0.0335,0.0064,0.0000,
666     7 0.1958,0.3469,0.3147,0.1013,0.0365,0.0048,
667     8 0.0740,0.1636,0.4174,0.1783,0.1101,0.0566,
668     9 0.1437,0.2197,0.3185,0.2351,0.0647,0.0183/
669    
670     c-----gkw is the planck-weighted k-distribution function due to h2o
671     c line absorption in the 3 subbands (800-720,620-720,540-620 /cm)
672     c of band 3 given in table 7. Note that the order of the sub-bands
673     c is reversed.
674    
675     data gkw/ 0.1782,0.0593,0.0215,0.0068,0.0022,0.0000,
676     2 0.0923,0.1675,0.0923,0.0187,0.0178,0.0000,
677     3 0.0000,0.1083,0.1581,0.0455,0.0274,0.0041/
678    
679     c-----ne is the number of terms used in each band to compute water vapor
680     c continuum transmittance (table 6).
681    
682     data ne /0,0,3,1,1,1,0,0,0/
683     c
684     c-----coefficients for computing the extinction coefficient
685     c for cloud ice particles
686     c polynomial fit: y=a1+a2/x**a3; x is in m**2/gm
687     c
688     data aib / -0.44171, 0.62951, 0.06465,
689     2 -0.13727, 0.61291, 0.28962,
690     3 -0.01878, 1.67680, 0.79080,
691     4 -0.01896, 1.06510, 0.69493,
692     5 -0.04788, 0.88178, 0.54492,
693     6 -0.02265, 1.57390, 0.76161,
694     7 -0.01038, 2.15640, 0.89045,
695     8 -0.00450, 2.51370, 0.95989,
696     9 -0.00044, 3.15050, 1.03750,
697     * -0.02956, 1.44680, 0.71283/
698     c
699     c-----coefficients for computing the extinction coefficient
700     c for cloud liquid drops
701     c polynomial fit: y=a1+a2*x+a3*x**2+a4*x**3; x is in m**2/gm
702     c
703     data awb / 0.08641, 0.01769, -1.5572e-3, 3.4896e-5,
704     2 0.22027, 0.00997, -1.8719e-3, 5.3112e-5,
705     3 0.39252, -0.02817, 7.2931e-4, -3.8151e-6,
706     4 0.39975, -0.03426, 1.2884e-3, -1.7930e-5,
707     5 0.34021, -0.02805, 1.0654e-3, -1.5443e-5,
708     6 0.15587, 0.00371, -7.7705e-4, 2.0547e-5,
709     7 0.05518, 0.04544, -4.2067e-3, 1.0184e-4,
710     8 0.12724, 0.04751, -5.2037e-3, 1.3711e-4,
711     9 0.30390, 0.01656, -3.5271e-3, 1.0828e-4,
712     * 0.63617, -0.06287, 2.2350e-3, -2.3177e-5/
713     c
714     c-----coefficients for computing the single-scattering albedo
715     c for cloud ice particles
716     c polynomial fit: y=a1+a2*x+a3*x**2+a4*x**3; x is in m**2/gm
717     c
718     data aiw/ 0.17201, 1.2229e-2, -1.4837e-4, 5.8020e-7,
719     2 0.81470, -2.7293e-3, 9.7816e-8, 5.7650e-8,
720     3 0.54859, -4.8273e-4, 5.4353e-6, -1.5679e-8,
721     4 0.39218, 4.1717e-3, - 4.8869e-5, 1.9144e-7,
722     5 0.71773, -3.3640e-3, 1.9713e-5, -3.3189e-8,
723     6 0.77345, -5.5228e-3, 4.8379e-5, -1.5151e-7,
724     7 0.74975, -5.6604e-3, 5.6475e-5, -1.9664e-7,
725     8 0.69011, -4.5348e-3, 4.9322e-5, -1.8255e-7,
726     9 0.83963, -6.7253e-3, 6.1900e-5, -2.0862e-7,
727     * 0.64860, -2.8692e-3, 2.7656e-5, -8.9680e-8/
728     c
729     c-----coefficients for computing the single-scattering albedo
730     c for cloud liquid drops
731     c polynomial fit: y=a1+a2*x+a3*x**2+a4*x**3; x is in m**2/gm
732     c
733     data aww/ -7.8566e-2, 8.0875e-2, -4.3403e-3, 8.1341e-5,
734     2 -1.3384e-2, 9.3134e-2, -6.0491e-3, 1.3059e-4,
735     3 3.7096e-2, 7.3211e-2, -4.4211e-3, 9.2448e-5,
736     4 -3.7600e-3, 9.3344e-2, -5.6561e-3, 1.1387e-4,
737     5 0.40212, 7.8083e-2, -5.9583e-3, 1.2883e-4,
738     6 0.57928, 5.9094e-2, -5.4425e-3, 1.2725e-4,
739     7 0.68974, 4.2334e-2, -4.9469e-3, 1.2863e-4,
740     8 0.80122, 9.4578e-3, -2.8508e-3, 9.0078e-5,
741     9 1.02340, -2.6204e-2, 4.2552e-4, 3.2160e-6,
742     * 0.05092, 7.5409e-2, -4.7305e-3, 1.0121e-4/
743     c
744     c-----coefficients for computing the asymmetry factor for cloud ice particles
745     c polynomial fit: y=a1+a2*x+a3*x**2+a4*x**3; x is in m**2/gm
746     c
747     data aig / 0.57867, 1.0135e-2, -1.1142e-4, 4.1537e-7,
748     2 0.72259, 3.1149e-3, -1.9927e-5, 5.6024e-8,
749     3 0.76109, 4.5449e-3, -4.6199e-5, 1.6446e-7,
750     4 0.86934, 2.7474e-3, -3.1301e-5, 1.1959e-7,
751     5 0.89103, 1.8513e-3, -1.6551e-5, 5.5193e-8,
752     6 0.86325, 2.1408e-3, -1.6846e-5, 4.9473e-8,
753     7 0.85064, 2.5028e-3, -2.0812e-5, 6.3427e-8,
754     8 0.86945, 2.4615e-3, -2.3882e-5, 8.2431e-8,
755     9 0.80122, 3.1906e-3, -2.4856e-5, 7.2411e-8,
756     * 0.73290, 4.8034e-3, -4.4425e-5, 1.4839e-7/
757     c
758     c-----coefficients for computing the asymmetry factor for cloud liquid drops
759     c polynomial fit: y=a1+a2*x+a3*x**2+a4*x**3; x is in m**2/gm
760     c
761     data awg / -0.51930, 0.20290, -1.1747e-2, 2.3868e-4,
762     2 -0.22151, 0.19708, -1.2462e-2, 2.6646e-4,
763     3 0.14157, 0.14705, -9.5802e-3, 2.0819e-4,
764     4 0.41590, 0.10482, -6.9118e-3, 1.5115e-4,
765     5 0.55338, 7.7016e-2, -5.2218e-3, 1.1587e-4,
766     6 0.61384, 6.4402e-2, -4.6241e-3, 1.0746e-4,
767     7 0.67891, 4.8698e-2, -3.7021e-3, 9.1966e-5,
768     8 0.78169, 2.0803e-2, -1.4749e-3, 3.9362e-5,
769     9 0.93218, -3.3425e-2, 2.9632e-3, -6.9362e-5,
770     * 0.01649, 0.16561, -1.0723e-2, 2.3220e-4/
771     c
772     c-----include tables used in the table look-up for co2 (band 3),
773     c o3 (band 5), and h2o (bands 1, 2, and 7) transmission functions.
774    
775     logical first
776     data first /.true./
777    
778 molod 1.7 #include "h2o-tran3.h"
779     #include "co2-tran3.h"
780     #include "o3-tran3.h"
781 molod 1.1
782     save c1,c2,c3,o1,o2,o3
783     save h11,h12,h13,h21,h22,h23,h81,h82,h83
784    
785 molod 1.15 c if (first) then
786 molod 1.1
787     c-----tables co2 and h2o are only used with 'high' option
788    
789     if (high) then
790    
791     do iw=1,nh
792     do ip=1,nx
793     h11(ip,iw,1)=1.0-h11(ip,iw,1)
794     h21(ip,iw,1)=1.0-h21(ip,iw,1)
795     h81(ip,iw,1)=1.0-h81(ip,iw,1)
796     enddo
797     enddo
798    
799     do iw=1,nc
800     do ip=1,nx
801     c1(ip,iw,1)=1.0-c1(ip,iw,1)
802     enddo
803     enddo
804    
805     c-----copy tables to enhance the speed of co2 (band 3), o3 (band 5),
806     c and h2o (bands 1, 2, and 8 only) transmission calculations
807     c using table look-up.
808     c-----tables are replicated to avoid memory bank conflicts
809    
810     do it=2,nt
811     do iw=1,nc
812     do ip=1,nx
813     c1 (ip,iw,it)= c1(ip,iw,1)
814     c2 (ip,iw,it)= c2(ip,iw,1)
815     c3 (ip,iw,it)= c3(ip,iw,1)
816     enddo
817     enddo
818     do iw=1,nh
819     do ip=1,nx
820     h11(ip,iw,it)=h11(ip,iw,1)
821     h12(ip,iw,it)=h12(ip,iw,1)
822     h13(ip,iw,it)=h13(ip,iw,1)
823     h21(ip,iw,it)=h21(ip,iw,1)
824     h22(ip,iw,it)=h22(ip,iw,1)
825     h23(ip,iw,it)=h23(ip,iw,1)
826     h81(ip,iw,it)=h81(ip,iw,1)
827     h82(ip,iw,it)=h82(ip,iw,1)
828     h83(ip,iw,it)=h83(ip,iw,1)
829     enddo
830     enddo
831     enddo
832    
833     endif
834    
835     c-----always use table look-up for ozone transmittance
836    
837     do iw=1,no
838     do ip=1,nx
839     o1(ip,iw,1)=1.0-o1(ip,iw,1)
840     enddo
841     enddo
842    
843     do it=2,nt
844     do iw=1,no
845     do ip=1,nx
846     o1 (ip,iw,it)= o1(ip,iw,1)
847     o2 (ip,iw,it)= o2(ip,iw,1)
848     o3 (ip,iw,it)= o3(ip,iw,1)
849     enddo
850     enddo
851     enddo
852    
853 molod 1.15 c first=.false.
854 molod 1.1
855 molod 1.15 c endif
856 molod 1.1
857     c-----set the pressure at the top of the model atmosphere
858     c to 1.0e-4 if it is zero
859    
860     do j=1,n
861     do i=1,m
862     if (pl(i,j,1) .eq. 0.0) then
863     pl(i,j,1)=1.0e-4
864     endif
865     enddo
866     enddo
867    
868     c-----compute layer pressure (pa) and layer temperature minus 250K (dt)
869    
870     do k=1,np
871     do j=1,n
872     do i=1,m
873     pa(i,j,k)=0.5*(pl(i,j,k)+pl(i,j,k+1))
874     dt(i,j,k)=ta(i,j,k)-250.0
875     enddo
876     enddo
877     enddo
878    
879     c-----compute layer absorber amount
880    
881     c dh2o : water vapor amount (g/cm**2)
882     c dcont: scaled water vapor amount for continuum absorption
883     c (g/cm**2)
884     c dco2 : co2 amount (cm-atm)stp
885     c do3 : o3 amount (cm-atm)stp
886     c dn2o : n2o amount (cm-atm)stp
887     c dch4 : ch4 amount (cm-atm)stp
888     c df11 : cfc11 amount (cm-atm)stp
889     c df12 : cfc12 amount (cm-atm)stp
890     c df22 : cfc22 amount (cm-atm)stp
891     c the factor 1.02 is equal to 1000/980
892     c factors 789 and 476 are for unit conversion
893     c the factor 0.001618 is equal to 1.02/(.622*1013.25)
894     c the factor 6.081 is equal to 1800/296
895    
896    
897     do k=1,np
898     do j=1,n
899     do i=1,m
900    
901     dp = pl(i,j,k+1)-pl(i,j,k)
902     dh2o (i,j,k) = 1.02*wa(i,j,k)*dp+1.e-10
903     do3 (i,j,k) = 476.*oa(i,j,k)*dp+1.e-10
904     dco2 (i,j,k) = 789.*co2*dp+1.e-10
905     dch4 (i,j,k) = 789.*ch4(k)*dp+1.e-10
906     dn2o (i,j,k) = 789.*n2o(k)*dp+1.e-10
907     df11 (i,j,k) = 789.*cfc11*dp+1.e-10
908     df12 (i,j,k) = 789.*cfc12*dp+1.e-10
909     df22 (i,j,k) = 789.*cfc22*dp+1.e-10
910    
911     c-----compute scaled water vapor amount for h2o continuum absorption
912     c following eq. (43).
913    
914     xx=pa(i,j,k)*0.001618*wa(i,j,k)*wa(i,j,k)*dp
915     dcont(i,j,k) = xx*exp(1800./ta(i,j,k)-6.081)+1.e-10
916    
917     enddo
918     enddo
919     enddo
920    
921     c-----compute column-integrated h2o amoumt, h2o-weighted pressure
922     c and temperature. it follows eqs. (37) and (38).
923    
924     if (high) then
925     call column(m,n,np,pa,dt,dh2o,sh2o,swpre,swtem)
926     endif
927    
928     c-----compute layer cloud water amount (gm/m**2)
929     c index is 1 for ice, 2 for waterdrops and 3 for raindrops.
930     c Rain optical thickness is 0.00307 /(gm/m**2).
931     c It is for a specific drop size distribution provided by Q. Fu.
932    
933     if (cldwater) then
934     do k=1,np
935     do j=1,n
936     do i=1,m
937     dp =pl(i,j,k+1)-pl(i,j,k)
938     cwp(i,j,k,1)=1.02*10000.0*cwc(i,j,k,1)*dp
939     cwp(i,j,k,2)=1.02*10000.0*cwc(i,j,k,2)*dp
940     cwp(i,j,k,3)=1.02*10000.0*cwc(i,j,k,3)*dp
941     taucl(i,j,k,3)=0.00307*cwp(i,j,k,3)
942     enddo
943     enddo
944     enddo
945     endif
946    
947     c-----the surface (np+1) is treated as a layer filled with black clouds.
948     c clr is the equivalent clear fraction of a layer
949     c transfc is the transmttance between the surface and a pressure level.
950     c trantcr is the clear-sky transmttance between the surface and a
951     c pressure level.
952    
953     do j=1,n
954     do i=1,m
955     clr(i,j,0) = 1.0
956     clr(i,j,np+1) = 0.0
957     st4(i,j) = 0.0
958     transfc(i,j,np+1)=1.0
959     trantcr(i,j,np+1)=1.0
960     enddo
961     enddo
962    
963     c-----initialize fluxes
964    
965     do k=1,np+1
966     do j=1,n
967     do i=1,m
968     flx(i,j,k) = 0.0
969     flc(i,j,k) = 0.0
970     dfdts(i,j,k)= 0.0
971     rflx(i,j,k) = 0.0
972     rflc(i,j,k) = 0.0
973     enddo
974     enddo
975     enddo
976    
977     c-----integration over spectral bands
978    
979     do 1000 ib=1,10
980    
981     c-----if h2otbl, compute h2o (line) transmittance using table look-up.
982     c if conbnd, compute h2o (continuum) transmittance in bands 3-6.
983     c if co2bnd, compute co2 transmittance in band 3.
984     c if oznbnd, compute o3 transmittance in band 5.
985     c if n2obnd, compute n2o transmittance in bands 6 and 7.
986     c if ch4bnd, compute ch4 transmittance in bands 6 and 7.
987     c if combnd, compute co2-minor transmittance in bands 4 and 5.
988     c if f11bnd, compute cfc11 transmittance in bands 4 and 5.
989     c if f12bnd, compute cfc12 transmittance in bands 4 and 6.
990     c if f22bnd, compute cfc22 transmittance in bands 4 and 6.
991     c if b10bnd, compute flux reduction due to n2o in band 10.
992    
993     h2otbl=high.and.(ib.eq.1.or.ib.eq.2.or.ib.eq.8)
994     conbnd=ib.ge.3.and.ib.le.6
995     co2bnd=ib.eq.3
996     oznbnd=ib.eq.5
997     n2obnd=ib.eq.6.or.ib.eq.7
998     ch4bnd=ib.eq.6.or.ib.eq.7
999     combnd=ib.eq.4.or.ib.eq.5
1000     f11bnd=ib.eq.4.or.ib.eq.5
1001     f12bnd=ib.eq.4.or.ib.eq.6
1002     f22bnd=ib.eq.4.or.ib.eq.6
1003     b10bnd=ib.eq.10
1004    
1005     c-----blayer is the spectrally integrated planck flux of the mean layer
1006     c temperature derived from eq. (22)
1007     c the fitting for the planck flux is valid in the range 160-345 K.
1008    
1009     do k=1,np
1010     do j=1,n
1011     do i=1,m
1012     blayer(i,j,k)=ta(i,j,k)*(ta(i,j,k)*(ta(i,j,k)
1013     * *(ta(i,j,k)*cb(5,ib)+cb(4,ib))+cb(3,ib))
1014     * +cb(2,ib))+cb(1,ib)
1015     enddo
1016     enddo
1017     enddo
1018    
1019     c-----the earth's surface, with an index "np+1", is treated as a layer
1020    
1021     do j=1,n
1022     do i=1,m
1023     blayer(i,j,0) = 0.0
1024     blayer(i,j,np+1)= ( ts(i,j)*(ts(i,j)*(ts(i,j)
1025     * *(ts(i,j)*cb(5,ib)+cb(4,ib))+cb(3,ib))
1026     * +cb(2,ib))+cb(1,ib) )*emiss(i,j,ib)
1027    
1028     c-----dbs is the derivative of the surface emission with respect to
1029     c surface temperature (eq. 59).
1030    
1031     dbs(i,j)=(ts(i,j)*(ts(i,j)*(ts(i,j)*4.*cb(5,ib)
1032     * +3.*cb(4,ib))+2.*cb(3,ib))+cb(2,ib))*emiss(i,j,ib)
1033    
1034     enddo
1035     enddo
1036    
1037     do k=1,np+1
1038     do j=1,n
1039     do i=1,m
1040     dlayer(i,j,k)=blayer(i,j,k-1)-blayer(i,j,k)
1041     enddo
1042     enddo
1043     enddo
1044    
1045     c-----compute column-integrated absorber amoumt, absorber-weighted
1046     c pressure and temperature for co2 (band 3) and o3 (band 5).
1047     c it follows eqs. (37) and (38).
1048    
1049     c-----this is in the band loop to save storage
1050    
1051     if (high .and. co2bnd) then
1052     call column(m,n,np,pa,dt,dco2,sco3,scopre,scotem)
1053     endif
1054    
1055     if (oznbnd) then
1056     call column(m,n,np,pa,dt,do3,sco3,scopre,scotem)
1057     endif
1058    
1059     c-----compute cloud optical thickness
1060    
1061     if (cldwater) then
1062     do k= 1, np
1063     do j= 1, n
1064     do i= 1, m
1065     taucl(i,j,k,1)=cwp(i,j,k,1)*(aib(1,ib)+aib(2,ib)/
1066     * reff(i,j,k,1)**aib(3,ib))
1067     taucl(i,j,k,2)=cwp(i,j,k,2)*(awb(1,ib)+(awb(2,ib)+(awb(3,ib)
1068     * +awb(4,ib)*reff(i,j,k,2))*reff(i,j,k,2))*reff(i,j,k,2))
1069     enddo
1070     enddo
1071     enddo
1072     endif
1073    
1074     c-----compute cloud single-scattering albedo and asymmetry factor for
1075     c a mixture of ice particles, liquid drops, and rain drops
1076     c single-scattering albedo and asymmetry factor of rain are set
1077     c to 0.54 and 0.95, respectively.
1078    
1079     do k= 1, np
1080     do j= 1, n
1081     do i= 1, m
1082    
1083     clr(i,j,k) = 1.0
1084     taux=taucl(i,j,k,1)+taucl(i,j,k,2)+taucl(i,j,k,3)
1085    
1086     if (taux.gt.0.02 .and. fcld(i,j,k).gt.0.01) then
1087    
1088     reff1=min(reff(i,j,k,1),130.)
1089     reff2=min(reff(i,j,k,2),20.0)
1090    
1091     w1=taucl(i,j,k,1)*(aiw(1,ib)+(aiw(2,ib)+(aiw(3,ib)
1092     * +aiw(4,ib)*reff1)*reff1)*reff1)
1093     w2=taucl(i,j,k,2)*(aww(1,ib)+(aww(2,ib)+(aww(3,ib)
1094     * +aww(4,ib)*reff2)*reff2)*reff2)
1095     w3=taucl(i,j,k,3)*0.54
1096     ww=(w1+w2+w3)/taux
1097    
1098     g1=w1*(aig(1,ib)+(aig(2,ib)+(aig(3,ib)
1099     * +aig(4,ib)*reff1)*reff1)*reff1)
1100     g2=w2*(awg(1,ib)+(awg(2,ib)+(awg(3,ib)
1101     * +awg(4,ib)*reff2)*reff2)*reff2)
1102     g3=w3*0.95
1103    
1104     gg=(g1+g2+g3)/(w1+w2+w3)
1105    
1106     c-----parameterization of LW scattering
1107     c compute forward-scattered fraction and scale optical thickness
1108    
1109     ff=0.5+(0.3739+(0.0076+0.1185*gg)*gg)*gg
1110     taux=taux*(1.-ww*ff)
1111    
1112     c-----compute equivalent cloud-free fraction, clr, for each layer
1113     c the cloud diffuse transmittance is approximated by using
1114     c a diffusivity factor of 1.66.
1115    
1116     clr(i,j,k)=1.0-(fcld(i,j,k)*(1.0-exp(-1.66*taux)))
1117    
1118     endif
1119    
1120     enddo
1121     enddo
1122     enddo
1123    
1124     c-----compute the exponential terms (eq. 32) at each layer due to
1125     c water vapor line absorption when k-distribution is used
1126    
1127     if (.not.h2otbl .and. .not.b10bnd) then
1128     call h2oexps(ib,m,n,np,dh2o,pa,dt,xkw,aw,bw,pm,mw,h2oexp)
1129     endif
1130    
1131     c-----compute the exponential terms (eq. 46) at each layer due to
1132     c water vapor continuum absorption
1133    
1134     if (conbnd) then
1135     call conexps(ib,m,n,np,dcont,xke,conexp)
1136     endif
1137    
1138     c-----compute the exponential terms (eq. 32) at each layer due to
1139     c co2 absorption
1140    
1141     if (.not.high .and. co2bnd) then
1142     call co2exps(m,n,np,dco2,pa,dt,co2exp)
1143     endif
1144    
1145     c***** for trace gases *****
1146    
1147     if (trace) then
1148    
1149     c-----compute the exponential terms at each layer due to n2o absorption
1150    
1151     if (n2obnd) then
1152     call n2oexps(ib,m,n,np,dn2o,pa,dt,n2oexp)
1153     endif
1154    
1155     c-----compute the exponential terms at each layer due to ch4 absorption
1156    
1157     if (ch4bnd) then
1158     call ch4exps(ib,m,n,np,dch4,pa,dt,ch4exp)
1159     endif
1160    
1161     c-----compute the exponential terms due to co2 minor absorption
1162    
1163     if (combnd) then
1164     call comexps(ib,m,n,np,dco2,dt,comexp)
1165     endif
1166    
1167     c-----compute the exponential terms due to cfc11 absorption
1168    
1169     if (f11bnd) then
1170     a1 = 1.26610e-3
1171     b1 = 3.55940e-6
1172     fk1 = 1.89736e+1
1173     a2 = 8.19370e-4
1174     b2 = 4.67810e-6
1175     fk2 = 1.01487e+1
1176     call cfcexps(ib,m,n,np,a1,b1,fk1,a2,b2,fk2,df11,dt,f11exp)
1177     endif
1178    
1179     c-----compute the exponential terms due to cfc12 absorption
1180    
1181     if (f12bnd) then
1182     a1 = 8.77370e-4
1183     b1 =-5.88440e-6
1184     fk1 = 1.58104e+1
1185     a2 = 8.62000e-4
1186     b2 =-4.22500e-6
1187     fk2 = 3.70107e+1
1188     call cfcexps(ib,m,n,np,a1,b1,fk1,a2,b2,fk2,df12,dt,f12exp)
1189     endif
1190    
1191     c-----compute the exponential terms due to cfc22 absorption
1192    
1193     if (f22bnd) then
1194     a1 = 9.65130e-4
1195     b1 = 1.31280e-5
1196     fk1 = 6.18536e+0
1197     a2 =-3.00010e-5
1198     b2 = 5.25010e-7
1199     fk2 = 3.27912e+1
1200     call cfcexps(ib,m,n,np,a1,b1,fk1,a2,b2,fk2,df22,dt,f22exp)
1201     endif
1202    
1203     c-----compute the exponential terms at each layer in band 10 due to
1204     c h2o line and continuum, co2, and n2o absorption
1205    
1206     if (b10bnd) then
1207     call b10exps(m,n,np,dh2o,dcont,dco2,dn2o,pa,dt
1208     * ,h2oexp,conexp,co2exp,n2oexp)
1209     endif
1210    
1211     endif
1212    
1213     c-----compute transmittances for regions between levels k1 and k2
1214     c and update the fluxes at the two levels.
1215    
1216    
1217     c-----initialize fluxes
1218    
1219     do k=1,np+1
1220     do j=1,n
1221     do i=1,m
1222     flxu(i,j,k) = 0.0
1223     flxd(i,j,k) = 0.0
1224     flcu(i,j,k) = 0.0
1225     flcd(i,j,k) = 0.0
1226     enddo
1227     enddo
1228     enddo
1229    
1230     do 2000 k1=1,np
1231    
1232     c-----initialize fclr, th2o, tcon, tco2, and tranal
1233     c fclr is the clear fraction of the line-of-sight
1234     c clrlw, clrmd, and clrhi are the clear-sky fractions of the
1235     c low, middle, and high troposphere, respectively
1236     c tranal is the aerosol transmission function
1237    
1238     do j=1,n
1239     do i=1,m
1240     fclr(i,j) = 1.0
1241     clrlw(i,j) = 1.0
1242     clrmd(i,j) = 1.0
1243     clrhi(i,j) = 1.0
1244     tranal(i,j)= 1.0
1245     enddo
1246     enddo
1247    
1248     c-----for h2o line transmission
1249    
1250     if (.not. h2otbl) then
1251     do ik=1,6
1252     do j=1,n
1253     do i=1,m
1254     th2o(i,j,ik)=1.0
1255     enddo
1256     enddo
1257     enddo
1258     endif
1259    
1260     c-----for h2o continuum transmission
1261    
1262     if (conbnd) then
1263     do iq=1,3
1264     do j=1,n
1265     do i=1,m
1266     tcon(i,j,iq)=1.0
1267     enddo
1268     enddo
1269     enddo
1270     endif
1271    
1272     c-----for co2 transmission using k-distribution method.
1273     c band 3 is divided into 3 sub-bands, but sub-bands 3a and 3c
1274     c are combined in computing the co2 transmittance.
1275    
1276     if (.not.high .and. co2bnd) then
1277     do isb=1,2
1278     do ik=1,6
1279     do j=1,n
1280     do i=1,m
1281     tco2(i,j,ik,isb)=1.0
1282     enddo
1283     enddo
1284     enddo
1285     enddo
1286     endif
1287    
1288     c***** for trace gases *****
1289    
1290     if (trace) then
1291    
1292     c-----for n2o transmission using k-distribution method.
1293    
1294     if (n2obnd) then
1295     do ik=1,4
1296     do j=1,n
1297     do i=1,m
1298     tn2o(i,j,ik)=1.0
1299     enddo
1300     enddo
1301     enddo
1302     endif
1303    
1304     c-----for ch4 transmission using k-distribution method.
1305    
1306     if (ch4bnd) then
1307     do ik=1,4
1308     do j=1,n
1309     do i=1,m
1310     tch4(i,j,ik)=1.0
1311     enddo
1312     enddo
1313     enddo
1314     endif
1315    
1316     c-----for co2-minor transmission using k-distribution method.
1317    
1318     if (combnd) then
1319     do ik=1,2
1320     do j=1,n
1321     do i=1,m
1322     tcom(i,j,ik)=1.0
1323     enddo
1324     enddo
1325     enddo
1326     endif
1327    
1328     c-----for cfc-11 transmission using k-distribution method.
1329    
1330     if (f11bnd) then
1331     do j=1,n
1332     do i=1,m
1333     tf11(i,j)=1.0
1334     enddo
1335     enddo
1336     endif
1337    
1338     c-----for cfc-12 transmission using k-distribution method.
1339    
1340     if (f12bnd) then
1341     do j=1,n
1342     do i=1,m
1343     tf12(i,j)=1.0
1344     enddo
1345     enddo
1346     endif
1347    
1348     c-----for cfc-22 transmission when using k-distribution method.
1349    
1350     if (f22bnd) then
1351     do j=1,n
1352     do i=1,m
1353     tf22(i,j)=1.0
1354     enddo
1355     enddo
1356     endif
1357    
1358     c-----for the transmission in band 10 using k-distribution method.
1359    
1360     if (b10bnd) then
1361     do ik=1,6
1362     do j=1,n
1363     do i=1,m
1364     th2o(i,j,ik)=1.0
1365     tco2(i,j,ik,1)=1.0
1366     enddo
1367     enddo
1368     enddo
1369     do iq=1,3
1370     do j=1,n
1371     do i=1,m
1372     tcon(i,j,iq)=1.0
1373     enddo
1374     enddo
1375     enddo
1376     do ik=1,4
1377     do j=1,n
1378     do i=1,m
1379     tn2o(i,j,ik)=1.0
1380     enddo
1381     enddo
1382     enddo
1383     endif
1384    
1385     endif
1386    
1387     c-----loop over the bottom level of the region (k2)
1388    
1389     do 3000 k2=k1+1,np+1
1390    
1391     c-----initialize total transmission function (trant)
1392    
1393     do j=1,n
1394     do i=1,m
1395     trant(i,j)=1.0
1396     enddo
1397     enddo
1398    
1399     if (h2otbl) then
1400     w1=-8.0
1401     p1=-2.0
1402     dwe=0.3
1403     dpe=0.2
1404    
1405     c-----compute water vapor transmittance using table look-up
1406    
1407     if (ib.eq.1) then
1408     call tablup(k1,k2,m,n,np,nx,nh,nt,sh2o,swpre,swtem,
1409     * w1,p1,dwe,dpe,h11,h12,h13,trant)
1410     endif
1411     if (ib.eq.2) then
1412     call tablup(k1,k2,m,n,np,nx,nh,nt,sh2o,swpre,swtem,
1413     * w1,p1,dwe,dpe,h21,h22,h23,trant)
1414    
1415     endif
1416     if (ib.eq.8) then
1417     call tablup(k1,k2,m,n,np,nx,nh,nt,sh2o,swpre,swtem,
1418     * w1,p1,dwe,dpe,h81,h82,h83,trant)
1419     endif
1420    
1421     else
1422    
1423     c-----compute water vapor transmittance using k-distribution
1424    
1425     if (.not.b10bnd) then
1426     call h2okdis(ib,m,n,np,k2-1,fkw,gkw,ne,h2oexp,conexp,
1427     * th2o,tcon,trant)
1428     endif
1429    
1430     endif
1431    
1432     if (co2bnd) then
1433    
1434     if (high) then
1435    
1436     c-----compute co2 transmittance using table look-up method
1437    
1438     w1=-4.0
1439     p1=-2.0
1440     dwe=0.3
1441     dpe=0.2
1442     call tablup(k1,k2,m,n,np,nx,nc,nt,sco3,scopre,scotem,
1443     * w1,p1,dwe,dpe,c1,c2,c3,trant)
1444 molod 1.11
1445 molod 1.1 else
1446    
1447     c-----compute co2 transmittance using k-distribution method
1448     call co2kdis(m,n,np,k2-1,co2exp,tco2,trant)
1449    
1450     endif
1451    
1452     endif
1453    
1454     c-----All use table look-up to compute o3 transmittance.
1455    
1456     if (oznbnd) then
1457     w1=-6.0
1458     p1=-2.0
1459     dwe=0.3
1460     dpe=0.2
1461     call tablup(k1,k2,m,n,np,nx,no,nt,sco3,scopre,scotem,
1462     * w1,p1,dwe,dpe,o1,o2,o3,trant)
1463     endif
1464    
1465     c***** for trace gases *****
1466    
1467     if (trace) then
1468    
1469     c-----compute n2o transmittance using k-distribution method
1470    
1471     if (n2obnd) then
1472     call n2okdis(ib,m,n,np,k2-1,n2oexp,tn2o,trant)
1473     endif
1474    
1475     c-----compute ch4 transmittance using k-distribution method
1476    
1477     if (ch4bnd) then
1478     call ch4kdis(ib,m,n,np,k2-1,ch4exp,tch4,trant)
1479     endif
1480    
1481     c-----compute co2-minor transmittance using k-distribution method
1482    
1483     if (combnd) then
1484     call comkdis(ib,m,n,np,k2-1,comexp,tcom,trant)
1485     endif
1486    
1487     c-----compute cfc11 transmittance using k-distribution method
1488    
1489     if (f11bnd) then
1490     call cfckdis(m,n,np,k2-1,f11exp,tf11,trant)
1491     endif
1492    
1493     c-----compute cfc12 transmittance using k-distribution method
1494    
1495     if (f12bnd) then
1496     call cfckdis(m,n,np,k2-1,f12exp,tf12,trant)
1497     endif
1498    
1499     c-----compute cfc22 transmittance using k-distribution method
1500    
1501     if (f22bnd) then
1502     call cfckdis(m,n,np,k2-1,f22exp,tf22,trant)
1503     endif
1504    
1505     c-----compute transmittance in band 10 using k-distribution method
1506     c here, trant is the change in transmittance due to n2o absorption
1507    
1508     if (b10bnd) then
1509     call b10kdis(m,n,np,k2-1,h2oexp,conexp,co2exp,n2oexp
1510     * ,th2o,tcon,tco2,tn2o,trant)
1511     endif
1512    
1513     endif
1514     c
1515     c-----include aerosol effect
1516     c
1517     do j=1,n
1518     do i=1,m
1519     ff=0.5+(0.3739+(0.0076+0.1185*asyal(i,j,k2-1,ib))
1520     * *asyal(i,j,k2-1,ib))*asyal(i,j,k2-1,ib)
1521     taux=taual(i,j,k2-1,ib)*(1.-ssaal(i,j,k2-1,ib)*ff)
1522     tranal(i,j)=tranal(i,j)*exp(-1.66*taux)
1523     trant (i,j)=trant(i,j) *tranal(i,j)
1524     enddo
1525     enddo
1526    
1527     c-----Identify the clear-sky fractions clrhi, clrmd and clrlw, in the
1528     c high, middle and low cloud groups.
1529     c fclr is the clear-sky fraction between levels k1 and k2 assuming
1530     c the three cloud groups are randomly overlapped.
1531    
1532     do j=1,n
1533     do i=1,m
1534     if( k2 .le. ict ) then
1535     clrhi(i,j)=min(clr(i,j,k2-1),clrhi(i,j))
1536     elseif( k2 .gt. ict .and. k2 .le. icb ) then
1537     clrmd(i,j)=min(clr(i,j,k2-1),clrmd(i,j))
1538     elseif( k2 .gt. icb ) then
1539     clrlw(i,j)=min(clr(i,j,k2-1),clrlw(i,j))
1540     endif
1541     fclr(i,j)=clrlw(i,j)*clrmd(i,j)*clrhi(i,j)
1542    
1543     enddo
1544     enddo
1545    
1546     c-----compute upward and downward fluxes (band 1-9).
1547     c add "boundary" terms to the net downward flux.
1548     c these are the first terms on the right-hand-side of
1549     c eqs. (56a) and (56b). downward fluxes are positive.
1550    
1551     if (.not. b10bnd) then
1552    
1553     if (k2 .eq. k1+1) then
1554    
1555     do j=1,n
1556     do i=1,m
1557    
1558     c-----compute upward and downward fluxes for clear-sky situation
1559    
1560     flcu(i,j,k1)=flcu(i,j,k1)-blayer(i,j,k1)
1561     flcd(i,j,k2)=flcd(i,j,k2)+blayer(i,j,k1)
1562    
1563     c-----compute upward and downward fluxes for all-sky situation
1564    
1565     flxu(i,j,k1)=flxu(i,j,k1)-blayer(i,j,k1)
1566     flxd(i,j,k2)=flxd(i,j,k2)+blayer(i,j,k1)
1567    
1568     enddo
1569     enddo
1570    
1571     endif
1572    
1573     c-----add flux components involving the four layers above and below
1574     c the levels k1 and k2. it follows eqs. (56a) and (56b).
1575    
1576     do j=1,n
1577     do i=1,m
1578     xx=trant(i,j)*dlayer(i,j,k2)
1579     flcu(i,j,k1) =flcu(i,j,k1)+xx
1580     flxu(i,j,k1) =flxu(i,j,k1)+xx*fclr(i,j)
1581     xx=trant(i,j)*dlayer(i,j,k1)
1582     flcd(i,j,k2) =flcd(i,j,k2)+xx
1583     flxd(i,j,k2) =flxd(i,j,k2)+xx*fclr(i,j)
1584     enddo
1585     enddo
1586    
1587     else
1588    
1589     c-----flux reduction due to n2o in band 10
1590    
1591     if (trace) then
1592    
1593     do j=1,n
1594     do i=1,m
1595     rflx(i,j,k1) = rflx(i,j,k1)+trant(i,j)*fclr(i,j)
1596     * *dlayer(i,j,k2)
1597     rflx(i,j,k2) = rflx(i,j,k2)+trant(i,j)*fclr(i,j)
1598     * *dlayer(i,j,k1)
1599     rflc(i,j,k1) = rflc(i,j,k1)+trant(i,j)
1600     * *dlayer(i,j,k2)
1601     rflc(i,j,k2) = rflc(i,j,k2)+trant(i,j)
1602     * *dlayer(i,j,k1)
1603     enddo
1604     enddo
1605    
1606     endif
1607    
1608     endif
1609    
1610     3000 continue
1611    
1612    
1613     c-----transmission between level k1 and the surface
1614    
1615     do j=1,n
1616     do i=1,m
1617     trantcr(i,j,k1) =trant(i,j)
1618     transfc(i,j,k1) =trant(i,j)*fclr(i,j)
1619     enddo
1620     enddo
1621    
1622     c-----compute the partial derivative of fluxes with respect to
1623     c surface temperature (eq. 59)
1624    
1625     if (trace .or. (.not. b10bnd) ) then
1626    
1627     do j=1,n
1628     do i=1,m
1629     dfdts(i,j,k1) =dfdts(i,j,k1)-dbs(i,j)*transfc(i,j,k1)
1630     enddo
1631     enddo
1632    
1633     endif
1634    
1635     2000 continue
1636    
1637     if (.not. b10bnd) then
1638    
1639     c-----add contribution from the surface to the flux terms at the surface
1640    
1641     do j=1,n
1642     do i=1,m
1643     flcu(i,j,np+1)=flcu(i,j,np+1)-blayer(i,j,np+1)
1644     flxu(i,j,np+1)=flxu(i,j,np+1)-blayer(i,j,np+1)
1645     st4(i,j)=st4(i,j)-blayer(i,j,np+1)
1646     dfdts(i,j,np+1)=dfdts(i,j,np+1)-dbs(i,j)
1647     enddo
1648     enddo
1649    
1650     c-----add the flux component reflected by the surface
1651     c note: upward flux is negative
1652    
1653     do k=1, np+1
1654     do j=1,n
1655     do i=1,m
1656     flcu(i,j,k)=flcu(i,j,k)-
1657     * flcd(i,j,np+1)*trantcr(i,j,k)*(1.-emiss(i,j,ib))
1658     flxu(i,j,k)=flxu(i,j,k)-
1659     * flxd(i,j,np+1)*transfc(i,j,k)*(1.-emiss(i,j,ib))
1660     enddo
1661     enddo
1662     enddo
1663    
1664     endif
1665    
1666     c-----summation of fluxes over spectral bands
1667    
1668     do k=1,np+1
1669     do j=1,n
1670     do i=1,m
1671     flc(i,j,k)=flc(i,j,k)+flcd(i,j,k)+flcu(i,j,k)
1672     flx(i,j,k)=flx(i,j,k)+flxd(i,j,k)+flxu(i,j,k)
1673     enddo
1674     enddo
1675     enddo
1676    
1677     1000 continue
1678    
1679     c-----adjust fluxes due to n2o absorption in band 10
1680    
1681     do k=1,np+1
1682     do j=1,n
1683     do i=1,m
1684     flc(i,j,k)=flc(i,j,k)+rflc(i,j,k)
1685     flx(i,j,k)=flx(i,j,k)+rflx(i,j,k)
1686     enddo
1687     enddo
1688     enddo
1689    
1690     return
1691     end
1692     c***********************************************************************
1693     subroutine column (m,n,np,pa,dt,sabs0,sabs,spre,stem)
1694     c***********************************************************************
1695     c-----compute column-integrated (from top of the model atmosphere)
1696     c absorber amount (sabs), absorber-weighted pressure (spre) and
1697     c temperature (stem).
1698     c computations of spre and stem follows eqs. (37) and (38).
1699     c
1700     c--- input parameters
1701     c number of soundings in zonal direction (m)
1702     c number of soundings in meridional direction (n)
1703     c number of atmospheric layers (np)
1704     c layer pressure (pa)
1705     c layer temperature minus 250K (dt)
1706     c layer absorber amount (sabs0)
1707     c
1708     c--- output parameters
1709     c column-integrated absorber amount (sabs)
1710     c column absorber-weighted pressure (spre)
1711     c column absorber-weighted temperature (stem)
1712     c
1713     c--- units of pa and dt are mb and k, respectively.
1714     c units of sabs are g/cm**2 for water vapor and (cm-atm)stp
1715     c for co2 and o3
1716     c***********************************************************************
1717     implicit none
1718     integer m,n,np,i,j,k
1719    
1720     c---- input parameters -----
1721    
1722 molod 1.10 _RL pa(m,n,np),dt(m,n,np),sabs0(m,n,np)
1723 molod 1.1
1724     c---- output parameters -----
1725    
1726 molod 1.10 _RL sabs(m,n,np+1),spre(m,n,np+1),stem(m,n,np+1)
1727 molod 1.1
1728     c*********************************************************************
1729     do j=1,n
1730     do i=1,m
1731     sabs(i,j,1)=0.0
1732     spre(i,j,1)=0.0
1733     stem(i,j,1)=0.0
1734     enddo
1735     enddo
1736    
1737     do k=1,np
1738     do j=1,n
1739     do i=1,m
1740     sabs(i,j,k+1)=sabs(i,j,k)+sabs0(i,j,k)
1741     spre(i,j,k+1)=spre(i,j,k)+pa(i,j,k)*sabs0(i,j,k)
1742     stem(i,j,k+1)=stem(i,j,k)+dt(i,j,k)*sabs0(i,j,k)
1743     enddo
1744     enddo
1745     enddo
1746    
1747     return
1748     end
1749     c**********************************************************************
1750     subroutine h2oexps(ib,m,n,np,dh2o,pa,dt,xkw,aw,bw,pm,mw,h2oexp)
1751     c**********************************************************************
1752     c compute exponentials for water vapor line absorption
1753     c in individual layers.
1754     c
1755     c---- input parameters
1756     c spectral band (ib)
1757     c number of grid intervals in zonal direction (m)
1758     c number of grid intervals in meridional direction (n)
1759     c number of layers (np)
1760     c layer water vapor amount for line absorption (dh2o)
1761     c layer pressure (pa)
1762     c layer temperature minus 250K (dt)
1763     c absorption coefficients for the first k-distribution
1764     c function due to h2o line absorption (xkw)
1765     c coefficients for the temperature and pressure scaling (aw,bw,pm)
1766     c ratios between neighboring absorption coefficients for
1767     c h2o line absorption (mw)
1768     c
1769     c---- output parameters
1770     c 6 exponentials for each layer (h2oexp)
1771     c**********************************************************************
1772     implicit none
1773     integer ib,m,n,np,i,j,k,ik
1774    
1775     c---- input parameters ------
1776    
1777 molod 1.10 _RL dh2o(m,n,np),pa(m,n,np),dt(m,n,np)
1778 molod 1.1
1779     c---- output parameters -----
1780    
1781 molod 1.10 _RL h2oexp(m,n,np,6)
1782 molod 1.1
1783     c---- static data -----
1784    
1785     integer mw(9)
1786 molod 1.10 _RL xkw(9),aw(9),bw(9),pm(9)
1787 molod 1.1
1788     c---- temporary arrays -----
1789    
1790 molod 1.10 _RL xh,xh1
1791 molod 1.1
1792     c**********************************************************************
1793     c note that the 3 sub-bands in band 3 use the same set of xkw, aw,
1794     c and bw, therefore, h2oexp for these sub-bands are identical.
1795     c**********************************************************************
1796    
1797     do k=1,np
1798     do j=1,n
1799     do i=1,m
1800    
1801     c-----xh is the scaled water vapor amount for line absorption
1802     c computed from (27)
1803    
1804     xh = dh2o(i,j,k)*(pa(i,j,k)/500.)**pm(ib)
1805     1 * ( 1.+(aw(ib)+bw(ib)* dt(i,j,k))*dt(i,j,k) )
1806    
1807     c-----h2oexp is the water vapor transmittance of the layer k
1808     c due to line absorption
1809    
1810     h2oexp(i,j,k,1) = exp(-xh*xkw(ib))
1811    
1812     enddo
1813     enddo
1814     enddo
1815    
1816     do ik=2,6
1817    
1818     if (mw(ib).eq.6) then
1819    
1820     do k=1,np
1821     do j=1,n
1822     do i=1,m
1823     xh = h2oexp(i,j,k,ik-1)*h2oexp(i,j,k,ik-1)
1824     h2oexp(i,j,k,ik) = xh*xh*xh
1825     enddo
1826     enddo
1827     enddo
1828    
1829     elseif (mw(ib).eq.8) then
1830    
1831     do k=1,np
1832     do j=1,n
1833     do i=1,m
1834     xh = h2oexp(i,j,k,ik-1)*h2oexp(i,j,k,ik-1)
1835     xh = xh*xh
1836     h2oexp(i,j,k,ik) = xh*xh
1837     enddo
1838     enddo
1839     enddo
1840    
1841     elseif (mw(ib).eq.9) then
1842    
1843     do k=1,np
1844     do j=1,n
1845     do i=1,m
1846     xh=h2oexp(i,j,k,ik-1)*h2oexp(i,j,k,ik-1)*h2oexp(i,j,k,ik-1)
1847     xh1 = xh*xh
1848     h2oexp(i,j,k,ik) = xh*xh1
1849     enddo
1850     enddo
1851     enddo
1852    
1853     else
1854    
1855     do k=1,np
1856     do j=1,n
1857     do i=1,m
1858     xh = h2oexp(i,j,k,ik-1)*h2oexp(i,j,k,ik-1)
1859     xh = xh*xh
1860     xh = xh*xh
1861     h2oexp(i,j,k,ik) = xh*xh
1862     enddo
1863     enddo
1864     enddo
1865    
1866     endif
1867     enddo
1868    
1869     return
1870     end
1871     c**********************************************************************
1872     subroutine conexps(ib,m,n,np,dcont,xke,conexp)
1873     c**********************************************************************
1874     c compute exponentials for continuum absorption in individual layers.
1875     c
1876     c---- input parameters
1877     c spectral band (ib)
1878     c number of grid intervals in zonal direction (m)
1879     c number of grid intervals in meridional direction (n)
1880     c number of layers (np)
1881     c layer scaled water vapor amount for continuum absorption (dcont)
1882     c absorption coefficients for the first k-distribution function
1883     c due to water vapor continuum absorption (xke)
1884     c
1885     c---- output parameters
1886     c 1 or 3 exponentials for each layer (conexp)
1887     c**********************************************************************
1888     implicit none
1889     integer ib,m,n,np,i,j,k,iq
1890    
1891     c---- input parameters ------
1892    
1893 molod 1.10 _RL dcont(m,n,np)
1894 molod 1.1
1895     c---- updated parameters -----
1896    
1897 molod 1.10 _RL conexp(m,n,np,3)
1898 molod 1.1
1899     c---- static data -----
1900    
1901 molod 1.10 _RL xke(9)
1902 molod 1.1
1903     c**********************************************************************
1904    
1905     do k=1,np
1906     do j=1,n
1907     do i=1,m
1908     conexp(i,j,k,1) = exp(-dcont(i,j,k)*xke(ib))
1909     enddo
1910     enddo
1911     enddo
1912    
1913     if (ib .eq. 3) then
1914    
1915     c-----the absorption coefficients for sub-bands 3b (iq=2) and 3a (iq=3)
1916     c are, respectively, two and three times the absorption coefficient
1917     c for sub-band 3c (iq=1) (table 6).
1918    
1919     do iq=2,3
1920     do k=1,np
1921     do j=1,n
1922     do i=1,m
1923     conexp(i,j,k,iq) = conexp(i,j,k,iq-1) *conexp(i,j,k,iq-1)
1924     enddo
1925     enddo
1926     enddo
1927     enddo
1928    
1929     endif
1930    
1931     return
1932     end
1933     c**********************************************************************
1934     subroutine co2exps(m,n,np,dco2,pa,dt,co2exp)
1935     c**********************************************************************
1936     c compute co2 exponentials for individual layers.
1937     c
1938     c---- input parameters
1939     c number of grid intervals in zonal direction (m)
1940     c number of grid intervals in meridional direction (n)
1941     c number of layers (np)
1942     c layer co2 amount (dco2)
1943     c layer pressure (pa)
1944     c layer temperature minus 250K (dt)
1945     c
1946     c---- output parameters
1947     c 6 exponentials for each layer (co2exp)
1948     c**********************************************************************
1949     implicit none
1950     integer m,n,np,i,j,k
1951    
1952     c---- input parameters -----
1953    
1954 molod 1.10 _RL dco2(m,n,np),pa(m,n,np),dt(m,n,np)
1955 molod 1.1
1956     c---- output parameters -----
1957    
1958 molod 1.10 _RL co2exp(m,n,np,6,2)
1959 molod 1.1
1960     c---- temporary arrays -----
1961    
1962 molod 1.10 _RL xc
1963 molod 1.1
1964     c**********************************************************************
1965    
1966     do k=1,np
1967     do j=1,n
1968     do i=1,m
1969    
1970     c-----compute the scaled co2 amount from eq. (27) for band-wings
1971     c (sub-bands 3a and 3c).
1972    
1973     xc = dco2(i,j,k)*(pa(i,j,k)/300.0)**0.5
1974     1 *(1.+(0.0182+1.07e-4*dt(i,j,k))*dt(i,j,k))
1975    
1976     c-----six exponentials by powers of 8 (table 7).
1977    
1978     co2exp(i,j,k,1,1)=exp(-xc*2.656e-5)
1979    
1980     xc=co2exp(i,j,k,1,1)*co2exp(i,j,k,1,1)
1981     xc=xc*xc
1982     co2exp(i,j,k,2,1)=xc*xc
1983    
1984     xc=co2exp(i,j,k,2,1)*co2exp(i,j,k,2,1)
1985     xc=xc*xc
1986     co2exp(i,j,k,3,1)=xc*xc
1987    
1988     xc=co2exp(i,j,k,3,1)*co2exp(i,j,k,3,1)
1989     xc=xc*xc
1990     co2exp(i,j,k,4,1)=xc*xc
1991    
1992     xc=co2exp(i,j,k,4,1)*co2exp(i,j,k,4,1)
1993     xc=xc*xc
1994     co2exp(i,j,k,5,1)=xc*xc
1995    
1996     xc=co2exp(i,j,k,5,1)*co2exp(i,j,k,5,1)
1997     xc=xc*xc
1998     co2exp(i,j,k,6,1)=xc*xc
1999    
2000     c-----compute the scaled co2 amount from eq. (27) for band-center
2001     c region (sub-band 3b).
2002    
2003     xc = dco2(i,j,k)*(pa(i,j,k)/30.0)**0.85
2004     1 *(1.+(0.0042+2.00e-5*dt(i,j,k))*dt(i,j,k))
2005    
2006     co2exp(i,j,k,1,2)=exp(-xc*2.656e-3)
2007    
2008     xc=co2exp(i,j,k,1,2)*co2exp(i,j,k,1,2)
2009     xc=xc*xc
2010     co2exp(i,j,k,2,2)=xc*xc
2011    
2012     xc=co2exp(i,j,k,2,2)*co2exp(i,j,k,2,2)
2013     xc=xc*xc
2014     co2exp(i,j,k,3,2)=xc*xc
2015    
2016     xc=co2exp(i,j,k,3,2)*co2exp(i,j,k,3,2)
2017     xc=xc*xc
2018     co2exp(i,j,k,4,2)=xc*xc
2019    
2020     xc=co2exp(i,j,k,4,2)*co2exp(i,j,k,4,2)
2021     xc=xc*xc
2022     co2exp(i,j,k,5,2)=xc*xc
2023    
2024     xc=co2exp(i,j,k,5,2)*co2exp(i,j,k,5,2)
2025     xc=xc*xc
2026     co2exp(i,j,k,6,2)=xc*xc
2027    
2028     enddo
2029     enddo
2030     enddo
2031    
2032     return
2033     end
2034     c**********************************************************************
2035     subroutine n2oexps(ib,m,n,np,dn2o,pa,dt,n2oexp)
2036     c**********************************************************************
2037     c compute n2o exponentials for individual layers.
2038     c
2039     c---- input parameters
2040     c spectral band (ib)
2041     c number of grid intervals in zonal direction (m)
2042     c number of grid intervals in meridional direction (n)
2043     c number of layers (np)
2044     c layer n2o amount (dn2o)
2045     c layer pressure (pa)
2046     c layer temperature minus 250K (dt)
2047     c
2048     c---- output parameters
2049     c 2 or 4 exponentials for each layer (n2oexp)
2050     c**********************************************************************
2051     implicit none
2052     integer ib,m,n,np,i,j,k
2053    
2054     c---- input parameters -----
2055    
2056 molod 1.10 _RL dn2o(m,n,np),pa(m,n,np),dt(m,n,np)
2057 molod 1.1
2058     c---- output parameters -----
2059    
2060 molod 1.10 _RL n2oexp(m,n,np,4)
2061 molod 1.1
2062     c---- temporary arrays -----
2063    
2064 molod 1.10 _RL xc,xc1,xc2
2065 molod 1.1
2066     c**********************************************************************
2067    
2068     do k=1,np
2069     do j=1,n
2070     do i=1,m
2071    
2072     c-----four exponential by powers of 21 for band 6
2073    
2074     if (ib.eq.6) then
2075    
2076     xc=dn2o(i,j,k)*(1.+(1.9297e-3+4.3750e-6*dt(i,j,k))*dt(i,j,k))
2077     n2oexp(i,j,k,1)=exp(-xc*6.31582e-2)
2078    
2079     xc=n2oexp(i,j,k,1)*n2oexp(i,j,k,1)*n2oexp(i,j,k,1)
2080     xc1=xc*xc
2081     xc2=xc1*xc1
2082     n2oexp(i,j,k,2)=xc*xc1*xc2
2083    
2084     c-----four exponential by powers of 8 for band 7
2085    
2086     else
2087    
2088     xc=dn2o(i,j,k)*(pa(i,j,k)/500.0)**0.48
2089     * *(1.+(1.3804e-3+7.4838e-6*dt(i,j,k))*dt(i,j,k))
2090     n2oexp(i,j,k,1)=exp(-xc*5.35779e-2)
2091    
2092     xc=n2oexp(i,j,k,1)*n2oexp(i,j,k,1)
2093     xc=xc*xc
2094     n2oexp(i,j,k,2)=xc*xc
2095     xc=n2oexp(i,j,k,2)*n2oexp(i,j,k,2)
2096     xc=xc*xc
2097     n2oexp(i,j,k,3)=xc*xc
2098     xc=n2oexp(i,j,k,3)*n2oexp(i,j,k,3)
2099     xc=xc*xc
2100     n2oexp(i,j,k,4)=xc*xc
2101    
2102     endif
2103    
2104     enddo
2105     enddo
2106     enddo
2107    
2108     return
2109     end
2110     c**********************************************************************
2111     subroutine ch4exps(ib,m,n,np,dch4,pa,dt,ch4exp)
2112     c**********************************************************************
2113     c compute ch4 exponentials for individual layers.
2114     c
2115     c---- input parameters
2116     c spectral band (ib)
2117     c number of grid intervals in zonal direction (m)
2118     c number of grid intervals in meridional direction (n)
2119     c number of layers (np)
2120     c layer ch4 amount (dch4)
2121     c layer pressure (pa)
2122     c layer temperature minus 250K (dt)
2123     c
2124     c---- output parameters
2125     c 1 or 4 exponentials for each layer (ch4exp)
2126     c**********************************************************************
2127     implicit none
2128     integer ib,m,n,np,i,j,k
2129    
2130     c---- input parameters -----
2131    
2132 molod 1.10 _RL dch4(m,n,np),pa(m,n,np),dt(m,n,np)
2133 molod 1.1
2134     c---- output parameters -----
2135    
2136 molod 1.10 _RL ch4exp(m,n,np,4)
2137 molod 1.1
2138     c---- temporary arrays -----
2139    
2140 molod 1.10 _RL xc
2141 molod 1.1
2142     c**********************************************************************
2143    
2144     do k=1,np
2145     do j=1,n
2146     do i=1,m
2147    
2148     c-----four exponentials for band 6
2149    
2150     if (ib.eq.6) then
2151    
2152     xc=dch4(i,j,k)*(1.+(1.7007e-2+1.5826e-4*dt(i,j,k))*dt(i,j,k))
2153     ch4exp(i,j,k,1)=exp(-xc*5.80708e-3)
2154    
2155     c-----four exponentials by powers of 12 for band 7
2156    
2157     else
2158    
2159     xc=dch4(i,j,k)*(pa(i,j,k)/500.0)**0.65
2160     * *(1.+(5.9590e-4-2.2931e-6*dt(i,j,k))*dt(i,j,k))
2161     ch4exp(i,j,k,1)=exp(-xc*6.29247e-2)
2162    
2163     xc=ch4exp(i,j,k,1)*ch4exp(i,j,k,1)*ch4exp(i,j,k,1)
2164     xc=xc*xc
2165     ch4exp(i,j,k,2)=xc*xc
2166    
2167     xc=ch4exp(i,j,k,2)*ch4exp(i,j,k,2)*ch4exp(i,j,k,2)
2168     xc=xc*xc
2169     ch4exp(i,j,k,3)=xc*xc
2170    
2171     xc=ch4exp(i,j,k,3)*ch4exp(i,j,k,3)*ch4exp(i,j,k,3)
2172     xc=xc*xc
2173     ch4exp(i,j,k,4)=xc*xc
2174    
2175     endif
2176    
2177     enddo
2178     enddo
2179     enddo
2180    
2181     return
2182     end
2183     c**********************************************************************
2184     subroutine comexps(ib,m,n,np,dcom,dt,comexp)
2185     c**********************************************************************
2186     c compute co2-minor exponentials for individual layers.
2187     c
2188     c---- input parameters
2189     c spectral band (ib)
2190     c number of grid intervals in zonal direction (m)
2191     c number of grid intervals in meridional direction (n)
2192     c number of layers (np)
2193     c layer co2 amount (dcom)
2194     c layer temperature minus 250K (dt)
2195     c
2196     c---- output parameters
2197     c 2 exponentials for each layer (comexp)
2198     c**********************************************************************
2199     implicit none
2200     integer ib,m,n,np,i,j,k
2201    
2202     c---- input parameters -----
2203    
2204 molod 1.10 _RL dcom(m,n,np),dt(m,n,np)
2205 molod 1.1
2206     c---- output parameters -----
2207    
2208 molod 1.10 _RL comexp(m,n,np,2)
2209 molod 1.1
2210     c---- temporary arrays -----
2211    
2212 molod 1.10 _RL xc,xc1,xc2
2213 molod 1.1
2214     c**********************************************************************
2215    
2216     do k=1,np
2217     do j=1,n
2218     do i=1,m
2219    
2220     c-----two exponentials by powers of 60 for band 4
2221    
2222     if (ib.eq.4) then
2223    
2224     xc=dcom(i,j,k)*(1.+(3.5775e-2+4.0447e-4*dt(i,j,k))*dt(i,j,k))
2225     comexp(i,j,k,1)=exp(-xc*2.18947e-5)
2226    
2227     xc=comexp(i,j,k,1)*comexp(i,j,k,1)*comexp(i,j,k,1)
2228     xc=xc*xc
2229     xc1=xc*xc
2230     xc=xc1*xc1
2231     xc=xc*xc
2232     comexp(i,j,k,2)=xc*xc1
2233    
2234     c-----two exponentials by powers of 44 for band 5
2235    
2236     else
2237    
2238     xc=dcom(i,j,k)*(1.+(3.4268e-2+3.7401e-4*dt(i,j,k))*dt(i,j,k))
2239     comexp(i,j,k,1)=exp(-xc*4.74570e-5)
2240    
2241     xc=comexp(i,j,k,1)*comexp(i,j,k,1)
2242     xc1=xc*xc
2243     xc2=xc1*xc1
2244     xc=xc2*xc2
2245     xc=xc*xc
2246     comexp(i,j,k,2)=xc1*xc2*xc
2247    
2248     endif
2249    
2250     enddo
2251     enddo
2252     enddo
2253    
2254     return
2255     end
2256     c**********************************************************************
2257     subroutine cfcexps(ib,m,n,np,a1,b1,fk1,a2,b2,fk2,dcfc,dt,cfcexp)
2258     c**********************************************************************
2259     c compute cfc(-11, -12, -22) exponentials for individual layers.
2260     c
2261     c---- input parameters
2262     c spectral band (ib)
2263     c number of grid intervals in zonal direction (m)
2264     c number of grid intervals in meridional direction (n)
2265     c number of layers (np)
2266     c parameters for computing the scaled cfc amounts
2267     c for temperature scaling (a1,b1,a2,b2)
2268     c the absorption coefficients for the
2269     c first k-distribution function due to cfcs (fk1,fk2)
2270     c layer cfc amounts (dcfc)
2271     c layer temperature minus 250K (dt)
2272     c
2273     c---- output parameters
2274     c 1 exponential for each layer (cfcexp)
2275     c**********************************************************************
2276     implicit none
2277     integer ib,m,n,np,i,j,k
2278    
2279     c---- input parameters -----
2280    
2281 molod 1.10 _RL dcfc(m,n,np),dt(m,n,np)
2282 molod 1.1
2283     c---- output parameters -----
2284    
2285 molod 1.10 _RL cfcexp(m,n,np)
2286 molod 1.1
2287     c---- static data -----
2288    
2289 molod 1.10 _RL a1,b1,fk1,a2,b2,fk2
2290 molod 1.1
2291     c---- temporary arrays -----
2292    
2293 molod 1.10 _RL xf
2294 molod 1.1
2295     c**********************************************************************
2296    
2297     do k=1,np
2298     do j=1,n
2299     do i=1,m
2300    
2301     c-----compute the scaled cfc amount (xf) and exponential (cfcexp)
2302    
2303     if (ib.eq.4) then
2304     xf=dcfc(i,j,k)*(1.+(a1+b1*dt(i,j,k))*dt(i,j,k))
2305     cfcexp(i,j,k)=exp(-xf*fk1)
2306     else
2307     xf=dcfc(i,j,k)*(1.+(a2+b2*dt(i,j,k))*dt(i,j,k))
2308     cfcexp(i,j,k)=exp(-xf*fk2)
2309     endif
2310    
2311     enddo
2312     enddo
2313     enddo
2314    
2315     return
2316     end
2317     c**********************************************************************
2318     subroutine b10exps(m,n,np,dh2o,dcont,dco2,dn2o,pa,dt
2319     * ,h2oexp,conexp,co2exp,n2oexp)
2320     c**********************************************************************
2321     c compute band3a exponentials for individual layers.
2322     c
2323     c---- input parameters
2324     c number of grid intervals in zonal direction (m)
2325     c number of grid intervals in meridional direction (n)
2326     c number of layers (np)
2327     c layer h2o amount for line absorption (dh2o)
2328     c layer h2o amount for continuum absorption (dcont)
2329     c layer co2 amount (dco2)
2330     c layer n2o amount (dn2o)
2331     c layer pressure (pa)
2332     c layer temperature minus 250K (dt)
2333     c
2334     c---- output parameters
2335     c
2336     c exponentials for each layer (h2oexp,conexp,co2exp,n2oexp)
2337     c**********************************************************************
2338     implicit none
2339     integer m,n,np,i,j,k
2340    
2341     c---- input parameters -----
2342    
2343 molod 1.10 _RL dh2o(m,n,np),dcont(m,n,np),dn2o(m,n,np)
2344     _RL dco2(m,n,np),pa(m,n,np),dt(m,n,np)
2345 molod 1.1
2346     c---- output parameters -----
2347    
2348 molod 1.10 _RL h2oexp(m,n,np,6),conexp(m,n,np,3),co2exp(m,n,np,6,2)
2349 molod 1.1 * ,n2oexp(m,n,np,4)
2350    
2351     c---- temporary arrays -----
2352    
2353 molod 1.10 _RL xx,xx1,xx2,xx3
2354 molod 1.1
2355     c**********************************************************************
2356    
2357     do k=1,np
2358     do j=1,n
2359     do i=1,m
2360    
2361     c-----compute the scaled h2o-line amount for the sub-band 3a
2362     c table 3, Chou et al. (JAS, 1993)
2363    
2364     xx=dh2o(i,j,k)*(pa(i,j,k)/500.0)
2365     1 *(1.+(0.0149+6.20e-5*dt(i,j,k))*dt(i,j,k))
2366    
2367     c-----six exponentials by powers of 8
2368     c the constant 0.10624 is equal to 1.66*0.064
2369    
2370     h2oexp(i,j,k,1)=exp(-xx*0.10624)
2371    
2372     xx=h2oexp(i,j,k,1)*h2oexp(i,j,k,1)
2373     xx=xx*xx
2374     h2oexp(i,j,k,2)=xx*xx
2375    
2376     xx=h2oexp(i,j,k,2)*h2oexp(i,j,k,2)
2377     xx=xx*xx
2378     h2oexp(i,j,k,3)=xx*xx
2379    
2380     xx=h2oexp(i,j,k,3)*h2oexp(i,j,k,3)
2381     xx=xx*xx
2382     h2oexp(i,j,k,4)=xx*xx
2383    
2384     xx=h2oexp(i,j,k,4)*h2oexp(i,j,k,4)
2385     xx=xx*xx
2386     h2oexp(i,j,k,5)=xx*xx
2387    
2388     xx=h2oexp(i,j,k,5)*h2oexp(i,j,k,5)
2389     xx=xx*xx
2390     h2oexp(i,j,k,6)=xx*xx
2391    
2392     c-----compute the scaled co2 amount for the sub-band 3a
2393     c table 1, Chou et al. (JAS, 1993)
2394    
2395     xx=dco2(i,j,k)*(pa(i,j,k)/300.0)**0.5
2396     1 *(1.+(0.0179+1.02e-4*dt(i,j,k))*dt(i,j,k))
2397    
2398     c-----six exponentials by powers of 8
2399     c the constant 2.656e-5 is equal to 1.66*1.60e-5
2400    
2401     co2exp(i,j,k,1,1)=exp(-xx*2.656e-5)
2402    
2403     xx=co2exp(i,j,k,1,1)*co2exp(i,j,k,1,1)
2404     xx=xx*xx
2405     co2exp(i,j,k,2,1)=xx*xx
2406    
2407     xx=co2exp(i,j,k,2,1)*co2exp(i,j,k,2,1)
2408     xx=xx*xx
2409     co2exp(i,j,k,3,1)=xx*xx
2410    
2411     xx=co2exp(i,j,k,3,1)*co2exp(i,j,k,3,1)
2412     xx=xx*xx
2413     co2exp(i,j,k,4,1)=xx*xx
2414    
2415     xx=co2exp(i,j,k,4,1)*co2exp(i,j,k,4,1)
2416     xx=xx*xx
2417     co2exp(i,j,k,5,1)=xx*xx
2418    
2419     xx=co2exp(i,j,k,5,1)*co2exp(i,j,k,5,1)
2420     xx=xx*xx
2421     co2exp(i,j,k,6,1)=xx*xx
2422    
2423     c-----one exponential of h2o continuum for sub-band 3a
2424     c tabl 5 of Chou et. al. (JAS, 1993)
2425     c the constant 1.04995e+2 is equal to 1.66*63.25
2426    
2427     conexp(i,j,k,1)=exp(-dcont(i,j,k)*1.04995e+2)
2428    
2429     c-----compute the scaled n2o amount for sub-band 3a
2430    
2431     xx=dn2o(i,j,k)*(1.+(1.4476e-3+3.6656e-6*dt(i,j,k))*dt(i,j,k))
2432    
2433     c-----two exponential2 by powers of 58
2434    
2435     n2oexp(i,j,k,1)=exp(-xx*0.25238)
2436    
2437     xx=n2oexp(i,j,k,1)*n2oexp(i,j,k,1)
2438     xx1=xx*xx
2439     xx1=xx1*xx1
2440     xx2=xx1*xx1
2441     xx3=xx2*xx2
2442     n2oexp(i,j,k,2)=xx*xx1*xx2*xx3
2443    
2444     enddo
2445     enddo
2446     enddo
2447    
2448     return
2449     end
2450     c**********************************************************************
2451     subroutine tablup(k1,k2,m,n,np,nx,nh,nt,sabs,spre,stem,w1,p1,
2452     * dwe,dpe,coef1,coef2,coef3,tran)
2453     c**********************************************************************
2454     c compute water vapor, co2 and o3 transmittances between levels
2455     c k1 and k2 for m x n soundings, using table look-up.
2456     c
2457     c calculations follow Eq. (40) of Chou and Suarez (1994)
2458     c
2459     c---- input ---------------------
2460     c indices for pressure levels (k1 and k2)
2461     c number of grid intervals in zonal direction (m)
2462     c number of grid intervals in meridional direction (n)
2463     c number of atmospheric layers (np)
2464     c number of pressure intervals in the table (nx)
2465     c number of absorber amount intervals in the table (nh)
2466     c number of tables copied (nt)
2467     c column-integrated absorber amount (sabs)
2468     c column absorber amount-weighted pressure (spre)
2469     c column absorber amount-weighted temperature (stem)
2470     c first value of absorber amount (log10) in the table (w1)
2471     c first value of pressure (log10) in the table (p1)
2472     c size of the interval of absorber amount (log10) in the table (dwe)
2473     c size of the interval of pressure (log10) in the table (dpe)
2474     c pre-computed coefficients (coef1, coef2, and coef3)
2475     c
2476     c---- updated ---------------------
2477     c transmittance (tran)
2478     c
2479     c Note:
2480     c (1) units of sabs are g/cm**2 for water vapor and
2481     c (cm-atm)stp for co2 and o3.
2482     c (2) units of spre and stem are, respectively, mb and K.
2483     c (3) there are nt identical copies of the tables (coef1, coef2, and
2484     c coef3). the prupose of using the multiple copies of tables is
2485     c to increase the speed in parallel (vectorized) computations.
2486     C if such advantage does not exist, nt can be set to 1.
2487     c
2488     c**********************************************************************
2489     implicit none
2490     integer k1,k2,m,n,np,nx,nh,nt,i,j
2491    
2492     c---- input parameters -----
2493    
2494 molod 1.10 _RL w1,p1,dwe,dpe
2495     _RL sabs(m,n,np+1),spre(m,n,np+1),stem(m,n,np+1)
2496     _RL coef1(nx,nh,nt),coef2(nx,nh,nt),coef3(nx,nh,nt)
2497 molod 1.1
2498     c---- update parameter -----
2499    
2500 molod 1.10 _RL tran(m,n)
2501 molod 1.1
2502     c---- temporary variables -----
2503    
2504 molod 1.10 _RL x1,x2,x3,we,pe,fw,fp,pa,pb,pc,ax,ba,bb,t1,ca,cb,t2
2505 molod 1.1 integer iw,ip,nn
2506    
2507     c**********************************************************************
2508    
2509     do j=1,n
2510     do i=1,m
2511    
2512     nn=mod(i,nt)+1
2513    
2514     x1=sabs(i,j,k2)-sabs(i,j,k1)
2515     x2=(spre(i,j,k2)-spre(i,j,k1))/x1
2516     x3=(stem(i,j,k2)-stem(i,j,k1))/x1
2517    
2518     we=(log10(x1)-w1)/dwe
2519     pe=(log10(x2)-p1)/dpe
2520    
2521     we=max(we,w1-2.*dwe)
2522     pe=max(pe,p1)
2523    
2524     iw=int(we+1.5)
2525     ip=int(pe+1.5)
2526    
2527     iw=min(iw,nh-1)
2528     iw=max(iw, 2)
2529    
2530     ip=min(ip,nx-1)
2531     ip=max(ip, 1)
2532    
2533     fw=we-float(iw-1)
2534     fp=pe-float(ip-1)
2535    
2536     c-----linear interpolation in pressure
2537    
2538     pa = coef1(ip,iw-1,nn)*(1.-fp)+coef1(ip+1,iw-1,nn)*fp
2539     pb = coef1(ip,iw, nn)*(1.-fp)+coef1(ip+1,iw, nn)*fp
2540     pc = coef1(ip,iw+1,nn)*(1.-fp)+coef1(ip+1,iw+1,nn)*fp
2541    
2542     c-----quadratic interpolation in absorber amount for coef1
2543    
2544     ax = (-pa*(1.-fw)+pc*(1.+fw)) *fw*0.5 + pb*(1.-fw*fw)
2545    
2546     c-----linear interpolation in absorber amount for coef2 and coef3
2547    
2548     ba = coef2(ip,iw, nn)*(1.-fp)+coef2(ip+1,iw, nn)*fp
2549     bb = coef2(ip,iw+1,nn)*(1.-fp)+coef2(ip+1,iw+1,nn)*fp
2550     t1 = ba*(1.-fw) + bb*fw
2551    
2552     ca = coef3(ip,iw, nn)*(1.-fp)+coef3(ip+1,iw, nn)*fp
2553     cb = coef3(ip,iw+1,nn)*(1.-fp)+coef3(ip+1,iw+1,nn)*fp
2554     t2 = ca*(1.-fw) + cb*fw
2555    
2556     c-----update the total transmittance between levels k1 and k2
2557    
2558     tran(i,j)= (ax + (t1+t2*x3) * x3)*tran(i,j)
2559    
2560     enddo
2561     enddo
2562    
2563     return
2564     end
2565     c**********************************************************************
2566     subroutine h2okdis(ib,m,n,np,k,fkw,gkw,ne,h2oexp,conexp,
2567     * th2o,tcon,tran)
2568     c**********************************************************************
2569     c compute water vapor transmittance between levels k1 and k2 for
2570     c m x n soundings, using the k-distribution method.
2571     c
2572     c computations follow eqs. (34), (46), (50) and (52).
2573     c
2574     c---- input parameters
2575     c spectral band (ib)
2576     c number of grid intervals in zonal direction (m)
2577     c number of grid intervals in meridional direction (n)
2578     c number of levels (np)
2579     c current level (k)
2580     c planck-weighted k-distribution function due to
2581     c h2o line absorption (fkw)
2582     c planck-weighted k-distribution function due to
2583     c h2o continuum absorption (gkw)
2584     c number of terms used in each band to compute water vapor
2585     c continuum transmittance (ne)
2586     c exponentials for line absorption (h2oexp)
2587     c exponentials for continuum absorption (conexp)
2588     c
2589     c---- updated parameters
2590     c transmittance between levels k1 and k2 due to
2591     c water vapor line absorption (th2o)
2592     c transmittance between levels k1 and k2 due to
2593     c water vapor continuum absorption (tcon)
2594     c total transmittance (tran)
2595     c
2596     c**********************************************************************
2597     implicit none
2598     integer ib,m,n,np,k,i,j
2599    
2600     c---- input parameters ------
2601    
2602 molod 1.10 _RL conexp(m,n,np,3),h2oexp(m,n,np,6)
2603 molod 1.1 integer ne(9)
2604 molod 1.10 _RL fkw(6,9),gkw(6,3)
2605 molod 1.1
2606     c---- updated parameters -----
2607    
2608 molod 1.10 _RL th2o(m,n,6),tcon(m,n,3),tran(m,n)
2609 molod 1.1
2610     c---- temporary arrays -----
2611    
2612 molod 1.10 _RL trnth2o
2613 molod 1.1
2614     c-----tco2 are the six exp factors between levels k1 and k2
2615     c tran is the updated total transmittance between levels k1 and k2
2616    
2617     c-----th2o is the 6 exp factors between levels k1 and k2 due to
2618     c h2o line absorption.
2619    
2620     c-----tcon is the 3 exp factors between levels k1 and k2 due to
2621     c h2o continuum absorption.
2622    
2623     c-----trnth2o is the total transmittance between levels k1 and k2 due
2624     c to both line and continuum absorption computed from eq. (52).
2625    
2626     do j=1,n
2627     do i=1,m
2628     th2o(i,j,1) = th2o(i,j,1)*h2oexp(i,j,k,1)
2629     th2o(i,j,2) = th2o(i,j,2)*h2oexp(i,j,k,2)
2630     th2o(i,j,3) = th2o(i,j,3)*h2oexp(i,j,k,3)
2631     th2o(i,j,4) = th2o(i,j,4)*h2oexp(i,j,k,4)
2632     th2o(i,j,5) = th2o(i,j,5)*h2oexp(i,j,k,5)
2633     th2o(i,j,6) = th2o(i,j,6)*h2oexp(i,j,k,6)
2634     enddo
2635     enddo
2636    
2637     if (ne(ib).eq.0) then
2638    
2639     do j=1,n
2640     do i=1,m
2641    
2642     trnth2o =(fkw(1,ib)*th2o(i,j,1)
2643     * + fkw(2,ib)*th2o(i,j,2)
2644     * + fkw(3,ib)*th2o(i,j,3)
2645     * + fkw(4,ib)*th2o(i,j,4)
2646     * + fkw(5,ib)*th2o(i,j,5)
2647     * + fkw(6,ib)*th2o(i,j,6))
2648    
2649     tran(i,j)=tran(i,j)*trnth2o
2650    
2651     enddo
2652     enddo
2653    
2654     elseif (ne(ib).eq.1) then
2655    
2656     do j=1,n
2657     do i=1,m
2658    
2659     tcon(i,j,1)= tcon(i,j,1)*conexp(i,j,k,1)
2660    
2661     trnth2o =(fkw(1,ib)*th2o(i,j,1)
2662     * + fkw(2,ib)*th2o(i,j,2)
2663     * + fkw(3,ib)*th2o(i,j,3)
2664     * + fkw(4,ib)*th2o(i,j,4)
2665     * + fkw(5,ib)*th2o(i,j,5)
2666     * + fkw(6,ib)*th2o(i,j,6))*tcon(i,j,1)
2667    
2668     tran(i,j)=tran(i,j)*trnth2o
2669    
2670     enddo
2671     enddo
2672    
2673     else
2674    
2675     do j=1,n
2676     do i=1,m
2677    
2678     tcon(i,j,1)= tcon(i,j,1)*conexp(i,j,k,1)
2679     tcon(i,j,2)= tcon(i,j,2)*conexp(i,j,k,2)
2680     tcon(i,j,3)= tcon(i,j,3)*conexp(i,j,k,3)
2681    
2682    
2683     trnth2o = ( gkw(1,1)*th2o(i,j,1)
2684     * + gkw(2,1)*th2o(i,j,2)
2685     * + gkw(3,1)*th2o(i,j,3)
2686     * + gkw(4,1)*th2o(i,j,4)
2687     * + gkw(5,1)*th2o(i,j,5)
2688     * + gkw(6,1)*th2o(i,j,6) ) * tcon(i,j,1)
2689     * + ( gkw(1,2)*th2o(i,j,1)
2690     * + gkw(2,2)*th2o(i,j,2)
2691     * + gkw(3,2)*th2o(i,j,3)
2692     * + gkw(4,2)*th2o(i,j,4)
2693     * + gkw(5,2)*th2o(i,j,5)
2694     * + gkw(6,2)*th2o(i,j,6) ) * tcon(i,j,2)
2695     * + ( gkw(1,3)*th2o(i,j,1)
2696     * + gkw(2,3)*th2o(i,j,2)
2697     * + gkw(3,3)*th2o(i,j,3)
2698     * + gkw(4,3)*th2o(i,j,4)
2699     * + gkw(5,3)*th2o(i,j,5)
2700     * + gkw(6,3)*th2o(i,j,6) ) * tcon(i,j,3)
2701    
2702     tran(i,j)=tran(i,j)*trnth2o
2703    
2704     enddo
2705     enddo
2706    
2707     endif
2708    
2709     return
2710     end
2711     c**********************************************************************
2712     subroutine co2kdis(m,n,np,k,co2exp,tco2,tran)
2713     c**********************************************************************
2714     c compute co2 transmittances between levels k1 and k2 for
2715     c m x n soundings, using the k-distribution method with linear
2716     c pressure scaling. computations follow eq. (34).
2717     c
2718     c---- input parameters
2719     c number of grid intervals in zonal direction (m)
2720     c number of grid intervals in meridional direction (n)
2721     c number of levels (np)
2722     c current level (k)
2723     c exponentials for co2 absorption (co2exp)
2724     c
2725     c---- updated parameters
2726     c transmittance between levels k1 and k2 due to co2 absorption
2727     c for the various values of the absorption coefficient (tco2)
2728     c total transmittance (tran)
2729     c
2730     c**********************************************************************
2731     implicit none
2732     integer m,n,np,k,i,j
2733    
2734     c---- input parameters -----
2735    
2736 molod 1.10 _RL co2exp(m,n,np,6,2)
2737 molod 1.1
2738     c---- updated parameters -----
2739    
2740 molod 1.10 _RL tco2(m,n,6,2),tran(m,n)
2741 molod 1.1
2742     c---- temporary arrays -----
2743    
2744 molod 1.10 _RL xc
2745 molod 1.1
2746     c-----tco2 is the 6 exp factors between levels k1 and k2.
2747     c xc is the total co2 transmittance given by eq. (53).
2748    
2749     do j=1,n
2750     do i=1,m
2751    
2752     c-----band-wings
2753    
2754     tco2(i,j,1,1)=tco2(i,j,1,1)*co2exp(i,j,k,1,1)
2755     xc= 0.1395 *tco2(i,j,1,1)
2756    
2757     tco2(i,j,2,1)=tco2(i,j,2,1)*co2exp(i,j,k,2,1)
2758     xc=xc+0.1407 *tco2(i,j,2,1)
2759    
2760     tco2(i,j,3,1)=tco2(i,j,3,1)*co2exp(i,j,k,3,1)
2761     xc=xc+0.1549 *tco2(i,j,3,1)
2762    
2763     tco2(i,j,4,1)=tco2(i,j,4,1)*co2exp(i,j,k,4,1)
2764     xc=xc+0.1357 *tco2(i,j,4,1)
2765    
2766     tco2(i,j,5,1)=tco2(i,j,5,1)*co2exp(i,j,k,5,1)
2767     xc=xc+0.0182 *tco2(i,j,5,1)
2768    
2769     tco2(i,j,6,1)=tco2(i,j,6,1)*co2exp(i,j,k,6,1)
2770     xc=xc+0.0220 *tco2(i,j,6,1)
2771    
2772     c-----band-center region
2773    
2774     tco2(i,j,1,2)=tco2(i,j,1,2)*co2exp(i,j,k,1,2)
2775     xc=xc+0.0766 *tco2(i,j,1,2)
2776    
2777     tco2(i,j,2,2)=tco2(i,j,2,2)*co2exp(i,j,k,2,2)
2778     xc=xc+0.1372 *tco2(i,j,2,2)
2779    
2780     tco2(i,j,3,2)=tco2(i,j,3,2)*co2exp(i,j,k,3,2)
2781     xc=xc+0.1189 *tco2(i,j,3,2)
2782    
2783     tco2(i,j,4,2)=tco2(i,j,4,2)*co2exp(i,j,k,4,2)
2784     xc=xc+0.0335 *tco2(i,j,4,2)
2785    
2786     tco2(i,j,5,2)=tco2(i,j,5,2)*co2exp(i,j,k,5,2)
2787     xc=xc+0.0169 *tco2(i,j,5,2)
2788    
2789     tco2(i,j,6,2)=tco2(i,j,6,2)*co2exp(i,j,k,6,2)
2790     xc=xc+0.0059 *tco2(i,j,6,2)
2791    
2792     tran(i,j)=tran(i,j)*xc
2793    
2794     enddo
2795     enddo
2796    
2797     return
2798     end
2799     c**********************************************************************
2800     subroutine n2okdis(ib,m,n,np,k,n2oexp,tn2o,tran)
2801     c**********************************************************************
2802     c compute n2o transmittances between levels k1 and k2 for
2803     c m x n soundings, using the k-distribution method with linear
2804     c pressure scaling.
2805     c
2806     c---- input parameters
2807     c spectral band (ib)
2808     c number of grid intervals in zonal direction (m)
2809     c number of grid intervals in meridional direction (n)
2810     c number of levels (np)
2811     c current level (k)
2812     c exponentials for n2o absorption (n2oexp)
2813     c
2814     c---- updated parameters
2815     c transmittance between levels k1 and k2 due to n2o absorption
2816     c for the various values of the absorption coefficient (tn2o)
2817     c total transmittance (tran)
2818     c
2819     c**********************************************************************
2820     implicit none
2821     integer ib,m,n,np,k,i,j
2822    
2823     c---- input parameters -----
2824    
2825 molod 1.10 _RL n2oexp(m,n,np,4)
2826 molod 1.1
2827     c---- updated parameters -----
2828    
2829 molod 1.10 _RL tn2o(m,n,4),tran(m,n)
2830 molod 1.1
2831     c---- temporary arrays -----
2832    
2833 molod 1.10 _RL xc
2834 molod 1.1
2835     c-----tn2o is the 2 exp factors between levels k1 and k2.
2836     c xc is the total n2o transmittance
2837    
2838     do j=1,n
2839     do i=1,m
2840    
2841     c-----band 6
2842    
2843     if (ib.eq.6) then
2844    
2845     tn2o(i,j,1)=tn2o(i,j,1)*n2oexp(i,j,k,1)
2846     xc= 0.940414*tn2o(i,j,1)
2847    
2848     tn2o(i,j,2)=tn2o(i,j,2)*n2oexp(i,j,k,2)
2849     xc=xc+0.059586*tn2o(i,j,2)
2850    
2851     c-----band 7
2852    
2853     else
2854    
2855     tn2o(i,j,1)=tn2o(i,j,1)*n2oexp(i,j,k,1)
2856     xc= 0.561961*tn2o(i,j,1)
2857    
2858     tn2o(i,j,2)=tn2o(i,j,2)*n2oexp(i,j,k,2)
2859     xc=xc+0.138707*tn2o(i,j,2)
2860    
2861     tn2o(i,j,3)=tn2o(i,j,3)*n2oexp(i,j,k,3)
2862     xc=xc+0.240670*tn2o(i,j,3)
2863    
2864     tn2o(i,j,4)=tn2o(i,j,4)*n2oexp(i,j,k,4)
2865     xc=xc+0.058662*tn2o(i,j,4)
2866    
2867     endif
2868    
2869     tran(i,j)=tran(i,j)*xc
2870    
2871     enddo
2872     enddo
2873    
2874     return
2875     end
2876     c**********************************************************************
2877     subroutine ch4kdis(ib,m,n,np,k,ch4exp,tch4,tran)
2878     c**********************************************************************
2879     c compute ch4 transmittances between levels k1 and k2 for
2880     c m x n soundings, using the k-distribution method with
2881     c linear pressure scaling.
2882     c
2883     c---- input parameters
2884     c spectral band (ib)
2885     c number of grid intervals in zonal direction (m)
2886     c number of grid intervals in meridional direction (n)
2887     c number of levels (np)
2888     c current level (k)
2889     c exponentials for ch4 absorption (ch4exp)
2890     c
2891     c---- updated parameters
2892     c transmittance between levels k1 and k2 due to ch4 absorption
2893     c for the various values of the absorption coefficient (tch4)
2894     c total transmittance (tran)
2895     c
2896     c**********************************************************************
2897     implicit none
2898     integer ib,m,n,np,k,i,j
2899    
2900     c---- input parameters -----
2901    
2902 molod 1.10 _RL ch4exp(m,n,np,4)
2903 molod 1.1
2904     c---- updated parameters -----
2905    
2906 molod 1.10 _RL tch4(m,n,4),tran(m,n)
2907 molod 1.1
2908     c---- temporary arrays -----
2909    
2910 molod 1.10 _RL xc
2911 molod 1.1
2912     c-----tch4 is the 2 exp factors between levels k1 and k2.
2913     c xc is the total ch4 transmittance
2914    
2915     do j=1,n
2916     do i=1,m
2917    
2918     c-----band 6
2919    
2920     if (ib.eq.6) then
2921    
2922     tch4(i,j,1)=tch4(i,j,1)*ch4exp(i,j,k,1)
2923     xc= tch4(i,j,1)
2924    
2925     c-----band 7
2926    
2927     else
2928    
2929     tch4(i,j,1)=tch4(i,j,1)*ch4exp(i,j,k,1)
2930     xc= 0.610650*tch4(i,j,1)
2931    
2932     tch4(i,j,2)=tch4(i,j,2)*ch4exp(i,j,k,2)
2933     xc=xc+0.280212*tch4(i,j,2)
2934    
2935     tch4(i,j,3)=tch4(i,j,3)*ch4exp(i,j,k,3)
2936     xc=xc+0.107349*tch4(i,j,3)
2937    
2938     tch4(i,j,4)=tch4(i,j,4)*ch4exp(i,j,k,4)
2939     xc=xc+0.001789*tch4(i,j,4)
2940    
2941     endif
2942    
2943     tran(i,j)=tran(i,j)*xc
2944    
2945     enddo
2946     enddo
2947    
2948     return
2949     end
2950     c**********************************************************************
2951     subroutine comkdis(ib,m,n,np,k,comexp,tcom,tran)
2952     c**********************************************************************
2953     c compute co2-minor transmittances between levels k1 and k2
2954     c for m x n soundings, using the k-distribution method
2955     c with linear pressure scaling.
2956     c
2957     c---- input parameters
2958     c spectral band (ib)
2959     c number of grid intervals in zonal direction (m)
2960     c number of grid intervals in meridional direction (n)
2961     c number of levels (np)
2962     c current level (k)
2963     c exponentials for co2-minor absorption (comexp)
2964     c
2965     c---- updated parameters
2966     c transmittance between levels k1 and k2 due to co2-minor absorption
2967     c for the various values of the absorption coefficient (tcom)
2968     c total transmittance (tran)
2969     c
2970     c**********************************************************************
2971     implicit none
2972     integer ib,m,n,np,k,i,j
2973    
2974     c---- input parameters -----
2975    
2976 molod 1.10 _RL comexp(m,n,np,2)
2977 molod 1.1
2978     c---- updated parameters -----
2979    
2980 molod 1.10 _RL tcom(m,n,2),tran(m,n)
2981 molod 1.1
2982     c---- temporary arrays -----
2983    
2984 molod 1.10 _RL xc
2985 molod 1.1
2986     c-----tcom is the 2 exp factors between levels k1 and k2.
2987     c xc is the total co2-minor transmittance
2988    
2989     do j=1,n
2990     do i=1,m
2991    
2992     c-----band 4
2993    
2994     if (ib.eq.4) then
2995    
2996     tcom(i,j,1)=tcom(i,j,1)*comexp(i,j,k,1)
2997     xc= 0.972025*tcom(i,j,1)
2998     tcom(i,j,2)=tcom(i,j,2)*comexp(i,j,k,2)
2999     xc=xc+0.027975*tcom(i,j,2)
3000    
3001     c-----band 5
3002    
3003     else
3004    
3005     tcom(i,j,1)=tcom(i,j,1)*comexp(i,j,k,1)
3006     xc= 0.961324*tcom(i,j,1)
3007     tcom(i,j,2)=tcom(i,j,2)*comexp(i,j,k,2)
3008     xc=xc+0.038676*tcom(i,j,2)
3009    
3010     endif
3011    
3012     tran(i,j)=tran(i,j)*xc
3013    
3014     enddo
3015     enddo
3016    
3017     return
3018     end
3019     c**********************************************************************
3020     subroutine cfckdis(m,n,np,k,cfcexp,tcfc,tran)
3021     c**********************************************************************
3022     c compute cfc-(11,12,22) transmittances between levels k1 and k2
3023     c for m x n soundings, using the k-distribution method with
3024     c linear pressure scaling.
3025     c
3026     c---- input parameters
3027     c number of grid intervals in zonal direction (m)
3028     c number of grid intervals in meridional direction (n)
3029     c number of levels (np)
3030     c current level (k)
3031     c exponentials for cfc absorption (cfcexp)
3032     c
3033     c---- updated parameters
3034     c transmittance between levels k1 and k2 due to cfc absorption
3035     c for the various values of the absorption coefficient (tcfc)
3036     c total transmittance (tran)
3037     c
3038     c**********************************************************************
3039     implicit none
3040     integer m,n,np,k,i,j
3041    
3042     c---- input parameters -----
3043    
3044 molod 1.10 _RL cfcexp(m,n,np)
3045 molod 1.1
3046     c---- updated parameters -----
3047    
3048 molod 1.10 _RL tcfc(m,n),tran(m,n)
3049 molod 1.1
3050     c-----tcfc is the exp factors between levels k1 and k2.
3051    
3052     do j=1,n
3053     do i=1,m
3054    
3055     tcfc(i,j)=tcfc(i,j)*cfcexp(i,j,k)
3056     tran(i,j)=tran(i,j)*tcfc(i,j)
3057    
3058     enddo
3059     enddo
3060    
3061     return
3062     end
3063     c**********************************************************************
3064     subroutine b10kdis(m,n,np,k,h2oexp,conexp,co2exp,n2oexp
3065     * ,th2o,tcon,tco2,tn2o,tran)
3066     c**********************************************************************
3067     c
3068     c compute h2o (line and continuum),co2,n2o transmittances between
3069     c levels k1 and k2 for m x n soundings, using the k-distribution
3070     c method with linear pressure scaling.
3071     c
3072     c---- input parameters
3073     c number of grid intervals in zonal direction (m)
3074     c number of grid intervals in meridional direction (n)
3075     c number of levels (np)
3076     c current level (k)
3077     c exponentials for h2o line absorption (h2oexp)
3078     c exponentials for h2o continuum absorption (conexp)
3079     c exponentials for co2 absorption (co2exp)
3080     c exponentials for n2o absorption (n2oexp)
3081     c
3082     c---- updated parameters
3083     c transmittance between levels k1 and k2 due to h2o line absorption
3084     c for the various values of the absorption coefficient (th2o)
3085     c transmittance between levels k1 and k2 due to h2o continuum
3086     c absorption for the various values of the absorption
3087     c coefficient (tcon)
3088     c transmittance between levels k1 and k2 due to co2 absorption
3089     c for the various values of the absorption coefficient (tco2)
3090     c transmittance between levels k1 and k2 due to n2o absorption
3091     c for the various values of the absorption coefficient (tn2o)
3092     c total transmittance (tran)
3093     c
3094     c**********************************************************************
3095     implicit none
3096     integer m,n,np,k,i,j
3097    
3098     c---- input parameters -----
3099    
3100 molod 1.10 _RL h2oexp(m,n,np,6),conexp(m,n,np,3),co2exp(m,n,np,6,2)
3101 molod 1.1 * ,n2oexp(m,n,np,4)
3102    
3103     c---- updated parameters -----
3104    
3105 molod 1.10 _RL th2o(m,n,6),tcon(m,n,3),tco2(m,n,6,2),tn2o(m,n,4)
3106 molod 1.1 * ,tran(m,n)
3107    
3108     c---- temporary arrays -----
3109    
3110 molod 1.10 _RL xx
3111 molod 1.1
3112     c-----initialize tran
3113    
3114     do j=1,n
3115     do i=1,m
3116     tran(i,j)=1.0
3117     enddo
3118     enddo
3119    
3120     c-----for h2o line
3121    
3122     do j=1,n
3123     do i=1,m
3124    
3125     th2o(i,j,1)=th2o(i,j,1)*h2oexp(i,j,k,1)
3126     xx= 0.3153*th2o(i,j,1)
3127    
3128     th2o(i,j,2)=th2o(i,j,2)*h2oexp(i,j,k,2)
3129     xx=xx+0.4604*th2o(i,j,2)
3130    
3131     th2o(i,j,3)=th2o(i,j,3)*h2oexp(i,j,k,3)
3132     xx=xx+0.1326*th2o(i,j,3)
3133    
3134     th2o(i,j,4)=th2o(i,j,4)*h2oexp(i,j,k,4)
3135     xx=xx+0.0798*th2o(i,j,4)
3136    
3137     th2o(i,j,5)=th2o(i,j,5)*h2oexp(i,j,k,5)
3138     xx=xx+0.0119*th2o(i,j,5)
3139    
3140     tran(i,j)=tran(i,j)*xx
3141    
3142     enddo
3143     enddo
3144    
3145     c-----for h2o continuum
3146    
3147     do j=1,n
3148     do i=1,m
3149    
3150     tcon(i,j,1)=tcon(i,j,1)*conexp(i,j,k,1)
3151     tran(i,j)=tran(i,j)*tcon(i,j,1)
3152    
3153     enddo
3154     enddo
3155    
3156     c-----for co2
3157    
3158     do j=1,n
3159     do i=1,m
3160    
3161     tco2(i,j,1,1)=tco2(i,j,1,1)*co2exp(i,j,k,1,1)
3162     xx= 0.2673*tco2(i,j,1,1)
3163    
3164     tco2(i,j,2,1)=tco2(i,j,2,1)*co2exp(i,j,k,2,1)
3165     xx=xx+ 0.2201*tco2(i,j,2,1)
3166    
3167     tco2(i,j,3,1)=tco2(i,j,3,1)*co2exp(i,j,k,3,1)
3168     xx=xx+ 0.2106*tco2(i,j,3,1)
3169    
3170     tco2(i,j,4,1)=tco2(i,j,4,1)*co2exp(i,j,k,4,1)
3171     xx=xx+ 0.2409*tco2(i,j,4,1)
3172    
3173     tco2(i,j,5,1)=tco2(i,j,5,1)*co2exp(i,j,k,5,1)
3174     xx=xx+ 0.0196*tco2(i,j,5,1)
3175    
3176     tco2(i,j,6,1)=tco2(i,j,6,1)*co2exp(i,j,k,6,1)
3177     xx=xx+ 0.0415*tco2(i,j,6,1)
3178    
3179     tran(i,j)=tran(i,j)*xx
3180    
3181     enddo
3182     enddo
3183    
3184     c-----for n2o
3185    
3186     do j=1,n
3187     do i=1,m
3188    
3189     tn2o(i,j,1)=tn2o(i,j,1)*n2oexp(i,j,k,1)
3190     xx= 0.970831*tn2o(i,j,1)
3191    
3192     tn2o(i,j,2)=tn2o(i,j,2)*n2oexp(i,j,k,2)
3193     xx=xx+0.029169*tn2o(i,j,2)
3194    
3195     tran(i,j)=tran(i,j)*(xx-1.0)
3196    
3197     enddo
3198     enddo
3199    
3200     return
3201     end

  ViewVC Help
Powered by ViewVC 1.1.22