/[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.25 - (hide annotations) (download)
Fri Jun 17 16:51:24 2005 UTC (19 years ago) by ce107
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, checkpoint57v_post, checkpoint58u_post, checkpoint58w_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint60, checkpoint61, checkpoint62, checkpoint58r_post, checkpoint57i_post, checkpoint57y_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58q_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint57r_post, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint58p_post, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint57j_post, checkpoint61z, checkpoint61x, checkpoint61y, checkpoint58b_post, checkpoint58m_post, checkpoint57l_post
Changes since 1.24: +4 -3 lines
Fixed length of lines with _d 0 additions to 72 chars

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

  ViewVC Help
Powered by ViewVC 1.1.22