/[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.13 - (hide annotations) (download)
Thu Jul 29 22:49:34 2004 UTC (19 years, 11 months ago) by molod
Branch: MAIN
Changes since 1.12: +4 -1 lines
debugging

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

  ViewVC Help
Powered by ViewVC 1.1.22