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

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

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


Revision 1.12 - (hide annotations) (download)
Mon Jul 26 18:45:17 2004 UTC (19 years, 10 months ago) by molod
Branch: MAIN
Changes since 1.11: +144 -147 lines
Went to use of FIZHI_OPTIONS and _RL in all routines

1 molod 1.12 C $Header: /u/gcmpack/MITgcm/pkg/fizhi/fizhi_swrad.F,v 1.11 2004/07/16 20:08:08 molod Exp $
2 molod 1.1 C $Name: $
3 molod 1.2
4 molod 1.12 #include "FIZHI_OPTIONS.h"
5 molod 1.4 subroutine swrio (nymd,nhms,bi,bj,ndswr,myid,istrip,npcs,
6 molod 1.5 . low_level,mid_level,
7     . pz,plz,plze,dpres,pkht,pkz,tz,qz,oz,co2,
8 molod 1.2 . albvisdr,albvisdf,albnirdr,albnirdf,
9 molod 1.3 . dtradsw,dtswclr,radswg,swgclr,
10 molod 1.2 . fdifpar,fdirpar,osr,osrclr,
11 molod 1.5 . im,jm,lm,ptop,
12 molod 1.2 . nswcld,cldsw,cswmo,nswlz,swlz,
13     . lpnt,imstturb,qliqave,fccave,landtype,xlats,xlons)
14 molod 1.1
15     implicit none
16 molod 1.2 #ifdef ALLOW_DIAGNOSTICS
17 molod 1.7 #include "SIZE.h"
18     #include "diagnostics_SIZE.h"
19 molod 1.2 #include "diagnostics.h"
20     #endif
21 molod 1.1
22     c Input Variables
23     c ---------------
24 molod 1.5 integer nymd,nhms,bi,bj,ndswr,myid,istrip,npcs
25     integer mid_level,low_level
26 molod 1.2 integer im,jm,lm
27 molod 1.12 _RL ptop
28     _RL pz(im,jm),plz(im,jm,lm),plze(im,jm,lm+1),dpres(im,jm,lm)
29     _RL pkht(im,jm,lm+1),pkz(im,jm,lm)
30     _RL tz(im,jm,lm),qz(im,jm,lm)
31     _RL oz(im,jm,lm)
32     _RL co2
33     _RL albvisdr(im,jm),albvisdf(im,jm),albnirdr(im,jm)
34     _RL albnirdf(im,jm)
35     _RL radswg(im,jm),swgclr(im,jm),fdifpar(im,jm),fdirpar(im,jm)
36     _RL osr(im,jm),osrclr(im,jm),dtradsw(im,jm,lm),dtswclr(im,jm,lm)
37 molod 1.2 integer nswcld,nswlz
38 molod 1.12 _RL cldsw(im,jm,lm),cswmo(im,jm,lm),swlz(im,jm,lm)
39 molod 1.2 logical lpnt
40     integer imstturb
41 molod 1.12 _RL qliqave(im,jm,lm),fccave(im,jm,lm)
42 molod 1.2 integer landtype(im,jm)
43 molod 1.12 _RL xlats(im,jm),xlons(im,jm)
44 molod 1.1
45     c Local Variables
46     c ---------------
47 molod 1.5 integer i,j,L,nn,nsecf
48 molod 1.8 integer ntmstp,nymd2,nhms2
49 molod 1.12 _RL getcon,grav,cp,undef
50     _RL ra,alf,reffw,reffi,tminv
51 molod 1.1
52 molod 1.2 parameter ( reffw = 10.0 )
53     parameter ( reffi = 65.0 )
54 molod 1.1
55 molod 1.12 _RL tdry(im,jm,lm)
56     _RL TEMP1(im,jm)
57     _RL TEMP2(im,jm)
58     _RL zenith (im,jm)
59     _RL cldtot (im,jm,lm)
60     _RL cldmxo (im,jm,lm)
61     _RL totcld (im,jm)
62     _RL cldlow (im,jm)
63     _RL cldmid (im,jm)
64     _RL cldhi (im,jm)
65     _RL taulow (im,jm)
66     _RL taumid (im,jm)
67     _RL tauhi (im,jm)
68     _RL tautype(im,jm,lm,3)
69     _RL tau(im,jm,lm)
70     _RL albedo(im,jm)
71    
72     _RL PK(ISTRIP,lm)
73     _RL qzl(ISTRIP,lm),CLRO(ISTRIP,lm)
74     _RL TZL(ISTRIP,lm)
75     _RL OZL(ISTRIP,lm)
76     _RL PLE(ISTRIP,lm+1)
77     _RL COSZ(ISTRIP)
78     _RL dpstrip(ISTRIP,lm)
79    
80     _RL albuvdr(ISTRIP),albuvdf(ISTRIP)
81     _RL albirdr(ISTRIP),albirdf(ISTRIP)
82     _RL difpar (ISTRIP),dirpar (ISTRIP)
83    
84     _RL fdirir(istrip),fdifir(istrip)
85     _RL fdiruv(istrip),fdifuv(istrip)
86    
87     _RL flux(istrip,lm+1)
88     _RL fluxclr(istrip,lm+1)
89     _RL dtsw(istrip,lm)
90     _RL dtswc(istrip,lm)
91    
92     _RL taul (istrip,lm)
93     _RL reff (istrip,lm,2)
94     _RL tauc (istrip,lm,2)
95     _RL taua (istrip,lm)
96     _RL tstrip (istrip)
97 molod 1.1
98 molod 1.5 logical first
99     data first /.true./
100 molod 1.1
101     C **********************************************************************
102     C **** INITIALIZATION ****
103     C **********************************************************************
104    
105     grav = getcon('GRAVITY')
106     cp = getcon('CP')
107     undef = getcon('UNDEF')
108    
109     NTMSTP = nsecf(NDSWR)
110     TMINV = 1./float(ntmstp)
111    
112     C Compute Temperature from Theta
113     C ------------------------------
114     do L=1,lm
115     do j=1,jm
116     do i=1,im
117     tdry(i,j,L) = tz(i,j,L)*pkz(i,j,L)
118     enddo
119     enddo
120     enddo
121    
122     if (first .and. myid.eq.0 ) then
123     print *
124     print *,'Low-Level Clouds are Grouped between levels: ',
125     . lm,' and ',low_level
126     print *,'Mid-Level Clouds are Grouped between levels: ',
127     . low_level-1,' and ',mid_level
128     print *
129     first = .false.
130     endif
131    
132     C **********************************************************************
133     C **** CALCULATE COSINE OF THE ZENITH ANGLE ****
134     C **********************************************************************
135    
136 molod 1.5 CALL ASTRO ( NYMD, NHMS, XLATS,XLONS, im*jm, TEMP1,RA )
137 molod 1.1 NYMD2 = NYMD
138     NHMS2 = NHMS
139     CALL TICK ( NYMD2, NHMS2, NTMSTP )
140 molod 1.5 CALL ASTRO ( NYMD2, NHMS2, XLATS,XLONS, im*jm, TEMP2,RA )
141 molod 1.1
142     do j = 1,jm
143     do i = 1,im
144     zenith(I,j) = TEMP1(I,j) + TEMP2(I,j)
145     IF( zenith(I,j) .GT. 0.0 ) THEN
146     zenith(I,j) = (2./3.)*( zenith(I,j)-TEMP2(I,j)*TEMP1(I,j)
147     . / zenith(I,j) )
148     ENDIF
149     ENDDO
150     ENDDO
151    
152    
153     C **********************************************************************
154     c **** Compute Two-Dimension Total Cloud Fraction (0-1) ****
155     C **********************************************************************
156    
157     c Initialize Clear Sky Probability for Low, Mid, and High Clouds
158     c --------------------------------------------------------------
159     do j =1,jm
160     do i =1,im
161     cldlow(i,j) = 0.0
162     cldmid(i,j) = 0.0
163     cldhi (i,j) = 0.0
164     enddo
165     enddo
166    
167     c Adjust cloud fractions and cloud liquid water due to moist turbulence
168     c ---------------------------------------------------------------------
169     if(imstturb.ne.0) then
170     do L =1,lm
171     do j =1,jm
172     do i =1,im
173 molod 1.2 cldtot(i,j,L)=min(1.0,max(cldsw(i,j,L),fccave(i,j,L)/imstturb))
174     cldmxo(i,j,L)=min(1.0,cswmo(i,j,L))
175     swlz(i,j,L)=swlz(i,j,L)+qliqave(i,j,L)/imstturb
176 molod 1.1 enddo
177     enddo
178     enddo
179     else
180     do L =1,lm
181     do j =1,jm
182     do i =1,im
183     cldtot(i,j,L) = min( 1.0,cldsw(i,j,L) )
184     cldmxo(i,j,L) = min( 1.0,cswmo(i,j,L) )
185     enddo
186     enddo
187     enddo
188     endif
189    
190     c Compute 3-D Cloud Fractions
191     c ---------------------------
192     if( nswcld.ne.0 ) then
193     do L = 1,lm
194     do j = 1,jm
195     do i = 1,im
196     c Compute Low-Mid-High Maximum Overlap Cloud Fractions
197     c ----------------------------------------------------
198     if( L.lt.mid_level ) then
199     cldhi (i,j) = max( cldtot(i,j,L),cldhi (i,j) )
200     elseif( L.ge.mid_level .and.
201     . L.lt.low_level ) then
202     cldmid(i,j) = max( cldtot(i,j,L),cldmid(i,j) )
203     elseif( L.ge.low_level ) then
204     cldlow(i,j) = max( cldtot(i,j,L),cldlow(i,j) )
205     endif
206    
207     enddo
208     enddo
209     enddo
210     endif
211    
212     c Totcld => Product of Clear Sky Probabilities for Low, Mid, and High Clouds
213     c --------------------------------------------------------------------------
214     do j = 1,jm
215     do i = 1,im
216     totcld(i,j) = 1.0 - (1.-cldhi (i,j))
217     . * (1.-cldmid(i,j))
218     . * (1.-cldlow(i,j))
219     enddo
220     enddo
221    
222     c Compute Cloud Diagnostics
223     c -------------------------
224     if(icldfrc.gt.0) then
225     do j=1,jm
226     do i=1,im
227 molod 1.4 qdiag(i,j,icldfrc,bi,bj) = qdiag(i,j,icldfrc,bi,bj) + totcld(i,j)
228 molod 1.1 enddo
229     enddo
230     ncldfrc = ncldfrc + 1
231     endif
232    
233     if( icldras.gt.0 ) then
234     do L=1,lm
235     do j=1,jm
236     do i=1,im
237 molod 1.4 qdiag(i,j,icldras+L-1,bi,bj) = qdiag(i,j,icldras+L-1,bi,bj) +
238     . cswmo(i,j,L)
239 molod 1.1 enddo
240     enddo
241     enddo
242     ncldras = ncldras + 1
243     endif
244    
245     if( icldtot.gt.0 ) then
246     do L=1,lm
247     do j=1,jm
248     do i=1,im
249 molod 1.4 qdiag(i,j,icldtot+L-1,bi,bj) = qdiag(i,j,icldtot+L-1,bi,bj) +
250     . cldtot(i,j,L)
251 molod 1.1 enddo
252     enddo
253     enddo
254     ncldtot = ncldtot + 1
255     endif
256    
257     if( icldlow.gt.0 ) then
258     do j=1,jm
259     do i=1,im
260 molod 1.4 qdiag(i,j,icldlow,bi,bj) = qdiag(i,j,icldlow,bi,bj) + cldlow(i,j)
261 molod 1.1 enddo
262     enddo
263     ncldlow = ncldlow + 1
264     endif
265    
266     if( icldmid.gt.0 ) then
267     do j=1,jm
268     do i=1,im
269 molod 1.4 qdiag(i,j,icldmid,bi,bj) = qdiag(i,j,icldmid,bi,bj) + cldmid(i,j)
270 molod 1.1 enddo
271     enddo
272     ncldmid = ncldmid + 1
273     endif
274    
275     if( icldhi.gt.0 ) then
276     do j=1,jm
277     do i=1,im
278 molod 1.4 qdiag(i,j,icldhi,bi,bj) = qdiag(i,j,icldhi,bi,bj) + cldhi(i,j)
279 molod 1.1 enddo
280     enddo
281     ncldhi = ncldhi + 1
282     endif
283    
284     if( ilzrad.gt.0 ) then
285     do L=1,lm
286     do j=1,jm
287     do i=1,im
288 molod 1.4 qdiag(i,j,ilzrad+L-1,bi,bj) = qdiag(i,j,ilzrad+L-1,bi,bj) +
289     . swlz(i,j,L)*1.0e6
290 molod 1.1 enddo
291     enddo
292     enddo
293     nlzrad = nlzrad + 1
294     endif
295    
296     c Albedo Diagnostics
297     c ------------------
298     if( ialbvisdr.gt.0 ) then
299     do j=1,jm
300     do i=1,im
301 molod 1.4 qdiag(i,j,ialbvisdr,bi,bj) = qdiag(i,j,ialbvisdr,bi,bj) +
302     . albvisdr(i,j)
303 molod 1.1 enddo
304     enddo
305     nalbvisdr = nalbvisdr + 1
306     endif
307    
308     if( ialbvisdf.gt.0 ) then
309     do j=1,jm
310     do i=1,im
311 molod 1.4 qdiag(i,j,ialbvisdf,bi,bj) = qdiag(i,j,ialbvisdf,bi,bj) +
312     . albvisdf(i,j)
313 molod 1.1 enddo
314     enddo
315     nalbvisdf = nalbvisdf + 1
316     endif
317    
318     if( ialbnirdr.gt.0 ) then
319     do j=1,jm
320     do i=1,im
321 molod 1.4 qdiag(i,j,ialbnirdr,bi,bj) = qdiag(i,j,ialbnirdr,bi,bj) +
322     . albnirdr(i,j)
323 molod 1.1 enddo
324     enddo
325     nalbnirdr = nalbnirdr + 1
326     endif
327    
328     if( ialbnirdf.gt.0 ) then
329     do j=1,jm
330     do i=1,im
331 molod 1.4 qdiag(i,j,ialbnirdf,bi,bj) = qdiag(i,j,ialbnirdf,bi,bj) +
332     . albnirdf(i,j)
333 molod 1.1 enddo
334     enddo
335     nalbnirdf = nalbnirdf + 1
336     endif
337    
338     C Compute Optical Thicknesses and Diagnostics
339     C -------------------------------------------
340 molod 1.2 call opthk(tdry,plz,plze,swlz,cldtot,cldmxo,landtype,im,jm,lm,
341     . tautype)
342 molod 1.1
343     do L = 1,lm
344     do j = 1,jm
345     do i = 1,im
346 molod 1.2 tau(i,j,L) = tautype(i,j,L,1)+tautype(i,j,L,2)+tautype(i,j,L,3)
347 molod 1.1 enddo
348     enddo
349     enddo
350    
351     if( itauave.gt.0 ) then
352     do L=1,lm
353     do j=1,jm
354     do i=1,im
355 molod 1.4 qdiag(i,j,itauave+L-1,bi,bj) = qdiag(i,j,itauave+L-1,bi,bj) +
356 molod 1.2 . tau(i,j,L)*100/(plze(i,j,L+1)-plze(i,j,L))
357 molod 1.1 enddo
358     enddo
359     enddo
360     ntauave = ntauave + 1
361     endif
362    
363     if( itaucld.gt.0 ) then
364     do L=1,lm
365     do j=1,jm
366     do i=1,im
367 molod 1.2 if( cldtot(i,j,L).ne.0.0 ) then
368 molod 1.4 qdiag(i,j,itaucld +L-1,bi,bj) = qdiag(i,j,itaucld +L-1,bi,bj) +
369 molod 1.2 . tau(i,j,L)*100/(plze(i,j,L+1)-plze(i,j,L))
370 molod 1.4 qdiag(i,j,itaucldc+L-1,bi,bj) =
371     . qdiag(i,j,itaucldc+L-1,bi,bj) + 1.0
372 molod 1.2 endif
373 molod 1.1 enddo
374     enddo
375     enddo
376     endif
377    
378     c Compute Low, Mid, and High Cloud Optical Depth Diagnostics
379     c ----------------------------------------------------------
380     if( itaulow.ne.0 ) then
381 molod 1.4 do j = 1,jm
382     do i = 1,im
383     if( cldlow(i,j).ne.0.0 ) then
384     taulow(i,j) = 0.0
385     do L = low_level,lm
386     taulow(i,j) = taulow(i,j) + tau(i,j,L)
387     enddo
388     qdiag(i,j,itaulow,bi,bj ) = qdiag(i,j,itaulow,bi,bj ) +
389     . taulow(i,j)
390     qdiag(i,j,itaulowc,bi,bj) = qdiag(i,j,itaulowc,bi,bj) + 1.0
391     endif
392     enddo
393     enddo
394 molod 1.1 endif
395    
396     if( itaumid.ne.0 ) then
397 molod 1.4 do j = 1,jm
398     do i = 1,im
399     if( cldmid(i,j).ne.0.0 ) then
400     taumid(i,j) = 0.0
401     do L = mid_level,low_level+1
402     taumid(i,j) = taumid(i,j) + tau(i,j,L)
403     enddo
404     qdiag(i,j,itaumid,bi,bj ) = qdiag(i,j,itaumid,bi,bj ) +
405     . taumid(i,j)
406     qdiag(i,j,itaumidc,bi,bj) = qdiag(i,j,itaumidc,bi,bj) + 1.0
407     endif
408     enddo
409     enddo
410 molod 1.1 endif
411    
412     if( itauhi.ne.0 ) then
413 molod 1.4 do j = 1,jm
414     do i = 1,im
415     if( cldhi(i,j).ne.0.0 ) then
416     tauhi(i,j) = 0.0
417     do L = 1,mid_level+1
418     tauhi(i,j) = tauhi(i,j) + tau(i,j,L)
419     enddo
420     qdiag(i,j,itauhi,bi,bj ) = qdiag(i,j,itauhi,bi,bj ) +
421     . tauhi(i,j)
422     qdiag(i,j,itauhic,bi,bj) = qdiag(i,j,itauhic,bi,bj) + 1.0
423     endif
424     enddo
425     enddo
426 molod 1.1 endif
427    
428     C***********************************************************************
429     C **** LOOP OVER GLOBAL REGIONS ****
430     C **********************************************************************
431    
432     do 1000 nn = 1,npcs
433    
434     C **********************************************************************
435     C **** VARIABLE INITIALIZATION ****
436     C **********************************************************************
437    
438     CALL STRIP ( zenith,COSZ,im*jm,ISTRIP,1,NN )
439    
440 molod 1.5 CALL STRIP ( plze, ple ,im*jm,ISTRIP,lm+1,NN)
441     CALL STRIP ( pkz , pk ,im*jm,ISTRIP,lm ,NN)
442     CALL STRIP ( dpres,dpstrip,im*jm,ISTRIP,lm ,NN)
443     CALL STRIP ( tdry, tzl ,im*jm,ISTRIP,lm ,NN)
444     CALL STRIP ( qz , qzl ,im*jm,ISTRIP,lm ,NN)
445     CALL STRIP ( oz , ozl ,im*jm,ISTRIP,lm ,NN)
446     CALL STRIP ( tau , taul ,im*jm,ISTRIP,lm ,NN)
447 molod 1.1
448     CALL STRIP ( albvisdr,albuvdr,im*jm,ISTRIP,1,NN )
449     CALL STRIP ( albvisdf,albuvdf,im*jm,ISTRIP,1,NN )
450     CALL STRIP ( albnirdr,albirdr,im*jm,ISTRIP,1,NN )
451     CALL STRIP ( albnirdf,albirdf,im*jm,ISTRIP,1,NN )
452    
453     call strip ( cldtot,clro,im*jm,istrip,lm,nn )
454    
455     c Partition Tau between Water and Ice Particles
456     c ---------------------------------------------
457     do L= 1,lm
458     do i= 1,istrip
459     alf = min( max((tzl(i,l)-253.15)/20.,0.) ,1.)
460     taua(i,L) = 0.
461    
462     if( alf.ne.0.0 .and. alf.ne.1.0 ) then
463     tauc(i,L,1) = taul(i,L)/(1.+alf/(1-alf) * (reffi/reffw*0.80) )
464     tauc(i,L,2) = taul(i,L)/(1.+(1-alf)/alf * (reffw/reffi*1.25) )
465     endif
466    
467     if( alf.eq.0.0 ) then
468     tauc(i,L,1) = taul(i,L)
469     tauc(i,L,2) = 0.0
470     endif
471    
472     if( alf.eq.1.0 ) then
473     tauc(i,L,1) = 0.0
474     tauc(i,L,2) = taul(i,L)
475     endif
476    
477     reff(i,L,1) = reffi
478     reff(i,L,2) = reffw
479     enddo
480     enddo
481    
482     call sorad ( istrip,1,1,lm,ple,tzl,qzl,ozl,co2,
483     . tauc,reff,clro,mid_level,low_level,taua,
484     . albirdr,albirdf,albuvdr,albuvdf,cosz,
485     . flux,fluxclr,fdirir,fdifir,dirpar,difpar,
486     . fdiruv,fdifuv )
487    
488     C **********************************************************************
489     C **** Compute Mass-Weighted Theta Tendencies from Fluxes ****
490     C **********************************************************************
491    
492     do l=1,lm
493     do i=1,istrip
494 molod 1.5 alf = grav*(ple(i,L+1)-ptop)/(cp*dpstrip(i,L)*100)
495 molod 1.1 dtsw (i,L) = alf*( flux (i,L)-flux (i,L+1) )/pk(i,L)
496     dtswc(i,L) = alf*( fluxclr(i,L)-fluxclr(i,L+1) )/pk(i,L)
497     enddo
498     enddo
499    
500     call paste ( dtsw , dtradsw ,istrip,im*jm,lm,nn )
501     call paste ( dtswc, dtswclr ,istrip,im*jm,lm,nn )
502    
503     call paste ( flux (1,1),osr ,istrip,im*jm,1,nn )
504     call paste ( fluxclr(1,1),osrclr,istrip,im*jm,1,nn )
505    
506     call paste ( flux (1,lm+1),radswg,istrip,im*jm,1,nn )
507     call paste ( fluxclr(1,lm+1),swgclr,istrip,im*jm,1,nn )
508    
509     call paste ( dirpar,fdirpar,istrip,im*jm,1,nn )
510     call paste ( difpar,fdifpar,istrip,im*jm,1,nn )
511    
512     c Calculate Mean Albedo
513     c ---------------------
514     do i=1,istrip
515 molod 1.2 if( cosz(i).gt.0.0 ) then
516     tstrip(i) = 1.0 - flux(i,lm+1)/
517     . ( fdirir(i)+fdifir(i)+dirpar(i)+difpar(i) + fdiruv(i)+fdifuv(i) )
518 molod 1.1 if( tstrip(i).lt.0.0 ) tstrip(i) = undef
519 molod 1.2 else
520     tstrip(i) = undef
521     endif
522 molod 1.1 enddo
523     call paste ( tstrip,albedo,istrip,im*jm,1,nn )
524    
525     1000 CONTINUE
526    
527     c Mean Albedo Diagnostic
528     c ----------------------
529     if( ialbedo.gt.0 ) then
530     do j=1,jm
531     do i=1,im
532     if( albedo(i,j).ne.undef ) then
533 molod 1.4 qdiag(i,j,ialbedo,bi,bj ) = qdiag(i,j,ialbedo,bi,bj )+albedo(i,j)
534     qdiag(i,j,ialbedoc,bi,bj) = qdiag(i,j,ialbedoc,bi,bj) + 1.0
535 molod 1.1 endif
536     enddo
537     enddo
538     endif
539    
540     C **********************************************************************
541     C **** ZERO-OUT OR BUMP COUNTERS ****
542     C **********************************************************************
543    
544     nswlz = 0
545     nswcld = 0
546     imstturb = 0
547    
548     do L = 1,lm
549     do j = 1,jm
550     do i = 1,im
551     fccave(i,j,L) = 0.
552     qliqave(i,j,L) = 0.
553     enddo
554     enddo
555     enddo
556    
557     return
558     end
559     subroutine opthk ( tl,pl,ple,lz,cf,cfm,lwi,im,jm,lm,tau )
560     C***********************************************************************
561     C
562     C PURPOSE:
563     C ========
564     C Compute cloud optical thickness using temperature and
565     C cloud fractions.
566     C
567     C INPUT:
568     C ======
569     C tl ......... Temperature at Model Layers (K)
570     C pl ......... Model Layer Pressures (mb)
571     C ple ........ Model Edge Pressures (mb)
572     C lz ......... Diagnosed Convective and Large-Scale Cloud Water (g/g)
573     C cf ......... Total Cloud Fraction (Random + Maximum Overlap)
574     C cfm ........ Maximum Overlap Cloud Fraction
575     C lwi ........ Surface Land Type
576     C im ......... Longitudinal dimension
577     C jm ......... Latitudinal dimension
578     C lm ......... Vertical dimension
579     C
580     C OUTPUT:
581     C =======
582     C tau ........ Cloud Optical Thickness (non-dimensional)
583     C tau(im,jm,lm,1): Suspended Ice
584     C tau(im,jm,lm,2): Suspended Water
585     C tau(im,jm,lm,3): Raindrops
586     C
587     C***********************************************************************
588    
589     implicit none
590    
591     integer im,jm,lm,i,j,L
592    
593 molod 1.12 _RL tl(im,jm,lm)
594     _RL pl(im,jm,lm)
595     _RL ple(im,jm,lm+1)
596     _RL lz(im,jm,lm)
597     _RL cf(im,jm,lm)
598     _RL cfm(im,jm,lm)
599     _RL tau(im,jm,lm,3)
600 molod 1.1 integer lwi(im,jm)
601    
602 molod 1.12 _RL dp, alf, fracls, fraccu
603     _RL tauice, tauh2o, tauras
604 molod 1.1
605     c Compute Cloud Optical Depths
606     c ----------------------------
607     do L=1,lm
608     do j=1,jm
609     do i=1,im
610     alf = min( max(( tl(i,j,L)-233.15)/20.,0.) ,1.)
611     dp = ple(i,j,L+1)-ple(i,j,L)
612     tau(i,j,L,1) = 0.0
613     tau(i,j,L,2) = 0.0
614     tau(i,j,L,3) = 0.0
615     if( cf(i,j,L).ne.0.0 ) then
616    
617     c Determine fraction of large-scale and cumulus clouds
618     c ----------------------------------------------------
619     fracls = ( cf(i,j,L)-cfm(i,j,L) )/cf(i,j,L)
620     fraccu = 1.0-fracls
621    
622     c Define tau for large-scale ice and water clouds
623     c Note: tauice is scaled between (0.02 & .2) for: 0 < lz < 2 mg/kg over Land
624     c Note: tauh2o is scaled between (0.20 & 20) for: 0 < lz < 5 mg/kg over Land
625     c Note: tauh2o is scaled between (0.20 & 12) for: 0 < lz < 50 mg/kg over Ocean
626     c -------------------------------------------------------------------------------
627    
628     c Large-Scale Ice
629     c ---------------
630     tauice = max( 0.0002, 0.002*min(500*lz(i,j,L)*1000,1.0) )
631     tau(i,j,L,1) = fracls*(1-alf)*tauice*dp
632    
633     c Large-Scale Water
634     c -----------------
635 molod 1.2 C Over Land
636 molod 1.1 if( lwi(i,j).le.10 ) then
637 molod 1.2 tauh2o = max( 0.0020, 0.200*min(200*lz(i,j,L)*1000,1.0) )
638     tau(i,j,L,3) = fracls*alf*tauh2o*dp
639 molod 1.1 else
640 molod 1.2 C Non-Precipitation Clouds Over Ocean
641     if( lz(i,j,L).eq.0.0 ) then
642     tauh2o = .12
643     tau(i,j,L,2) = fracls*alf*tauh2o*dp
644     else
645     C Over Ocean
646     tauh2o = max( 0.0020, 0.120*min( 20*lz(i,j,L)*1000,1.0) )
647     tau(i,j,L,3) = fracls*alf*tauh2o*dp
648     endif
649 molod 1.1 endif
650    
651     c Sub-Grid Convective
652     c -------------------
653     if( tl(i,j,L).gt.210.0 ) then
654     tauras = .16
655     tau(i,j,L,3) = tau(i,j,L,3) + fraccu*tauras*dp
656     else
657     tauras = tauice
658     tau(i,j,L,1) = tau(i,j,L,1) + fraccu*tauras*dp
659     endif
660    
661     c Define tau for large-scale and cumulus clouds
662     c ---------------------------------------------
663     ccc tau(i,j,L) = ( fracls*( alf*tauh2o + (1-alf)*tauice )
664     ccc . + fraccu*tauras )*dp
665    
666     endif
667    
668     enddo
669     enddo
670     enddo
671    
672     return
673     end
674     subroutine sorad(m,n,ndim,np,pl,ta,wa,oa,co2,
675     * taucld,reff,fcld,ict,icb,
676     * taual,rsirbm,rsirdf,rsuvbm,rsuvdf,cosz,
677     * flx,flc,fdirir,fdifir,fdirpar,fdifpar,
678     * fdiruv,fdifuv)
679     c********************************************************************
680     c
681     c This routine computes solar fluxes due to the absoption by water
682     c vapor, ozone, co2, o2, clouds, and aerosols and due to the
683     c scattering by clouds, aerosols, and gases.
684     c
685     c This is a vectorized code. It computes the fluxes simultaneous for
686     c (m x n) soundings, which is a subset of the (m x ndim) soundings.
687     c In a global climate model, m and ndim correspond to the numbers of
688     c grid boxes in the zonal and meridional directions, respectively.
689     c
690     c Ice and liquid cloud particles are allowed to co-exist in any of the
691     c np layers. Two sets of cloud parameters are required as inputs, one
692     c for ice paticles and the other for liquid particles. These parameters
693     c are optical thickness (taucld) and effective particle size (reff).
694     c
695     c If no information is available for reff, a default value of
696     c 10 micron for liquid water and 75 micron for ice can be used.
697     c
698     c Clouds are grouped into high, middle, and low clouds separated by the
699     c level indices ict and icb. For detail, see the subroutine cldscale.
700     c
701     c----- Input parameters:
702     c units size
703     c number of soundings in zonal direction (m) n/d 1
704     c number of soundings in meridional direction (n) n/d 1
705     c maximum number of soundings in n/d 1
706     c meridional direction (ndim)
707     c number of atmospheric layers (np) n/d 1
708     c level pressure (pl) mb m*ndim*(np+1)
709     c layer temperature (ta) k m*ndim*np
710     c layer specific humidity (wa) gm/gm m*ndim*np
711     c layer ozone concentration (oa) gm/gm m*ndim*np
712     c co2 mixing ratio by volumn (co2) parts/part 1
713     c cloud optical thickness (taucld) n/d m*ndim*np*2
714     c index 1 for ice particles
715     c index 2 for liquid drops
716     c effective cloud-particle size (reff) micrometer m*ndim*np*2
717     c index 1 for ice particles
718     c index 2 for liquid drops
719     c cloud amount (fcld) fraction m*ndim*np
720     c level index separating high and middle n/d 1
721     c clouds (ict)
722     c level index separating middle and low clouds n/d 1
723     c clouds (icb)
724     c aerosol optical thickness (taual) n/d m*ndim*np
725     c solar ir surface albedo for beam fraction m*ndim
726     c radiation (rsirbm)
727     c solar ir surface albedo for diffuse fraction m*ndim
728     c radiation (rsirdf)
729     c uv + par surface albedo for beam fraction m*ndim
730     c radiation (rsuvbm)
731     c uv + par surface albedo for diffuse fraction m*ndim
732     c radiation (rsuvdf)
733     c cosine of solar zenith angle (cosz) n/d m*ndim
734     c
735     c----- Output parameters
736     c
737     c all-sky flux (downward minus upward) (flx) fraction m*ndim*(np+1)
738     c clear-sky flux (downward minus upward) (flc) fraction m*ndim*(np+1)
739     c all-sky direct downward ir (0.7-10 micron)
740     c flux at the surface (fdirir) fraction m*ndim
741     c all-sky diffuse downward ir flux at
742     c the surface (fdifir) fraction m*ndim
743     c all-sky direct downward par (0.4-0.7 micron)
744     c flux at the surface (fdirpar) fraction m*ndim
745     c all-sky diffuse downward par flux at
746     c the surface (fdifpar) fraction m*ndim
747     *
748     c----- Notes:
749     c
750     c (1) The unit of flux is fraction of the incoming solar radiation
751     c at the top of the atmosphere. Therefore, fluxes should
752     c be equal to flux multiplied by the extra-terrestrial solar
753     c flux and the cosine of solar zenith angle.
754     c (2) Clouds and aerosols can be included in any layers by specifying
755     c fcld(i,j,k), taucld(i,j,k,*) and taual(i,j,k), k=1,np.
756     c For an atmosphere without clouds and aerosols,
757     c set fcld(i,j,k)=taucld(i,j,k,*)=taual(i,j,k)=0.0.
758     c (3) Aerosol single scattering albedos and asymmetry
759     c factors are specified in the subroutines solir and soluv.
760     c (4) pl(i,j,1) is the pressure at the top of the model, and
761     c pl(i,j,np+1) is the surface pressure.
762     c (5) the pressure levels ict and icb correspond approximately
763     c to 400 and 700 mb.
764     c
765     c**************************************************************************
766    
767     implicit none
768    
769     c-----Explicit Inline Directives
770    
771 molod 1.11 #ifdef CRAY
772     #ifdef f77
773 molod 1.1 cfpp$ expand (expmn)
774     #endif
775     #endif
776 molod 1.12 _RL expmn
777 molod 1.1
778     c-----input parameters
779    
780     integer m,n,ndim,np,ict,icb
781 molod 1.12 _RL pl(m,ndim,np+1),ta(m,ndim,np),wa(m,ndim,np),oa(m,ndim,np)
782     _RL taucld(m,ndim,np,2),reff(m,ndim,np,2)
783     _RL fcld(m,ndim,np),taual(m,ndim,np)
784     _RL rsirbm(m,ndim),rsirdf(m,ndim),
785 molod 1.1 * rsuvbm(m,ndim),rsuvdf(m,ndim),cosz(m,ndim),co2
786    
787     c-----output parameters
788    
789 molod 1.12 _RL flx(m,ndim,np+1),flc(m,ndim,np+1)
790     _RL fdirir(m,ndim),fdifir(m,ndim)
791     _RL fdirpar(m,ndim),fdifpar(m,ndim)
792     _RL fdiruv(m,ndim),fdifuv(m,ndim)
793 molod 1.1
794     c-----temporary array
795    
796 molod 1.10 integer i,j,k
797 molod 1.12 _RL cc(m,n,3),tauclb(m,n,np),tauclf(m,n,np)
798     _RL dp(m,n,np),wh(m,n,np),oh(m,n,np),scal(m,n,np)
799     _RL swh(m,n,np+1),so2(m,n,np+1),df(m,n,np+1)
800     _RL sdf(m,n),sclr(m,n),csm(m,n),x
801 molod 1.1
802     c-----------------------------------------------------------------
803    
804     do j= 1, n
805     do i= 1, m
806    
807     swh(i,j,1)=0.
808     so2(i,j,1)=0.
809    
810     c-----csm is the effective secant of the solar zenith angle
811     c see equation (12) of Lacis and Hansen (1974, JAS)
812    
813     csm(i,j)=35./sqrt(1224.*cosz(i,j)*cosz(i,j)+1.)
814    
815     enddo
816     enddo
817    
818    
819     do k= 1, np
820     do j= 1, n
821     do i= 1, m
822    
823     c-----compute layer thickness and pressure-scaling function.
824     c indices for the surface level and surface layer
825     c are np+1 and np, respectively.
826    
827     dp(i,j,k)=pl(i,j,k+1)-pl(i,j,k)
828     scal(i,j,k)=dp(i,j,k)*(.5*(pl(i,j,k)+pl(i,j,k+1))/300.)**.8
829    
830     c-----compute scaled water vapor amount, unit is g/cm**2
831    
832     wh(i,j,k)=1.02*wa(i,j,k)*scal(i,j,k)*
833     * (1.+0.00135*(ta(i,j,k)-240.))
834     swh(i,j,k+1)=swh(i,j,k)+wh(i,j,k)
835    
836     c-----compute ozone amount, unit is (cm-atm)stp.
837    
838     oh(i,j,k)=1.02*oa(i,j,k)*dp(i,j,k)*466.7
839    
840     enddo
841     enddo
842     enddo
843    
844    
845     c-----scale cloud optical thickness in each layer from taucld (with
846     c cloud amount fcld) to tauclb and tauclf (with cloud amount cc).
847     c tauclb is the scaled optical thickness for beam radiation and
848     c tauclf is for diffuse radiation.
849    
850     call cldscale(m,n,ndim,np,cosz,fcld,taucld,ict,icb,
851     * cc,tauclb,tauclf)
852    
853     c-----initialize fluxes for all-sky (flx), clear-sky (flc), and
854     c flux reduction (df)
855    
856     do k=1, np+1
857     do j=1, n
858     do i=1, m
859     flx(i,j,k)=0.
860     flc(i,j,k)=0.
861     df(i,j,k)=0.
862     enddo
863     enddo
864     enddo
865    
866     c-----compute solar ir fluxes
867    
868     call solir (m,n,ndim,np,wh,taucld,tauclb,tauclf,reff,ict,icb
869     * ,fcld,cc,taual,csm,rsirbm,rsirdf,flx,flc,fdirir,fdifir)
870    
871     c-----compute and update uv and par fluxes
872    
873     call soluv (m,n,ndim,np,oh,dp,taucld,tauclb,tauclf,reff,ict,icb
874     * ,fcld,cc,taual,csm,rsuvbm,rsuvdf,flx,flc
875     * ,fdirpar,fdifpar,fdiruv,fdifuv)
876    
877     c-----compute scaled amount of o2 (so2), unit is (cm-atm)stp.
878    
879     do k= 1, np
880     do j= 1, n
881     do i= 1, m
882     so2(i,j,k+1)=so2(i,j,k)+165.22*scal(i,j,k)
883     enddo
884     enddo
885     enddo
886    
887     c-----compute flux reduction due to oxygen following
888     c chou (J. climate, 1990). The fraction 0.0287 is the
889     c extraterrestrial solar flux in the o2 bands.
890    
891     do k= 2, np+1
892     do j= 1, n
893     do i= 1, m
894     x=so2(i,j,k)*csm(i,j)
895     df(i,j,k)=df(i,j,k)+0.0287*(1.-expmn(-0.00027*sqrt(x)))
896     enddo
897     enddo
898     enddo
899    
900     c-----compute scaled amounts for co2 (so2). unit is (cm-atm)stp.
901    
902     do k= 1, np
903     do j= 1, n
904     do i= 1, m
905     so2(i,j,k+1)=so2(i,j,k)+co2*789.*scal(i,j,k)
906     enddo
907     enddo
908     enddo
909    
910     c-----compute and update flux reduction due to co2 following
911     c chou (J. Climate, 1990)
912    
913     call flxco2(m,n,np,so2,swh,csm,df)
914    
915     c-----adjust for the effect of o2 cnd co2 on clear-sky fluxes.
916    
917     do k= 2, np+1
918     do j= 1, n
919     do i= 1, m
920     flc(i,j,k)=flc(i,j,k)-df(i,j,k)
921     enddo
922     enddo
923     enddo
924    
925     c-----adjust for the all-sky fluxes due to o2 and co2. It is
926     c assumed that o2 and co2 have no effects on solar radiation
927     c below clouds. clouds are assumed randomly overlapped.
928    
929     do j=1,n
930     do i=1,m
931     sdf(i,j)=0.0
932     sclr(i,j)=1.0
933     enddo
934     enddo
935    
936     do k=1,np
937     do j=1,n
938     do i=1,m
939    
940     c-----sclr is the fraction of clear sky.
941     c sdf is the flux reduction below clouds.
942    
943     if(fcld(i,j,k).gt.0.01) then
944     sdf(i,j)=sdf(i,j)+df(i,j,k)*sclr(i,j)*fcld(i,j,k)
945     sclr(i,j)=sclr(i,j)*(1.-fcld(i,j,k))
946     endif
947     flx(i,j,k+1)=flx(i,j,k+1)-sdf(i,j)-df(i,j,k+1)*sclr(i,j)
948    
949     enddo
950     enddo
951     enddo
952    
953     c-----adjust for the direct downward ir flux.
954     do j= 1, n
955     do i= 1, m
956     x = (1.-rsirdf(i,j))*fdifir(i,j) + (1.-rsirbm(i,j))*fdirir(i,j)
957     x = (-sdf(i,j)-df(i,j,np+1)*sclr(i,j))/x
958     fdirir(i,j)=fdirir(i,j)*(1.+x)
959     fdifir(i,j)=fdifir(i,j)*(1.+x)
960     enddo
961     enddo
962    
963     return
964     end
965    
966     c********************************************************************
967    
968     subroutine cldscale (m,n,ndim,np,cosz,fcld,taucld,ict,icb,
969     * cc,tauclb,tauclf)
970    
971     c********************************************************************
972     c
973     c This subroutine computes the covers of high, middle, and
974     c low clouds and scales the cloud optical thickness.
975     c
976     c To simplify calculations in a cloudy atmosphere, clouds are
977     c grouped into high, middle and low clouds separated by the levels
978     c ict and icb (level 1 is the top of the atmosphere).
979     c
980     c Within each of the three groups, clouds are assumed maximally
981     c overlapped, and the cloud cover (cc) of a group is the maximum
982     c cloud cover of all the layers in the group. The optical thickness
983     c (taucld) of a given layer is then scaled to new values (tauclb and
984     c tauclf) so that the layer reflectance corresponding to the cloud
985     c cover cc is the same as the original reflectance with optical
986     c thickness taucld and cloud cover fcld.
987     c
988     c---input parameters
989     c
990     c number of grid intervals in zonal direction (m)
991     c number of grid intervals in meridional direction (n)
992     c maximum number of grid intervals in meridional direction (ndim)
993     c number of atmospheric layers (np)
994     c cosine of the solar zenith angle (cosz)
995     c fractional cloud cover (fcld)
996     c cloud optical thickness (taucld)
997     c index separating high and middle clouds (ict)
998     c index separating middle and low clouds (icb)
999     c
1000     c---output parameters
1001     c
1002     c fractional cover of high, middle, and low clouds (cc)
1003     c scaled cloud optical thickness for beam radiation (tauclb)
1004     c scaled cloud optical thickness for diffuse radiation (tauclf)
1005     c
1006     c********************************************************************
1007    
1008     implicit none
1009    
1010     c-----input parameters
1011    
1012     integer m,n,ndim,np,ict,icb
1013 molod 1.12 _RL cosz(m,ndim),fcld(m,ndim,np),taucld(m,ndim,np,2)
1014 molod 1.1
1015     c-----output parameters
1016    
1017 molod 1.12 _RL cc(m,n,3),tauclb(m,n,np),tauclf(m,n,np)
1018 molod 1.1
1019     c-----temporary variables
1020    
1021     integer i,j,k,im,it,ia,kk
1022 molod 1.12 _RL fm,ft,fa,xai,taux
1023 molod 1.1
1024     c-----pre-computed table
1025    
1026     integer nm,nt,na
1027     parameter (nm=11,nt=9,na=11)
1028 molod 1.12 _RL dm,dt,da,t1,caib(nm,nt,na),caif(nt,na)
1029 molod 1.1 parameter (dm=0.1,dt=0.30103,da=0.1,t1=-0.9031)
1030    
1031     c-----include the pre-computed table for cai
1032    
1033 molod 1.8 #include "cai-dat.h"
1034 molod 1.9 c save caib,caif
1035 molod 1.1
1036    
1037     c-----clouds within each of the high, middle, and low clouds are
1038     c assumed maximally overlapped, and the cloud cover (cc)
1039     c for a group is the maximum cloud cover of all the layers
1040     c in the group
1041    
1042     do j=1,n
1043     do i=1,m
1044     cc(i,j,1)=0.0
1045     cc(i,j,2)=0.0
1046     cc(i,j,3)=0.0
1047     enddo
1048     enddo
1049    
1050     do k=1,ict-1
1051     do j=1,n
1052     do i=1,m
1053     cc(i,j,1)=max(cc(i,j,1),fcld(i,j,k))
1054     enddo
1055     enddo
1056     enddo
1057    
1058     do k=ict,icb-1
1059     do j=1,n
1060     do i=1,m
1061     cc(i,j,2)=max(cc(i,j,2),fcld(i,j,k))
1062     enddo
1063     enddo
1064     enddo
1065    
1066     do k=icb,np
1067     do j=1,n
1068     do i=1,m
1069     cc(i,j,3)=max(cc(i,j,3),fcld(i,j,k))
1070     enddo
1071     enddo
1072     enddo
1073    
1074     c-----scale the cloud optical thickness.
1075     c taucld(i,j,k,1) is the optical thickness for ice particles, and
1076     c taucld(i,j,k,2) is the optical thickness for liquid particles.
1077    
1078     do k=1,np
1079    
1080     if(k.lt.ict) then
1081     kk=1
1082     elseif(k.ge.ict .and. k.lt.icb) then
1083     kk=2
1084     else
1085     kk=3
1086     endif
1087    
1088     do j=1,n
1089     do i=1,m
1090    
1091     tauclb(i,j,k) = 0.0
1092     tauclf(i,j,k) = 0.0
1093    
1094     taux=taucld(i,j,k,1)+taucld(i,j,k,2)
1095     if (taux.gt.0.05 .and. fcld(i,j,k).gt.0.01) then
1096    
1097     c-----normalize cloud cover
1098    
1099     fa=fcld(i,j,k)/cc(i,j,kk)
1100    
1101     c-----table look-up
1102    
1103     taux=min(taux,32.)
1104    
1105     fm=cosz(i,j)/dm
1106     ft=(log10(taux)-t1)/dt
1107     fa=fa/da
1108    
1109     im=int(fm+1.5)
1110     it=int(ft+1.5)
1111     ia=int(fa+1.5)
1112    
1113     im=max(im,2)
1114     it=max(it,2)
1115     ia=max(ia,2)
1116    
1117     im=min(im,nm-1)
1118     it=min(it,nt-1)
1119     ia=min(ia,na-1)
1120    
1121     fm=fm-float(im-1)
1122     ft=ft-float(it-1)
1123     fa=fa-float(ia-1)
1124    
1125     c-----scale cloud optical thickness for beam radiation.
1126     c the scaling factor, xai, is a function of the solar zenith
1127     c angle, optical thickness, and cloud cover.
1128    
1129     xai= (-caib(im-1,it,ia)*(1.-fm)+
1130     * caib(im+1,it,ia)*(1.+fm))*fm*.5+caib(im,it,ia)*(1.-fm*fm)
1131    
1132     xai=xai+(-caib(im,it-1,ia)*(1.-ft)+
1133     * caib(im,it+1,ia)*(1.+ft))*ft*.5+caib(im,it,ia)*(1.-ft*ft)
1134    
1135     xai=xai+(-caib(im,it,ia-1)*(1.-fa)+
1136     * caib(im,it,ia+1)*(1.+fa))*fa*.5+caib(im,it,ia)*(1.-fa*fa)
1137    
1138     xai= xai-2.*caib(im,it,ia)
1139     xai=max(xai,0.0)
1140    
1141     tauclb(i,j,k) = taux*xai
1142    
1143     c-----scale cloud optical thickness for diffuse radiation.
1144     c the scaling factor, xai, is a function of the cloud optical
1145     c thickness and cover but not the solar zenith angle.
1146    
1147     xai= (-caif(it-1,ia)*(1.-ft)+
1148     * caif(it+1,ia)*(1.+ft))*ft*.5+caif(it,ia)*(1.-ft*ft)
1149    
1150     xai=xai+(-caif(it,ia-1)*(1.-fa)+
1151     * caif(it,ia+1)*(1.+fa))*fa*.5+caif(it,ia)*(1.-fa*fa)
1152    
1153     xai= xai-caif(it,ia)
1154     xai=max(xai,0.0)
1155    
1156     tauclf(i,j,k) = taux*xai
1157    
1158     endif
1159    
1160     enddo
1161     enddo
1162     enddo
1163    
1164     return
1165     end
1166     c***********************************************************************
1167    
1168     subroutine solir (m,n,ndim,np,wh,taucld,tauclb,tauclf,reff,
1169     * ict,icb,fcld,cc,taual,csm,rsirbm,rsirdf,flx,flc,fdirir,fdifir)
1170    
1171     c************************************************************************
1172     c compute solar flux in the infrared region. The spectrum is divided
1173     c into three bands:
1174     c
1175     c band wavenumber(/cm) wavelength (micron)
1176     c 1 1000-4400 2.27-10.0
1177     c 2 4400-8200 1.22-2.27
1178     c 3 8200-14300 0.70-1.22
1179     c
1180     c----- Input parameters: units size
1181     c
1182     c number of soundings in zonal direction (m) n/d 1
1183     c number of soundings in meridional direction (n) n/d 1
1184     c maximum number of soundings in n/d 1
1185     c meridional direction (ndim)
1186     c number of atmospheric layers (np) n/d 1
1187     c layer water vapor content (wh) gm/cm^2 m*n*np
1188     c cloud optical thickness (taucld) n/d m*ndim*np*2
1189     c index 1 for ice paticles
1190     c index 2 for liquid particles
1191     c scaled cloud optical thickness n/d m*n*np
1192     c for beam radiation (tauclb)
1193     c scaled cloud optical thickness n/d m*n*np
1194     c for diffuse radiation (tauclf)
1195     c effective cloud-particle size (reff) micrometer m*ndim*np*2
1196     c index 1 for ice paticles
1197     c index 2 for liquid particles
1198     c level index separating high and n/d m*n
1199     c middle clouds (ict)
1200     c level index separating middle and n/d m*n
1201     c low clouds (icb)
1202     c cloud amount (fcld) fraction m*ndim*np
1203     c cloud amount of high, middle, and n/d m*n*3
1204     c low clouds (cc)
1205     c aerosol optical thickness (taual) n/d m*ndim*np
1206     c cosecant of the solar zenith angle (csm) n/d m*n
1207     c near ir surface albedo for beam fraction m*ndim
1208     c radiation (rsirbm)
1209     c near ir surface albedo for diffuse fraction m*ndim
1210     c radiation (rsirdf)
1211     c
1212     c----- output (updated) parameters:
1213     c
1214     c all-sky flux (downward-upward) (flx) fraction m*ndim*(np+1)
1215     c clear-sky flux (downward-upward) (flc) fraction m*ndim*(np+1)
1216     c all-sky direct downward ir flux at
1217     c the surface (fdirir) fraction m*ndim
1218     c all-sky diffuse downward ir flux at
1219     c the surface (fdifir) fraction m*ndim
1220     c
1221     c----- note: the following parameters must be specified by users:
1222     c aerosol single scattering albedo (ssaal) n/d nband
1223     c aerosol asymmetry factor (asyal) n/d nband
1224     c
1225     c*************************************************************************
1226    
1227     implicit none
1228    
1229     c-----Explicit Inline Directives
1230    
1231 molod 1.11 #ifdef CRAY
1232     #ifdef f77
1233 molod 1.1 cfpp$ expand (deledd)
1234     cfpp$ expand (sagpol)
1235     cfpp$ expand (expmn)
1236     #endif
1237     #endif
1238 molod 1.12 _RL expmn
1239 molod 1.1
1240     c-----input parameters
1241    
1242     integer m,n,ndim,np,ict,icb
1243 molod 1.12 _RL taucld(m,ndim,np,2),reff(m,ndim,np,2),fcld(m,ndim,np)
1244     _RL tauclb(m,n,np),tauclf(m,n,np),cc(m,n,3)
1245     _RL rsirbm(m,ndim),rsirdf(m,ndim)
1246     _RL wh(m,n,np),taual(m,ndim,np),csm(m,n)
1247 molod 1.1
1248     c-----output (updated) parameters
1249    
1250 molod 1.12 _RL flx(m,ndim,np+1),flc(m,ndim,np+1)
1251     _RL fdirir(m,ndim),fdifir(m,ndim)
1252 molod 1.1
1253     c-----static parameters
1254    
1255     integer nk,nband
1256     parameter (nk=10,nband=3)
1257 molod 1.12 _RL xk(nk),hk(nband,nk),ssaal(nband),asyal(nband)
1258     _RL aia(nband,3),awa(nband,3),aig(nband,3),awg(nband,3)
1259 molod 1.1
1260     c-----temporary array
1261    
1262     integer ib,ik,i,j,k
1263 molod 1.12 _RL ssacl(m,n,np),asycl(m,n,np)
1264     _RL rr(m,n,np+1,2),tt(m,n,np+1,2),td(m,n,np+1,2),
1265 molod 1.1 * rs(m,n,np+1,2),ts(m,n,np+1,2)
1266 molod 1.12 _RL fall(m,n,np+1),fclr(m,n,np+1)
1267     _RL fsdir(m,n),fsdif(m,n)
1268 molod 1.1
1269 molod 1.12 _RL tauwv,tausto,ssatau,asysto,tauto,ssato,asyto
1270     _RL taux,reff1,reff2,w1,w2,g1,g2
1271     _RL ssaclt(m,n),asyclt(m,n)
1272     _RL rr1t(m,n),tt1t(m,n),td1t(m,n),rs1t(m,n),ts1t(m,n)
1273     _RL rr2t(m,n),tt2t(m,n),td2t(m,n),rs2t(m,n),ts2t(m,n)
1274 molod 1.1
1275     c-----water vapor absorption coefficient for 10 k-intervals.
1276     c unit: cm^2/gm
1277    
1278     data xk/
1279     1 0.0010, 0.0133, 0.0422, 0.1334, 0.4217,
1280     2 1.334, 5.623, 31.62, 177.8, 1000.0/
1281    
1282     c-----water vapor k-distribution function,
1283     c the sum of hk is 0.52926. unit: fraction
1284    
1285     data hk/
1286     1 .01074,.08236,.20673, .00360,.01157,.03497,
1287     2 .00411,.01133,.03011, .00421,.01143,.02260,
1288     3 .00389,.01240,.01336, .00326,.01258,.00696,
1289     4 .00499,.01381,.00441, .00465,.00650,.00115,
1290     5 .00245,.00244,.00026, .00145,.00094,.00000/
1291    
1292     c-----aerosol single-scattering albedo and asymmetry factor
1293    
1294     data ssaal,asyal/nband*0.999,nband*0.850/
1295    
1296     c-----coefficients for computing the single scattering albedo of
1297     c ice clouds from ssa=1-(aia(*,1)+aia(*,2)*reff+aia(*,3)*reff**2)
1298    
1299     data aia/
1300     1 .08938331, .00215346,-.00000260,
1301     2 .00299387, .00073709, .00000746,
1302     3 -.00001038,-.00000134, .00000000/
1303    
1304     c-----coefficients for computing the single scattering albedo of
1305     c liquid clouds from ssa=1-(awa(*,1)+awa(*,2)*reff+awa(*,3)*reff**2)
1306    
1307     data awa/
1308     1 .01209318,-.00019934, .00000007,
1309     2 .01784739, .00088757, .00000845,
1310     3 -.00036910,-.00000650,-.00000004/
1311    
1312     c-----coefficients for computing the asymmetry factor of ice clouds
1313     c from asycl=aig(*,1)+aig(*,2)*reff+aig(*,3)*reff**2
1314    
1315     data aig/
1316     1 .84090400, .76098937, .74935228,
1317     2 .00126222, .00141864, .00119715,
1318     3 -.00000385,-.00000396,-.00000367/
1319    
1320     c-----coefficients for computing the asymmetry factor of liquid clouds
1321     c from asycl=awg(*,1)+awg(*,2)*reff+awg(*,3)*reff**2
1322    
1323     data awg/
1324     1 .83530748, .74513197, .79375035,
1325     2 .00257181, .01370071, .00832441,
1326     3 .00005519,-.00038203,-.00023263/
1327    
1328     c-----initialize surface fluxes, reflectances, and transmittances
1329    
1330     do j= 1, n
1331     do i= 1, m
1332     fdirir(i,j)=0.0
1333     fdifir(i,j)=0.0
1334     rr(i,j,np+1,1)=rsirbm(i,j)
1335     rr(i,j,np+1,2)=rsirbm(i,j)
1336     rs(i,j,np+1,1)=rsirdf(i,j)
1337     rs(i,j,np+1,2)=rsirdf(i,j)
1338     td(i,j,np+1,1)=0.0
1339     td(i,j,np+1,2)=0.0
1340     tt(i,j,np+1,1)=0.0
1341     tt(i,j,np+1,2)=0.0
1342     ts(i,j,np+1,1)=0.0
1343     ts(i,j,np+1,2)=0.0
1344     enddo
1345     enddo
1346    
1347     c-----integration over spectral bands
1348    
1349     do 100 ib=1,nband
1350    
1351     c-----compute cloud single scattering albedo and asymmetry factor
1352     c for a mixture of ice and liquid particles.
1353    
1354     do k= 1, np
1355    
1356     do j= 1, n
1357     do i= 1, m
1358    
1359     ssaclt(i,j)=1.0
1360     asyclt(i,j)=1.0
1361    
1362     taux=taucld(i,j,k,1)+taucld(i,j,k,2)
1363     if (taux.gt.0.05 .and. fcld(i,j,k).gt.0.01) then
1364    
1365     reff1=min(reff(i,j,k,1),130.)
1366     reff2=min(reff(i,j,k,2),20.0)
1367    
1368     w1=(1.-(aia(ib,1)+(aia(ib,2)+
1369     * aia(ib,3)*reff1)*reff1))*taucld(i,j,k,1)
1370     w2=(1.-(awa(ib,1)+(awa(ib,2)+
1371     * awa(ib,3)*reff2)*reff2))*taucld(i,j,k,2)
1372     ssaclt(i,j)=(w1+w2)/taux
1373    
1374     g1=(aig(ib,1)+(aig(ib,2)+aig(ib,3)*reff1)*reff1)*w1
1375     g2=(awg(ib,1)+(awg(ib,2)+awg(ib,3)*reff2)*reff2)*w2
1376     asyclt(i,j)=(g1+g2)/(w1+w2)
1377    
1378     endif
1379    
1380     enddo
1381     enddo
1382    
1383     do j=1,n
1384     do i=1,m
1385     ssacl(i,j,k)=ssaclt(i,j)
1386     enddo
1387     enddo
1388     do j=1,n
1389     do i=1,m
1390     asycl(i,j,k)=asyclt(i,j)
1391     enddo
1392     enddo
1393    
1394     enddo
1395    
1396     c-----integration over the k-distribution function
1397    
1398     do 200 ik=1,nk
1399    
1400     do 300 k= 1, np
1401    
1402     do j= 1, n
1403     do i= 1, m
1404    
1405     tauwv=xk(ik)*wh(i,j,k)
1406    
1407     c-----compute total optical thickness, single scattering albedo,
1408     c and asymmetry factor.
1409    
1410     tausto=tauwv+taual(i,j,k)+1.0e-8
1411     ssatau=ssaal(ib)*taual(i,j,k)
1412     asysto=asyal(ib)*ssaal(ib)*taual(i,j,k)
1413    
1414     c-----compute reflectance and transmittance for cloudless layers
1415    
1416     tauto=tausto
1417     ssato=ssatau/tauto+1.0e-8
1418    
1419     c if (ssato .gt. 0.001) then
1420    
1421     c ssato=min(ssato,0.999999)
1422     c asyto=asysto/(ssato*tauto)
1423    
1424     c call deledd(tauto,ssato,asyto,csm(i,j),
1425     c * rr1t(i,j),tt1t(i,j),td1t(i,j))
1426    
1427     c call sagpol (tauto,ssato,asyto,rs1t(i,j),ts1t(i,j))
1428    
1429     c else
1430    
1431     td1t(i,j)=expmn(-tauto*csm(i,j))
1432     ts1t(i,j)=expmn(-1.66*tauto)
1433     tt1t(i,j)=0.0
1434     rr1t(i,j)=0.0
1435     rs1t(i,j)=0.0
1436    
1437     c endif
1438    
1439     c-----compute reflectance and transmittance for cloud layers
1440    
1441     if (tauclb(i,j,k) .lt. 0.01) then
1442    
1443     rr2t(i,j)=rr1t(i,j)
1444     tt2t(i,j)=tt1t(i,j)
1445     td2t(i,j)=td1t(i,j)
1446     rs2t(i,j)=rs1t(i,j)
1447     ts2t(i,j)=ts1t(i,j)
1448    
1449     else
1450    
1451     tauto=tausto+tauclb(i,j,k)
1452     ssato=(ssatau+ssacl(i,j,k)*tauclb(i,j,k))/tauto+1.0e-8
1453     ssato=min(ssato,0.999999)
1454     asyto=(asysto+asycl(i,j,k)*ssacl(i,j,k)*tauclb(i,j,k))/
1455     * (ssato*tauto)
1456    
1457     call deledd(tauto,ssato,asyto,csm(i,j),
1458     * rr2t(i,j),tt2t(i,j),td2t(i,j))
1459    
1460     tauto=tausto+tauclf(i,j,k)
1461     ssato=(ssatau+ssacl(i,j,k)*tauclf(i,j,k))/tauto+1.0e-8
1462     ssato=min(ssato,0.999999)
1463     asyto=(asysto+asycl(i,j,k)*ssacl(i,j,k)*tauclf(i,j,k))/
1464     * (ssato*tauto)
1465    
1466     call sagpol (tauto,ssato,asyto,rs2t(i,j),ts2t(i,j))
1467    
1468     endif
1469    
1470     enddo
1471     enddo
1472    
1473     c-----the following code appears to be awkward, but it is efficient
1474     c in certain parallel processors.
1475    
1476     do j=1,n
1477     do i=1,m
1478     rr(i,j,k,1)=rr1t(i,j)
1479     enddo
1480     enddo
1481     do j=1,n
1482     do i=1,m
1483     tt(i,j,k,1)=tt1t(i,j)
1484     enddo
1485     enddo
1486     do j=1,n
1487     do i=1,m
1488     td(i,j,k,1)=td1t(i,j)
1489     enddo
1490     enddo
1491     do j=1,n
1492     do i=1,m
1493     rs(i,j,k,1)=rs1t(i,j)
1494     enddo
1495     enddo
1496     do j=1,n
1497     do i=1,m
1498     ts(i,j,k,1)=ts1t(i,j)
1499     enddo
1500     enddo
1501    
1502     do j=1,n
1503     do i=1,m
1504     rr(i,j,k,2)=rr2t(i,j)
1505     enddo
1506     enddo
1507     do j=1,n
1508     do i=1,m
1509     tt(i,j,k,2)=tt2t(i,j)
1510     enddo
1511     enddo
1512     do j=1,n
1513     do i=1,m
1514     td(i,j,k,2)=td2t(i,j)
1515     enddo
1516     enddo
1517     do j=1,n
1518     do i=1,m
1519     rs(i,j,k,2)=rs2t(i,j)
1520     enddo
1521     enddo
1522     do j=1,n
1523     do i=1,m
1524     ts(i,j,k,2)=ts2t(i,j)
1525     enddo
1526     enddo
1527    
1528     300 continue
1529    
1530     c-----flux calculations
1531    
1532     call cldflx (m,n,np,ict,icb,cc,rr,tt,td,rs,ts,
1533     * fclr,fall,fsdir,fsdif)
1534    
1535     do k= 1, np+1
1536     do j= 1, n
1537     do i= 1, m
1538     flx(i,j,k) = flx(i,j,k)+fall(i,j,k)*hk(ib,ik)
1539     enddo
1540     enddo
1541     do j= 1, n
1542     do i= 1, m
1543     flc(i,j,k) = flc(i,j,k)+fclr(i,j,k)*hk(ib,ik)
1544     enddo
1545     enddo
1546     enddo
1547    
1548     do j= 1, n
1549     do i= 1, m
1550     fdirir(i,j) = fdirir(i,j)+fsdir(i,j)*hk(ib,ik)
1551     fdifir(i,j) = fdifir(i,j)+fsdif(i,j)*hk(ib,ik)
1552     enddo
1553     enddo
1554    
1555     200 continue
1556     100 continue
1557    
1558     return
1559     end
1560    
1561     c************************************************************************
1562    
1563     subroutine soluv (m,n,ndim,np,oh,dp,taucld,tauclb,tauclf,reff,
1564     * ict,icb,fcld,cc,taual,csm,rsuvbm,rsuvdf,flx,flc
1565     * ,fdirpar,fdifpar,fdiruv,fdifuv)
1566    
1567     c************************************************************************
1568     c compute solar fluxes in the uv+visible region. the spectrum is
1569     c grouped into 8 bands:
1570     c
1571     c Band Micrometer
1572     c
1573     c UV-C 1. .175 - .225
1574     c 2. .225 - .245
1575     c .260 - .280
1576     c 3. .245 - .260
1577     c
1578     c UV-B 4. .280 - .295
1579     c 5. .295 - .310
1580     c 6. .310 - .320
1581     c
1582     c UV-A 7. .320 - .400
1583     c
1584     c PAR 8. .400 - .700
1585     c
1586     c----- Input parameters: units size
1587     c
1588     c number of soundings in zonal direction (m) n/d 1
1589     c number of soundings in meridional direction (n) n/d 1
1590     c maximum number of soundings in n/d 1
1591     c meridional direction (ndim)
1592     c number of atmospheric layers (np) n/d 1
1593     c layer ozone content (oh) (cm-atm)stp m*n*np
1594     c layer pressure thickness (dp) mb m*n*np
1595     c cloud optical thickness (taucld) n/d m*ndim*np*2
1596     c index 1 for ice paticles
1597     c index 2 for liquid particles
1598     c scaled cloud optical thickness n/d m*n*np
1599     c for beam radiation (tauclb)
1600     c scaled cloud optical thickness n/d m*n*np
1601     c for diffuse radiation (tauclf)
1602     c effective cloud-particle size (reff) micrometer m*ndim*np*2
1603     c index 1 for ice paticles
1604     c index 2 for liquid particles
1605     c level indiex separating high and n/d m*n
1606     c middle clouds (ict)
1607     c level indiex separating middle and n/d m*n
1608     c low clouds (icb)
1609     c cloud amount (fcld) fraction m*ndim*np
1610     c cloud amounts of high, middle, and n/d m*n*3
1611     c low clouds (cc)
1612     c aerosol optical thickness (taual) n/d m*ndim*np
1613     c cosecant of the solar zenith angle (csm) n/d m*n
1614     c uv+par surface albedo for beam fraction m*ndim
1615     c radiation (rsuvbm)
1616     c uv+par surface albedo for diffuse fraction m*ndim
1617     c radiation (rsuvdf)
1618     c
1619     c----- output (updated) parameters:
1620     c
1621     c all-sky net downward flux (flx) fraction m*ndim*(np+1)
1622     c clear-sky net downward flux (flc) fraction m*ndim*(np+1)
1623     c all-sky direct downward par flux at
1624     c the surface (fdirpar) fraction m*ndim
1625     c all-sky diffuse downward par flux at
1626     c the surface (fdifpar) fraction m*ndim
1627     c
1628     c----- note: the following parameters must be specified by users:
1629     c
1630     c aerosol single scattering albedo (ssaal) n/d 1
1631     c aerosol asymmetry factor (asyal) n/d 1
1632     c
1633     *
1634     c***********************************************************************
1635    
1636     implicit none
1637    
1638     c-----Explicit Inline Directives
1639    
1640 molod 1.11 #ifdef CRAY
1641     #ifdef f77
1642 molod 1.1 cfpp$ expand (deledd)
1643     cfpp$ expand (sagpol)
1644     #endif
1645     #endif
1646    
1647     c-----input parameters
1648    
1649     integer m,n,ndim,np,ict,icb
1650 molod 1.12 _RL taucld(m,ndim,np,2),reff(m,ndim,np,2),fcld(m,ndim,np)
1651     _RL tauclb(m,n,np),tauclf(m,n,np),cc(m,n,3)
1652     _RL oh(m,n,np),dp(m,n,np),taual(m,ndim,np)
1653     _RL rsuvbm(m,ndim),rsuvdf(m,ndim),csm(m,n)
1654 molod 1.1
1655     c-----output (updated) parameter
1656    
1657 molod 1.12 _RL flx(m,ndim,np+1),flc(m,ndim,np+1)
1658     _RL fdirpar(m,ndim),fdifpar(m,ndim)
1659     _RL fdiruv(m,ndim),fdifuv(m,ndim)
1660 molod 1.1
1661     c-----static parameters
1662    
1663     integer nband
1664     parameter (nband=8)
1665 molod 1.12 _RL hk(nband),xk(nband),ry(nband)
1666     _RL asyal(nband),ssaal(nband),aig(3),awg(3)
1667 molod 1.1
1668     c-----temporary array
1669    
1670     integer i,j,k,ib
1671 molod 1.12 _RL taurs,tauoz,tausto,ssatau,asysto,tauto,ssato,asyto
1672     _RL taux,reff1,reff2,g1,g2,asycl(m,n,np)
1673     _RL td(m,n,np+1,2),rr(m,n,np+1,2),tt(m,n,np+1,2),
1674 molod 1.1 * rs(m,n,np+1,2),ts(m,n,np+1,2)
1675 molod 1.12 _RL fall(m,n,np+1),fclr(m,n,np+1),fsdir(m,n),fsdif(m,n)
1676     _RL asyclt(m,n)
1677     _RL rr1t(m,n),tt1t(m,n),td1t(m,n),rs1t(m,n),ts1t(m,n)
1678     _RL rr2t(m,n),tt2t(m,n),td2t(m,n),rs2t(m,n),ts2t(m,n)
1679 molod 1.1
1680     c-----hk is the fractional extra-terrestrial solar flux.
1681     c the sum of hk is 0.47074.
1682    
1683     data hk/.00057, .00367, .00083, .00417,
1684     * .00600, .00556, .05913, .39081/
1685    
1686     c-----xk is the ozone absorption coefficient. unit: /(cm-atm)stp
1687    
1688     data xk /30.47, 187.2, 301.9, 42.83,
1689     * 7.09, 1.25, 0.0345, 0.0539/
1690    
1691     c-----ry is the extinction coefficient for Rayleigh scattering.
1692     c unit: /mb.
1693    
1694     data ry /.00604, .00170, .00222, .00132,
1695     * .00107, .00091, .00055, .00012/
1696    
1697     c-----aerosol single-scattering albedo and asymmetry factor
1698    
1699     data ssaal,asyal/nband*0.999,nband*0.850/
1700    
1701     c-----coefficients for computing the asymmetry factor of ice clouds
1702     c from asycl=aig(*,1)+aig(*,2)*reff+aig(*,3)*reff**2
1703    
1704     data aig/.74625000,.00105410,-.00000264/
1705    
1706     c-----coefficients for computing the asymmetry factor of liquid
1707     c clouds from asycl=awg(*,1)+awg(*,2)*reff+awg(*,3)*reff**2
1708    
1709     data awg/.82562000,.00529000,-.00014866/
1710    
1711     c-----initialize surface reflectances and transmittances
1712    
1713     do j= 1, n
1714     do i= 1, m
1715     rr(i,j,np+1,1)=rsuvbm(i,j)
1716     rr(i,j,np+1,2)=rsuvbm(i,j)
1717     rs(i,j,np+1,1)=rsuvdf(i,j)
1718     rs(i,j,np+1,2)=rsuvdf(i,j)
1719     td(i,j,np+1,1)=0.0
1720     td(i,j,np+1,2)=0.0
1721     tt(i,j,np+1,1)=0.0
1722     tt(i,j,np+1,2)=0.0
1723     ts(i,j,np+1,1)=0.0
1724     ts(i,j,np+1,2)=0.0
1725     enddo
1726     enddo
1727    
1728     c-----compute cloud asymmetry factor for a mixture of
1729     c liquid and ice particles. unit of reff is micrometers.
1730    
1731     do k= 1, np
1732    
1733     do j= 1, n
1734     do i= 1, m
1735    
1736     asyclt(i,j)=1.0
1737    
1738     taux=taucld(i,j,k,1)+taucld(i,j,k,2)
1739     if (taux.gt.0.05 .and. fcld(i,j,k).gt.0.01) then
1740    
1741     reff1=min(reff(i,j,k,1),130.)
1742     reff2=min(reff(i,j,k,2),20.0)
1743    
1744     g1=(aig(1)+(aig(2)+aig(3)*reff1)*reff1)*taucld(i,j,k,1)
1745     g2=(awg(1)+(awg(2)+awg(3)*reff2)*reff2)*taucld(i,j,k,2)
1746     asyclt(i,j)=(g1+g2)/taux
1747    
1748     endif
1749    
1750     enddo
1751     enddo
1752    
1753     do j=1,n
1754     do i=1,m
1755     asycl(i,j,k)=asyclt(i,j)
1756     enddo
1757     enddo
1758    
1759     enddo
1760    
1761     do j=1,n
1762     do i=1,m
1763     fdiruv(i,j)=0.0
1764     fdifuv(i,j)=0.0
1765     enddo
1766     enddo
1767    
1768     c-----integration over spectral bands
1769    
1770     do 100 ib=1,nband
1771    
1772     do 300 k= 1, np
1773    
1774     do j= 1, n
1775     do i= 1, m
1776    
1777     c-----compute ozone and rayleigh optical thicknesses
1778    
1779     taurs=ry(ib)*dp(i,j,k)
1780     tauoz=xk(ib)*oh(i,j,k)
1781    
1782     c-----compute total optical thickness, single scattering albedo,
1783     c and asymmetry factor
1784    
1785     tausto=taurs+tauoz+taual(i,j,k)+1.0e-8
1786     ssatau=ssaal(ib)*taual(i,j,k)+taurs
1787     asysto=asyal(ib)*ssaal(ib)*taual(i,j,k)
1788    
1789     c-----compute reflectance and transmittance for cloudless layers
1790    
1791     tauto=tausto
1792     ssato=ssatau/tauto+1.0e-8
1793     ssato=min(ssato,0.999999)
1794     asyto=asysto/(ssato*tauto)
1795    
1796     call deledd(tauto,ssato,asyto,csm(i,j),
1797     * rr1t(i,j),tt1t(i,j),td1t(i,j))
1798    
1799     call sagpol (tauto,ssato,asyto,rs1t(i,j),ts1t(i,j))
1800    
1801     c-----compute reflectance and transmittance for cloud layers
1802    
1803     if (tauclb(i,j,k) .lt. 0.01) then
1804    
1805     rr2t(i,j)=rr1t(i,j)
1806     tt2t(i,j)=tt1t(i,j)
1807     td2t(i,j)=td1t(i,j)
1808     rs2t(i,j)=rs1t(i,j)
1809     ts2t(i,j)=ts1t(i,j)
1810    
1811     else
1812    
1813     tauto=tausto+tauclb(i,j,k)
1814     ssato=(ssatau+tauclb(i,j,k))/tauto+1.0e-8
1815     ssato=min(ssato,0.999999)
1816     asyto=(asysto+asycl(i,j,k)*tauclb(i,j,k))/(ssato*tauto)
1817    
1818     call deledd(tauto,ssato,asyto,csm(i,j),
1819     * rr2t(i,j),tt2t(i,j),td2t(i,j))
1820    
1821     tauto=tausto+tauclf(i,j,k)
1822     ssato=(ssatau+tauclf(i,j,k))/tauto+1.0e-8
1823     ssato=min(ssato,0.999999)
1824     asyto=(asysto+asycl(i,j,k)*tauclf(i,j,k))/(ssato*tauto)
1825    
1826     call sagpol (tauto,ssato,asyto,rs2t(i,j),ts2t(i,j))
1827    
1828     endif
1829    
1830     enddo
1831     enddo
1832    
1833     do j=1,n
1834     do i=1,m
1835     rr(i,j,k,1)=rr1t(i,j)
1836     enddo
1837     enddo
1838     do j=1,n
1839     do i=1,m
1840     tt(i,j,k,1)=tt1t(i,j)
1841     enddo
1842     enddo
1843     do j=1,n
1844     do i=1,m
1845     td(i,j,k,1)=td1t(i,j)
1846     enddo
1847     enddo
1848     do j=1,n
1849     do i=1,m
1850     rs(i,j,k,1)=rs1t(i,j)
1851     enddo
1852     enddo
1853     do j=1,n
1854     do i=1,m
1855     ts(i,j,k,1)=ts1t(i,j)
1856     enddo
1857     enddo
1858    
1859     do j=1,n
1860     do i=1,m
1861     rr(i,j,k,2)=rr2t(i,j)
1862     enddo
1863     enddo
1864     do j=1,n
1865     do i=1,m
1866     tt(i,j,k,2)=tt2t(i,j)
1867     enddo
1868     enddo
1869     do j=1,n
1870     do i=1,m
1871     td(i,j,k,2)=td2t(i,j)
1872     enddo
1873     enddo
1874     do j=1,n
1875     do i=1,m
1876     rs(i,j,k,2)=rs2t(i,j)
1877     enddo
1878     enddo
1879     do j=1,n
1880     do i=1,m
1881     ts(i,j,k,2)=ts2t(i,j)
1882     enddo
1883     enddo
1884    
1885     300 continue
1886    
1887     c-----flux calculations
1888    
1889     call cldflx (m,n,np,ict,icb,cc,rr,tt,td,rs,ts,
1890     * fclr,fall,fsdir,fsdif)
1891    
1892     do k= 1, np+1
1893     do j= 1, n
1894     do i= 1, m
1895     flx(i,j,k)=flx(i,j,k)+fall(i,j,k)*hk(ib)
1896     enddo
1897     enddo
1898     do j= 1, n
1899     do i= 1, m
1900     flc(i,j,k)=flc(i,j,k)+fclr(i,j,k)*hk(ib)
1901     enddo
1902     enddo
1903     enddo
1904    
1905     if(ib.eq.nband) then
1906     do j=1,n
1907     do i=1,m
1908     fdirpar(i,j)=fsdir(i,j)*hk(ib)
1909     fdifpar(i,j)=fsdif(i,j)*hk(ib)
1910     enddo
1911     enddo
1912     else
1913     do j=1,n
1914     do i=1,m
1915     fdiruv(i,j)=fdiruv(i,j)+fsdir(i,j)*hk(ib)
1916     fdifuv(i,j)=fdifuv(i,j)+fsdif(i,j)*hk(ib)
1917     enddo
1918     enddo
1919     endif
1920    
1921     100 continue
1922    
1923     return
1924     end
1925    
1926     c*********************************************************************
1927    
1928     subroutine deledd(tau,ssc,g0,csm,rr,tt,td)
1929    
1930     c*********************************************************************
1931     c
1932     c-----uses the delta-eddington approximation to compute the
1933     c bulk scattering properties of a single layer
1934     c coded following King and Harshvardhan (JAS, 1986)
1935     c
1936     c inputs:
1937     c
1938     c tau: the effective optical thickness
1939     c ssc: the effective single scattering albedo
1940     c g0: the effective asymmetry factor
1941     c csm: the effective secant of the zenith angle
1942     c
1943     c outputs:
1944     c
1945     c rr: the layer reflection of the direct beam
1946     c tt: the layer diffuse transmission of the direct beam
1947     c td: the layer direct transmission of the direct beam
1948    
1949     c*********************************************************************
1950    
1951     implicit none
1952    
1953     c-----Explicit Inline Directives
1954    
1955 molod 1.11 #ifdef CRAY
1956     #ifdef f77
1957 molod 1.1 cfpp$ expand (expmn)
1958     #endif
1959     #endif
1960 molod 1.12 _RL expmn
1961 molod 1.1
1962 molod 1.12 _RL zero,one,two,three,four,fourth,seven,tumin
1963 molod 1.1 parameter (one=1., three=3.)
1964     parameter (seven=7., two=2.)
1965     parameter (four=4., fourth=.25)
1966     parameter (zero=0., tumin=1.e-20)
1967    
1968     c-----input parameters
1969 molod 1.12 _RL tau,ssc,g0,csm
1970 molod 1.1
1971     c-----output parameters
1972 molod 1.12 _RL rr,tt,td
1973 molod 1.1
1974     c-----temporary parameters
1975    
1976 molod 1.12 _RL zth,ff,xx,taup,sscp,gp,gm1,gm2,gm3,akk,alf1,alf2,
1977 molod 1.1 * all,bll,st7,st8,cll,dll,fll,ell,st1,st2,st3,st4
1978     c
1979     zth = one / csm
1980    
1981     c delta-eddington scaling of single scattering albedo,
1982     c optical thickness, and asymmetry factor,
1983     c K & H eqs(27-29)
1984    
1985     ff = g0*g0
1986     xx = one-ff*ssc
1987     taup= tau*xx
1988     sscp= ssc*(one-ff)/xx
1989     gp = g0/(one+g0)
1990    
1991     c extinction of the direct beam transmission
1992    
1993     td = expmn(-taup*csm)
1994    
1995     c gamma1, gamma2, gamma3 and gamma4. see table 2 and eq(26) K & H
1996     c ssc and gp are the d-s single scattering
1997     c albedo and asymmetry factor.
1998    
1999     xx = three*gp
2000     gm1 = (seven - sscp*(four+xx))*fourth
2001     gm2 = -(one - sscp*(four-xx))*fourth
2002     gm3 = (two - zth*xx )*fourth
2003    
2004     c akk is k as defined in eq(25) of K & H
2005    
2006     xx = gm1-gm2
2007     akk = sqrt((gm1+gm2)*xx)
2008    
2009     c alf1 and alf2 are alpha1 and alpha2 from eqs (23) & (24) of K & H
2010    
2011     alf1 = gm1 - gm3 * xx
2012     alf2 = gm2 + gm3 * xx
2013    
2014     c all is last term in eq(21) of K & H
2015     c bll is last term in eq(22) of K & H
2016    
2017     xx = akk * two
2018     all = (gm3 - alf2 * zth )*xx*td
2019     bll = (one - gm3 + alf1*zth)*xx
2020    
2021     xx = akk * zth
2022     st7 = one - xx
2023     st8 = one + xx
2024    
2025     xx = akk * gm3
2026     cll = (alf2 + xx) * st7
2027     dll = (alf2 - xx) * st8
2028    
2029     xx = akk * (one-gm3)
2030     fll = (alf1 + xx) * st8
2031     ell = (alf1 - xx) * st7
2032    
2033     st3 = max(abs(st7*st8),tumin)
2034     st3 = sign (st3,st7)
2035    
2036     st2 = expmn(-akk*taup)
2037     st4 = st2 * st2
2038    
2039     st1 = sscp / ((akk+gm1 + (akk-gm1)*st4) * st3)
2040    
2041     c rr is r-hat of eq(21) of K & H
2042     c tt is diffuse part of t-hat of eq(22) of K & H
2043    
2044     rr = ( cll-dll*st4 -all*st2)*st1
2045     tt = - ((fll-ell*st4)*td-bll*st2)*st1
2046    
2047     rr = max(rr,zero)
2048     tt = max(tt,zero)
2049    
2050     return
2051     end
2052    
2053     c*********************************************************************
2054    
2055     subroutine sagpol(tau,ssc,g0,rll,tll)
2056    
2057     c*********************************************************************
2058     c-----transmittance (tll) and reflectance (rll) of diffuse radiation
2059     c follows Sagan and Pollock (JGR, 1967).
2060     c also, eq.(31) of Lacis and Hansen (JAS, 1974).
2061     c
2062     c-----input parameters:
2063     c
2064     c tau: the effective optical thickness
2065     c ssc: the effective single scattering albedo
2066     c g0: the effective asymmetry factor
2067     c
2068     c-----output parameters:
2069     c
2070     c rll: the layer reflection of diffuse radiation
2071     c tll: the layer transmission of diffuse radiation
2072     c
2073     c*********************************************************************
2074    
2075     implicit none
2076    
2077     c-----Explicit Inline Directives
2078    
2079 molod 1.11 #ifdef CRAY
2080     #ifdef f77
2081 molod 1.1 cfpp$ expand (expmn)
2082     #endif
2083     #endif
2084 molod 1.12 _RL expmn
2085 molod 1.1
2086 molod 1.12 _RL one,three,four
2087 molod 1.1 parameter (one=1., three=3., four=4.)
2088    
2089     c-----output parameters:
2090    
2091 molod 1.12 _RL tau,ssc,g0
2092 molod 1.1
2093     c-----output parameters:
2094    
2095 molod 1.12 _RL rll,tll
2096 molod 1.1
2097     c-----temporary arrays
2098    
2099 molod 1.12 _RL xx,uuu,ttt,emt,up1,um1,st1
2100 molod 1.1
2101     xx = one-ssc*g0
2102     uuu = sqrt( xx/(one-ssc))
2103     ttt = sqrt( xx*(one-ssc)*three )*tau
2104     emt = expmn(-ttt)
2105     up1 = uuu + one
2106     um1 = uuu - one
2107     xx = um1*emt
2108     st1 = one / ((up1+xx) * (up1-xx))
2109     rll = up1*um1*(one-emt*emt)*st1
2110     tll = uuu*four*emt *st1
2111    
2112     return
2113     end
2114    
2115     c*******************************************************************
2116    
2117     function expmn(fin)
2118    
2119     c*******************************************************************
2120     c compute exponential for arguments in the range 0> fin > -10.
2121 molod 1.10 c*******************************************************************
2122     implicit none
2123 molod 1.12 _RL fin,expmn
2124 molod 1.1
2125 molod 1.12 _RL one,expmin,e1,e2,e3,e4
2126 molod 1.1 parameter (one=1.0, expmin=-10.0)
2127     parameter (e1=1.0, e2=-2.507213e-1)
2128     parameter (e3=2.92732e-2, e4=-3.827800e-3)
2129    
2130     if (fin .lt. expmin) fin = expmin
2131     expmn = ((e4*fin + e3)*fin+e2)*fin+e1
2132     expmn = expmn * expmn
2133     expmn = one / (expmn * expmn)
2134    
2135     return
2136     end
2137    
2138     c*******************************************************************
2139    
2140     subroutine cldflx (m,n,np,ict,icb,cc,rr,tt,td,rs,ts,
2141     * fclr,fall,fsdir,fsdif)
2142    
2143     c*******************************************************************
2144     c compute upward and downward fluxes using a two-stream adding method
2145     c following equations (3)-(5) of Chou (1992, JAS).
2146     c
2147     c clouds are grouped into high, middle, and low clouds which are
2148     c assumed randomly overlapped. It involves eight sets of calculations.
2149     c In each set of calculations, each atmospheric layer is homogeneous,
2150     c either with clouds or without clouds.
2151    
2152     c input parameters:
2153     c m: number of soundings in zonal direction
2154     c n: number of soundings in meridional direction
2155     c np: number of atmospheric layers
2156     c ict: the level separating high and middle clouds
2157     c icb: the level separating middle and low clouds
2158     c cc: effective cloud covers for high, middle and low clouds
2159     c tt: diffuse transmission of a layer illuminated by beam radiation
2160     c td: direct beam tranmssion
2161     c ts: transmission of a layer illuminated by diffuse radiation
2162     c rr: reflection of a layer illuminated by beam radiation
2163     c rs: reflection of a layer illuminated by diffuse radiation
2164     c
2165     c output parameters:
2166     c fclr: clear-sky flux (downward minus upward)
2167     c fall: all-sky flux (downward minus upward)
2168     c fdndir: surface direct downward flux
2169     c fdndif: surface diffuse downward flux
2170     c*********************************************************************c
2171    
2172     implicit none
2173    
2174     c-----input parameters
2175    
2176     integer m,n,np,ict,icb
2177    
2178 molod 1.12 _RL rr(m,n,np+1,2),tt(m,n,np+1,2),td(m,n,np+1,2)
2179     _RL rs(m,n,np+1,2),ts(m,n,np+1,2)
2180     _RL cc(m,n,3)
2181 molod 1.1
2182     c-----temporary array
2183    
2184     integer i,j,k,ih,im,is
2185 molod 1.12 _RL rra(m,n,np+1,2,2),tta(m,n,np+1,2,2),tda(m,n,np+1,2,2)
2186     _RL rsa(m,n,np+1,2,2),rxa(m,n,np+1,2,2)
2187     _RL ch(m,n),cm(m,n),ct(m,n),flxdn(m,n,np+1)
2188     _RL fdndir(m,n),fdndif(m,n),fupdif
2189     _RL denm,xx
2190 molod 1.1
2191     c-----output parameters
2192    
2193 molod 1.12 _RL fclr(m,n,np+1),fall(m,n,np+1)
2194     _RL fsdir(m,n),fsdif(m,n)
2195 molod 1.1
2196     c-----initialize all-sky flux (fall) and surface downward fluxes
2197    
2198     do k=1,np+1
2199     do j=1,n
2200     do i=1,m
2201     fall(i,j,k)=0.0
2202     enddo
2203     enddo
2204     enddo
2205    
2206     do j=1,n
2207     do i=1,m
2208     fsdir(i,j)=0.0
2209     fsdif(i,j)=0.0
2210     enddo
2211     enddo
2212    
2213     c-----compute transmittances and reflectances for a composite of
2214     c layers. layers are added one at a time, going down from the top.
2215     c tda is the composite transmittance illuminated by beam radiation
2216     c tta is the composite diffuse transmittance illuminated by
2217     c beam radiation
2218     c rsa is the composite reflectance illuminated from below
2219     c by diffuse radiation
2220     c tta and rsa are computed from eqs. (4b) and (3b) of Chou
2221    
2222     c-----for high clouds. indices 1 and 2 denote clear and cloudy
2223     c situations, respectively.
2224    
2225     do 10 ih=1,2
2226    
2227     do j= 1, n
2228     do i= 1, m
2229     tda(i,j,1,ih,1)=td(i,j,1,ih)
2230     tta(i,j,1,ih,1)=tt(i,j,1,ih)
2231     rsa(i,j,1,ih,1)=rs(i,j,1,ih)
2232     tda(i,j,1,ih,2)=td(i,j,1,ih)
2233     tta(i,j,1,ih,2)=tt(i,j,1,ih)
2234     rsa(i,j,1,ih,2)=rs(i,j,1,ih)
2235     enddo
2236     enddo
2237    
2238     do k= 2, ict-1
2239     do j= 1, n
2240     do i= 1, m
2241     denm = ts(i,j,k,ih)/( 1.-rsa(i,j,k-1,ih,1)*rs(i,j,k,ih))
2242     tda(i,j,k,ih,1)= tda(i,j,k-1,ih,1)*td(i,j,k,ih)
2243     tta(i,j,k,ih,1)= tda(i,j,k-1,ih,1)*tt(i,j,k,ih)
2244     * +(tda(i,j,k-1,ih,1)*rr(i,j,k,ih)
2245     * *rsa(i,j,k-1,ih,1)+tta(i,j,k-1,ih,1))*denm
2246     rsa(i,j,k,ih,1)= rs(i,j,k,ih)+ts(i,j,k,ih)
2247     * *rsa(i,j,k-1,ih,1)*denm
2248     tda(i,j,k,ih,2)= tda(i,j,k,ih,1)
2249     tta(i,j,k,ih,2)= tta(i,j,k,ih,1)
2250     rsa(i,j,k,ih,2)= rsa(i,j,k,ih,1)
2251     enddo
2252     enddo
2253     enddo
2254    
2255     c-----for middle clouds
2256    
2257     do 10 im=1,2
2258    
2259     do k= ict, icb-1
2260     do j= 1, n
2261     do i= 1, m
2262     denm = ts(i,j,k,im)/( 1.-rsa(i,j,k-1,ih,im)*rs(i,j,k,im))
2263     tda(i,j,k,ih,im)= tda(i,j,k-1,ih,im)*td(i,j,k,im)
2264     tta(i,j,k,ih,im)= tda(i,j,k-1,ih,im)*tt(i,j,k,im)
2265     * +(tda(i,j,k-1,ih,im)*rr(i,j,k,im)
2266     * *rsa(i,j,k-1,ih,im)+tta(i,j,k-1,ih,im))*denm
2267     rsa(i,j,k,ih,im)= rs(i,j,k,im)+ts(i,j,k,im)
2268     * *rsa(i,j,k-1,ih,im)*denm
2269     enddo
2270     enddo
2271     enddo
2272    
2273     10 continue
2274    
2275     c-----layers are added one at a time, going up from the surface.
2276     c rra is the composite reflectance illuminated by beam radiation
2277     c rxa is the composite reflectance illuminated from above
2278     c by diffuse radiation
2279     c rra and rxa are computed from eqs. (4a) and (3a) of Chou
2280    
2281     c-----for the low clouds
2282    
2283     do 20 is=1,2
2284    
2285     do j= 1, n
2286     do i= 1, m
2287     rra(i,j,np+1,1,is)=rr(i,j,np+1,is)
2288     rxa(i,j,np+1,1,is)=rs(i,j,np+1,is)
2289     rra(i,j,np+1,2,is)=rr(i,j,np+1,is)
2290     rxa(i,j,np+1,2,is)=rs(i,j,np+1,is)
2291     enddo
2292     enddo
2293    
2294     do k=np,icb,-1
2295     do j= 1, n
2296     do i= 1, m
2297     denm=ts(i,j,k,is)/( 1.-rs(i,j,k,is)*rxa(i,j,k+1,1,is) )
2298     rra(i,j,k,1,is)=rr(i,j,k,is)+(td(i,j,k,is)
2299     * *rra(i,j,k+1,1,is)+tt(i,j,k,is)*rxa(i,j,k+1,1,is))*denm
2300     rxa(i,j,k,1,is)= rs(i,j,k,is)+ts(i,j,k,is)
2301     * *rxa(i,j,k+1,1,is)*denm
2302     rra(i,j,k,2,is)=rra(i,j,k,1,is)
2303     rxa(i,j,k,2,is)=rxa(i,j,k,1,is)
2304     enddo
2305     enddo
2306     enddo
2307    
2308     c-----for middle clouds
2309    
2310     do 20 im=1,2
2311    
2312     do k= icb-1,ict,-1
2313     do j= 1, n
2314     do i= 1, m
2315     denm=ts(i,j,k,im)/( 1.-rs(i,j,k,im)*rxa(i,j,k+1,im,is) )
2316     rra(i,j,k,im,is)= rr(i,j,k,im)+(td(i,j,k,im)
2317     * *rra(i,j,k+1,im,is)+tt(i,j,k,im)*rxa(i,j,k+1,im,is))*denm
2318     rxa(i,j,k,im,is)= rs(i,j,k,im)+ts(i,j,k,im)
2319     * *rxa(i,j,k+1,im,is)*denm
2320     enddo
2321     enddo
2322     enddo
2323    
2324     20 continue
2325    
2326     c-----integration over eight sky situations.
2327     c ih, im, is denotes high, middle and low cloud groups.
2328    
2329     do 100 ih=1,2
2330    
2331     c-----clear portion
2332    
2333     if(ih.eq.1) then
2334     do j=1,n
2335     do i=1,m
2336     ch(i,j)=1.0-cc(i,j,1)
2337     enddo
2338     enddo
2339    
2340     else
2341    
2342     c-----cloudy portion
2343    
2344     do j=1,n
2345     do i=1,m
2346     ch(i,j)=cc(i,j,1)
2347     enddo
2348     enddo
2349    
2350     endif
2351    
2352     do 100 im=1,2
2353    
2354     c-----clear portion
2355    
2356     if(im.eq.1) then
2357    
2358     do j=1,n
2359     do i=1,m
2360     cm(i,j)=ch(i,j)*(1.0-cc(i,j,2))
2361     enddo
2362     enddo
2363    
2364     else
2365    
2366     c-----cloudy portion
2367    
2368     do j=1,n
2369     do i=1,m
2370     cm(i,j)=ch(i,j)*cc(i,j,2)
2371     enddo
2372     enddo
2373    
2374     endif
2375    
2376     do 100 is=1,2
2377    
2378     c-----clear portion
2379    
2380     if(is.eq.1) then
2381    
2382     do j=1,n
2383     do i=1,m
2384     ct(i,j)=cm(i,j)*(1.0-cc(i,j,3))
2385     enddo
2386     enddo
2387    
2388     else
2389    
2390     c-----cloudy portion
2391    
2392     do j=1,n
2393     do i=1,m
2394     ct(i,j)=cm(i,j)*cc(i,j,3)
2395     enddo
2396     enddo
2397    
2398     endif
2399    
2400     c-----add one layer at a time, going down.
2401    
2402     do k= icb, np
2403     do j= 1, n
2404     do i= 1, m
2405     denm = ts(i,j,k,is)/( 1.-rsa(i,j,k-1,ih,im)*rs(i,j,k,is) )
2406     tda(i,j,k,ih,im)= tda(i,j,k-1,ih,im)*td(i,j,k,is)
2407     tta(i,j,k,ih,im)= tda(i,j,k-1,ih,im)*tt(i,j,k,is)
2408     * +(tda(i,j,k-1,ih,im)*rr(i,j,k,is)
2409     * *rsa(i,j,k-1,ih,im)+tta(i,j,k-1,ih,im))*denm
2410     rsa(i,j,k,ih,im)= rs(i,j,k,is)+ts(i,j,k,is)
2411     * *rsa(i,j,k-1,ih,im)*denm
2412     enddo
2413     enddo
2414     enddo
2415    
2416     c-----add one layer at a time, going up.
2417    
2418     do k= ict-1,1,-1
2419     do j= 1, n
2420     do i= 1, m
2421     denm =ts(i,j,k,ih)/(1.-rs(i,j,k,ih)*rxa(i,j,k+1,im,is))
2422     rra(i,j,k,im,is)= rr(i,j,k,ih)+(td(i,j,k,ih)
2423     * *rra(i,j,k+1,im,is)+tt(i,j,k,ih)*rxa(i,j,k+1,im,is))*denm
2424     rxa(i,j,k,im,is)= rs(i,j,k,ih)+ts(i,j,k,ih)
2425     * *rxa(i,j,k+1,im,is)*denm
2426     enddo
2427     enddo
2428     enddo
2429    
2430     c-----compute fluxes following eq (5) of Chou (1992)
2431    
2432     c fdndir is the direct downward flux
2433     c fdndif is the diffuse downward flux
2434     c fupdif is the diffuse upward flux
2435    
2436     do k=2,np+1
2437     do j=1, n
2438     do i=1, m
2439     denm= 1./(1.- rxa(i,j,k,im,is)*rsa(i,j,k-1,ih,im))
2440     fdndir(i,j)= tda(i,j,k-1,ih,im)
2441     xx = tda(i,j,k-1,ih,im)*rra(i,j,k,im,is)
2442     fdndif(i,j)= (xx*rsa(i,j,k-1,ih,im)+tta(i,j,k-1,ih,im))*denm
2443     fupdif= (xx+tta(i,j,k-1,ih,im)*rxa(i,j,k,im,is))*denm
2444     flxdn(i,j,k)=fdndir(i,j)+fdndif(i,j)-fupdif
2445     enddo
2446     enddo
2447     enddo
2448    
2449     do j=1, n
2450     do i=1, m
2451     flxdn(i,j,1)=1.0-rra(i,j,1,im,is)
2452     enddo
2453     enddo
2454    
2455     c-----summation of fluxes over all (eight) sky situations.
2456    
2457     do k=1,np+1
2458     do j=1,n
2459     do i=1,m
2460     if(ih.eq.1 .and. im.eq.1 .and. is.eq.1) then
2461     fclr(i,j,k)=flxdn(i,j,k)
2462     endif
2463     fall(i,j,k)=fall(i,j,k)+flxdn(i,j,k)*ct(i,j)
2464     enddo
2465     enddo
2466     enddo
2467    
2468     do j=1,n
2469     do i=1,m
2470     fsdir(i,j)=fsdir(i,j)+fdndir(i,j)*ct(i,j)
2471     fsdif(i,j)=fsdif(i,j)+fdndif(i,j)*ct(i,j)
2472     enddo
2473     enddo
2474    
2475     100 continue
2476    
2477     return
2478     end
2479    
2480     c*****************************************************************
2481    
2482     subroutine flxco2(m,n,np,swc,swh,csm,df)
2483    
2484     c*****************************************************************
2485    
2486     c-----compute the reduction of clear-sky downward solar flux
2487     c due to co2 absorption.
2488    
2489     implicit none
2490    
2491     c-----input parameters
2492    
2493     integer m,n,np
2494 molod 1.12 _RL csm(m,n),swc(m,n,np+1),swh(m,n,np+1),cah(22,19)
2495 molod 1.1
2496     c-----output (undated) parameter
2497    
2498 molod 1.12 _RL df(m,n,np+1)
2499 molod 1.1
2500     c-----temporary array
2501    
2502     integer i,j,k,ic,iw
2503 molod 1.12 _RL xx,clog,wlog,dc,dw,x1,x2,y2
2504 molod 1.1
2505     c********************************************************************
2506     c-----include co2 look-up table
2507    
2508 molod 1.8 #include "cah-dat.h"
2509 molod 1.9 c save cah
2510 molod 1.1
2511     c********************************************************************
2512     c-----table look-up for the reduction of clear-sky solar
2513     c radiation due to co2. The fraction 0.0343 is the
2514     c extraterrestrial solar flux in the co2 bands.
2515    
2516     do k= 2, np+1
2517     do j= 1, n
2518     do i= 1, m
2519     xx=1./.3
2520     clog=log10(swc(i,j,k)*csm(i,j))
2521     wlog=log10(swh(i,j,k)*csm(i,j))
2522     ic=int( (clog+3.15)*xx+1.)
2523     iw=int( (wlog+4.15)*xx+1.)
2524     if(ic.lt.2)ic=2
2525     if(iw.lt.2)iw=2
2526     if(ic.gt.22)ic=22
2527     if(iw.gt.19)iw=19
2528     dc=clog-float(ic-2)*.3+3.
2529     dw=wlog-float(iw-2)*.3+4.
2530     x1=cah(1,iw-1)+(cah(1,iw)-cah(1,iw-1))*xx*dw
2531     x2=cah(ic-1,iw-1)+(cah(ic-1,iw)-cah(ic-1,iw-1))*xx*dw
2532     y2=x2+(cah(ic,iw-1)-cah(ic-1,iw-1))*xx*dc
2533     if (x1.lt.y2) x1=y2
2534     df(i,j,k)=df(i,j,k)+0.0343*(x1-y2)
2535     enddo
2536     enddo
2537     enddo
2538    
2539     return
2540     end

  ViewVC Help
Powered by ViewVC 1.1.22