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

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

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


Revision 1.17 - (show annotations) (download)
Thu Aug 12 15:21:22 2004 UTC (19 years, 10 months ago) by molod
Branch: MAIN
Changes since 1.16: +55 -12 lines
Debugging - Code for work-around for input vegetation dataset

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

  ViewVC Help
Powered by ViewVC 1.1.22