/[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.15 - (hide annotations) (download)
Wed Jul 28 20:38:53 2004 UTC (19 years, 11 months ago) by molod
Branch: MAIN
Changes since 1.14: +214 -8 lines
debugging

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

  ViewVC Help
Powered by ViewVC 1.1.22