source: trunk/WRF.COMMON/WRFV2/phys/module_ra_gsfcsw.F @ 3094

Last change on this file since 3094 was 11, checked in by aslmd, 14 years ago

spiga@svn-planeto:ajoute le modele meso-echelle martien

File size: 107.8 KB
Line 
1!Comment the following out to turn off aerosol-radiation
2!feedback between MOSAIC and GSFCSW. wig, 21-Feb-2005
3#ifdef WRF_CHEM
4#define AER_RA_FEEDBACK   
5#endif
6
7MODULE module_ra_gsfcsw
8
9   REAL,    PARAMETER, PRIVATE ::   thresh=1.e-9
10   REAL,    SAVE               ::   center_lat
11
12!  Assign co2 and trace gases amount (units are parts/part by volumn)
13
14   REAL,    PARAMETER, PRIVATE ::   co2   = 300.e-6
15
16CONTAINS
17
18!------------------------------------------------------------------
19! urban related variable are added to arguments of gsfcswrad
20!------------------------------------------------------------------
21   SUBROUTINE GSFCSWRAD(rthraten,gsw,xlat,xlong                   &
22                   ,dz8w,rho_phy                                  &
23                   ,alb,t3d,qv3d,qc3d,qr3d                        &
24                   ,qi3d,qs3d,qg3d                                &
25                   ,p3d,p8w3d,pi3d,cldfra3d                       &
26                   ,gmt,cp,g,julday,xtime,declin,solcon           &
27                   ,radfrq,degrad,taucldi,taucldc,warm_rain       &
28                   ,tauaer300,tauaer400,tauaer600,tauaer999       & ! jcb
29                   ,gaer300,gaer400,gaer600,gaer999               & ! jcb
30                   ,waer300,waer400,waer600,waer999               & ! jcb
31                   ,f_qv,f_qc,f_qr,f_qi,f_qs,f_qg                 &
32                   ,ids,ide, jds,jde, kds,kde                     &
33                   ,ims,ime, jms,jme, kms,kme                     &
34                   ,its,ite, jts,jte, kts,kte                     &
35                   ,cosz_urb2d,omg_urb2d                          ) !Optional urban
36!------------------------------------------------------------------
37   IMPLICIT NONE
38!------------------------------------------------------------------
39   INTEGER,    PARAMETER     ::        np    = 75
40
41   INTEGER,    INTENT(IN   ) ::        ids,ide, jds,jde, kds,kde, &
42                                       ims,ime, jms,jme, kms,kme, &
43                                       its,ite, jts,jte, kts,kte
44   LOGICAL,    INTENT(IN   ) ::        warm_rain
45
46   INTEGER,    INTENT(IN  )  ::                           JULDAY 
47
48
49   REAL, INTENT(IN    )      ::        RADFRQ,DEGRAD,             &
50                                       XTIME,DECLIN,SOLCON
51!
52   REAL, DIMENSION( ims:ime, kms:kme, jms:jme ),                  &
53         INTENT(IN    ) ::                                   P3D, &
54                                                           P8W3D, &
55                                                            pi3D, &
56                                                             T3D, &
57                                                            dz8w, &
58                                                         rho_phy, &
59                                                        CLDFRA3D
60
61
62   REAL, DIMENSION( ims:ime, kms:kme, jms:jme ),                  &
63         INTENT(INOUT)  ::                              RTHRATEN
64   REAL, DIMENSION( ims:ime, kms:kme, jms:jme ),                  &
65         INTENT(INOUT)  ::                               taucldi, &
66                                                         taucldc
67!
68   REAL, DIMENSION( ims:ime, jms:jme ),                           &
69         INTENT(IN   )  ::                                  XLAT, &
70                                                           XLONG, &
71                                                             ALB
72!
73   REAL, DIMENSION( ims:ime, jms:jme ),                           &
74         INTENT(INOUT)  ::                                   GSW
75!
76   REAL, INTENT(IN   )  ::                              GMT,CP,G
77!
78
79!
80! Optional
81!
82   REAL, DIMENSION( ims:ime, kms:kme, jms:jme ), OPTIONAL ,       &
83         INTENT(IN    ) :: tauaer300,tauaer400,tauaer600,tauaer999, & ! jcb
84                                 gaer300,gaer400,gaer600,gaer999, & ! jcb
85                                 waer300,waer400,waer600,waer999    ! jcb
86
87   REAL, DIMENSION( ims:ime, kms:kme, jms:jme ),                  &
88         OPTIONAL,                                                &           
89         INTENT(IN    ) ::                                        &
90                                                            QV3D, &
91                                                            QC3D, &
92                                                            QR3D, &
93                                                            QI3D, &
94                                                            QS3D, &
95                                                            QG3D
96
97   LOGICAL, OPTIONAL, INTENT(IN )      ::        F_QV,F_QC,F_QR,F_QI,F_QS,F_QG
98
99! LOCAL VARS
100 
101   REAL, DIMENSION( its:ite ) ::                                  &
102                                                              ts, &
103                                                            cosz, &
104                                                          rsuvbm, &
105                                                          rsuvdf, &
106                                                          rsirbm, &
107                                                          rsirdf, &
108                                                            p400, &
109                                                            p700
110
111   INTEGER, DIMENSION( its:ite ) ::                               &
112                                                             ict, &
113                                                             icb   
114
115   REAL, DIMENSION( its:ite, kts-1:kte, 2 ) ::            taucld
116
117   REAL, DIMENSION( its:ite, kts-1:kte+1 )  ::               flx, &
118                                                            flxd
119!
120   REAL, DIMENSION( its:ite, kts-1:kte ) ::                     O3
121!
122   REAL, DIMENSION( its:ite, kts-1:kte, 11 ) ::                   &
123                                                           taual, &
124                                                           ssaal, &
125                                                           asyal
126
127   REAL, DIMENSION( its:ite, kts-1:kte, 2 ) ::                    &
128                                                            reff, &   
129                                                             cwc   
130   REAL, DIMENSION( its: ite, kts-1:kte+1 ) ::                    &
131                                                           P8W2D
132   REAL, DIMENSION( its: ite, kts-1:kte ) ::                      &
133                                                          TTEN2D, &
134                                                            SH2D, &
135                                                             P2D, &
136                                                             T2D, &
137                                                          fcld2D
138   real, DIMENSION( its:ite , kts:kte+1 ) :: phyd
139   real, DIMENSION( its:ite , kts:kte   ) :: phydmid
140
141   REAL, DIMENSION( np, 5 ) ::                              pres, &
142                                                           ozone
143   REAL, DIMENSION( np )    ::                                 p
144
145   LOGICAL :: cldwater,overcast, predicate
146!
147   INTEGER :: i,j,K,NK,ib,kk,mix,mkx
148
149!  iprof = 1  :  mid-latitude summer profile
150!        = 2  :  mid-latitude winter profile
151!        = 3  :  sub-arctic   summer profile
152!        = 4  :  sub-arctic   winter profile
153!        = 5  :  tropical profile
154!
155
156   INTEGER  ::                                             iprof, &
157                                                       is_summer, &
158                                                       ie_summer, &
159                                                          lattmp
160
161
162!
163   REAL    :: XLAT0,XLONG0
164   REAL    :: fac,latrmp
165   REAL    :: xt24,tloctm,hrang,xxlat
166
167!URBAN
168   REAL, OPTIONAL, DIMENSION( ims:ime, jms:jme ), INTENT(OUT)  :: COSZ_URB2D !urban
169   REAL, OPTIONAL, DIMENSION( ims:ime, jms:jme ), INTENT(OUT)  :: OMG_URB2D  !urban
170
171   real, dimension(11) :: midbands  ! jcb
172   data midbands/.2,.235,.27,.2875,.3025,.305,.3625,.55,1.92,1.745,6.135/   ! jcb
173   real :: ang,slope ! jcb
174   character(len=200) :: msg !wig
175!
176!--------------------------------------------------------------------------------
177!   data set 1
178!     mid-latitude summer (75 levels) :  p(mb)  o3(g/g)
179!     surface temp = 294.0
180!
181      data (pres(i,1),i=1,np)/ &
182          0.0006244,   0.0008759,   0.0012286,   0.0017234,   0.0024174, &
183          0.0033909,   0.0047565,   0.0066720,   0.0093589,   0.0131278, &
184          0.0184145,   0.0258302,   0.0362323,   0.0508234,   0.0712906, &
185          0.1000000,   0.1402710,   0.1967600,   0.2759970,   0.3871430, &
186          0.5430,    0.7617,    1.0685,    1.4988,    2.1024,    2.9490, &
187          4.1366,    5.8025,    8.1392,   11.4170,   16.0147,   22.4640, &
188         31.5105,   44.2001,   62.0000,   85.7750,  109.5500,  133.3250, &
189        157.1000,  180.8750,  204.6500,  228.4250,  252.2000,  275.9750, &
190        299.7500,  323.5250,  347.3000,  371.0750,  394.8500,  418.6250, &
191        442.4000,  466.1750,  489.9500,  513.7250,  537.5000,  561.2750, &
192        585.0500,  608.8250,  632.6000,  656.3750,  680.1500,  703.9250, &
193        727.7000,  751.4750,  775.2500,  799.0250,  822.8000,  846.5750, &
194        870.3500,  894.1250,  917.9000,  941.6750,  965.4500,  989.2250, &
195       1013.0000/
196!
197      data (ozone(i,1),i=1,np)/ &
198        0.1793E-06,  0.2228E-06,  0.2665E-06,  0.3104E-06,  0.3545E-06, &
199        0.3989E-06,  0.4435E-06,  0.4883E-06,  0.5333E-06,  0.5786E-06, &
200        0.6241E-06,  0.6698E-06,  0.7157E-06,  0.7622E-06,  0.8557E-06, &
201        0.1150E-05,  0.1462E-05,  0.1793E-05,  0.2143E-05,  0.2512E-05, &
202        0.2902E-05,  0.3313E-05,  0.4016E-05,  0.5193E-05,  0.6698E-05, &
203        0.8483E-05,  0.9378E-05,  0.9792E-05,  0.1002E-04,  0.1014E-04, &
204        0.9312E-05,  0.7834E-05,  0.6448E-05,  0.5159E-05,  0.3390E-05, &
205        0.1937E-05,  0.1205E-05,  0.8778E-06,  0.6935E-06,  0.5112E-06, &
206        0.3877E-06,  0.3262E-06,  0.2770E-06,  0.2266E-06,  0.2020E-06, &
207        0.1845E-06,  0.1679E-06,  0.1519E-06,  0.1415E-06,  0.1317E-06, &
208        0.1225E-06,  0.1137E-06,  0.1055E-06,  0.1001E-06,  0.9487E-07, &
209        0.9016E-07,  0.8641E-07,  0.8276E-07,  0.7930E-07,  0.7635E-07, &
210        0.7347E-07,  0.7065E-07,  0.6821E-07,  0.6593E-07,  0.6368E-07, &
211        0.6148E-07,  0.5998E-07,  0.5859E-07,  0.5720E-07,  0.5582E-07, &
212        0.5457E-07,  0.5339E-07,  0.5224E-07,  0.5110E-07,  0.4999E-07/
213
214!--------------------------------------------------------------------------------
215!   data set 2
216!   mid-latitude winter (75 levels) :  p(mb)  o3(g/g)
217!   surface temp = 272.2
218!
219      data (pres(i,2),i=1,np)/ &
220          0.0006244,   0.0008759,   0.0012286,   0.0017234,   0.0024174, &
221          0.0033909,   0.0047565,   0.0066720,   0.0093589,   0.0131278, &
222          0.0184145,   0.0258302,   0.0362323,   0.0508234,   0.0712906, &
223          0.1000000,   0.1402710,   0.1967600,   0.2759970,   0.3871430, &
224          0.5430,    0.7617,    1.0685,    1.4988,    2.1024,    2.9490, &
225          4.1366,    5.8025,    8.1392,   11.4170,   16.0147,   22.4640, &
226         31.5105,   44.2001,   62.0000,   85.9000,  109.8000,  133.7000, &
227        157.6000,  181.5000,  205.4000,  229.3000,  253.2000,  277.1000, &
228        301.0000,  324.9000,  348.8000,  372.7000,  396.6000,  420.5000, &
229        444.4000,  468.3000,  492.2000,  516.1000,  540.0000,  563.9000, &
230        587.8000,  611.7000,  635.6000,  659.5000,  683.4000,  707.3000, &
231        731.2000,  755.1000,  779.0000,  802.9000,  826.8000,  850.7000, &
232        874.6000,  898.5000,  922.4000,  946.3000,  970.2000,  994.1000, &
233       1018.0000/
234!
235      data (ozone(i,2),i=1,np)/ &
236        0.2353E-06,  0.3054E-06,  0.3771E-06,  0.4498E-06,  0.5236E-06, &
237        0.5984E-06,  0.6742E-06,  0.7511E-06,  0.8290E-06,  0.9080E-06, &
238        0.9881E-06,  0.1069E-05,  0.1152E-05,  0.1319E-05,  0.1725E-05, &
239        0.2145E-05,  0.2581E-05,  0.3031E-05,  0.3497E-05,  0.3980E-05, &
240        0.4478E-05,  0.5300E-05,  0.6725E-05,  0.8415E-05,  0.1035E-04, &
241        0.1141E-04,  0.1155E-04,  0.1143E-04,  0.1093E-04,  0.1060E-04, &
242        0.9720E-05,  0.8849E-05,  0.7424E-05,  0.6023E-05,  0.4310E-05, &
243        0.2820E-05,  0.1990E-05,  0.1518E-05,  0.1206E-05,  0.9370E-06, &
244        0.7177E-06,  0.5450E-06,  0.4131E-06,  0.3277E-06,  0.2563E-06, &
245        0.2120E-06,  0.1711E-06,  0.1524E-06,  0.1344E-06,  0.1199E-06, &
246        0.1066E-06,  0.9516E-07,  0.8858E-07,  0.8219E-07,  0.7598E-07, &
247        0.6992E-07,  0.6403E-07,  0.5887E-07,  0.5712E-07,  0.5540E-07, &
248        0.5370E-07,  0.5214E-07,  0.5069E-07,  0.4926E-07,  0.4785E-07, &
249        0.4713E-07,  0.4694E-07,  0.4676E-07,  0.4658E-07,  0.4641E-07, &
250        0.4634E-07,  0.4627E-07,  0.4619E-07,  0.4612E-07,  0.4605E-07/
251
252
253!--------------------------------------------------------------------------------
254!   data set 3
255!   sub-arctic summer (75 levels) :  p(mb)  o3(g/g)
256!   surface temp = 287.0
257!
258      data (pres(i,3),i=1,np)/ &
259          0.0006244,   0.0008759,   0.0012286,   0.0017234,   0.0024174, &
260          0.0033909,   0.0047565,   0.0066720,   0.0093589,   0.0131278, &
261          0.0184145,   0.0258302,   0.0362323,   0.0508234,   0.0712906, &
262          0.1000000,   0.1402710,   0.1967600,   0.2759970,   0.3871430, &
263          0.5430,    0.7617,    1.0685,    1.4988,    2.1024,    2.9490, &
264          4.1366,    5.8025,    8.1392,   11.4170,   16.0147,   22.4640, &
265         31.5105,   44.2001,   62.0000,   85.7000,  109.4000,  133.1000, &
266        156.8000,  180.5000,  204.2000,  227.9000,  251.6000,  275.3000, &
267        299.0000,  322.7000,  346.4000,  370.1000,  393.8000,  417.5000, &
268        441.2000,  464.9000,  488.6000,  512.3000,  536.0000,  559.7000, &
269        583.4000,  607.1000,  630.8000,  654.5000,  678.2000,  701.9000, &
270        725.6000,  749.3000,  773.0000,  796.7000,  820.4000,  844.1000, &
271        867.8000,  891.5000,  915.2000,  938.9000,  962.6000,  986.3000, &
272       1010.0000/
273!
274      data (ozone(i,3),i=1,np)/ &
275        0.1728E-06,  0.2131E-06,  0.2537E-06,  0.2944E-06,  0.3353E-06, &
276        0.3764E-06,  0.4176E-06,  0.4590E-06,  0.5006E-06,  0.5423E-06, &
277        0.5842E-06,  0.6263E-06,  0.6685E-06,  0.7112E-06,  0.7631E-06, &
278        0.1040E-05,  0.1340E-05,  0.1660E-05,  0.2001E-05,  0.2362E-05, &
279        0.2746E-05,  0.3153E-05,  0.3762E-05,  0.4988E-05,  0.6518E-05, &
280        0.8352E-05,  0.9328E-05,  0.9731E-05,  0.8985E-05,  0.7632E-05, &
281        0.6814E-05,  0.6384E-05,  0.5718E-05,  0.4728E-05,  0.4136E-05, &
282        0.3033E-05,  0.2000E-05,  0.1486E-05,  0.1121E-05,  0.8680E-06, &
283        0.6474E-06,  0.5164E-06,  0.3921E-06,  0.2996E-06,  0.2562E-06, &
284        0.2139E-06,  0.1723E-06,  0.1460E-06,  0.1360E-06,  0.1267E-06, &
285        0.1189E-06,  0.1114E-06,  0.1040E-06,  0.9678E-07,  0.8969E-07, &
286        0.8468E-07,  0.8025E-07,  0.7590E-07,  0.7250E-07,  0.6969E-07, &
287        0.6694E-07,  0.6429E-07,  0.6208E-07,  0.5991E-07,  0.5778E-07, &
288        0.5575E-07,  0.5403E-07,  0.5233E-07,  0.5067E-07,  0.4904E-07, &
289        0.4721E-07,  0.4535E-07,  0.4353E-07,  0.4173E-07,  0.3997E-07/
290
291
292!--------------------------------------------------------------------------------
293!   data set 3
294!   sub-arctic winter (75 levels) :   p(mb)  o3(g/g)
295!   surface temp = 257.1
296!
297      data (pres(i,4),i=1,np)/ &
298          0.0006244,   0.0008759,   0.0012286,   0.0017234,   0.0024174, &
299          0.0033909,   0.0047565,   0.0066720,   0.0093589,   0.0131278, &
300          0.0184145,   0.0258302,   0.0362323,   0.0508234,   0.0712906, &
301          0.1000000,   0.1402710,   0.1967600,   0.2759970,   0.3871430, &
302          0.5430,    0.7617,    1.0685,    1.4988,    2.1024,    2.9490, &
303          4.1366,    5.8025,    8.1392,   11.4170,   16.0147,   22.4640, &
304         31.5105,   44.2001,   62.0000,   85.7750,  109.5500,  133.3250, &
305        157.1000,  180.8750,  204.6500,  228.4250,  252.2000,  275.9750, &
306        299.7500,  323.5250,  347.3000,  371.0750,  394.8500,  418.6250, &
307        442.4000,  466.1750,  489.9500,  513.7250,  537.5000,  561.2750, &
308        585.0500,  608.8250,  632.6000,  656.3750,  680.1500,  703.9250, &
309        727.7000,  751.4750,  775.2500,  799.0250,  822.8000,  846.5750, &
310        870.3500,  894.1250,  917.9000,  941.6750,  965.4500,  989.2250, &
311       1013.0000/
312!
313      data (ozone(i,4),i=1,np)/ &
314        0.2683E-06,  0.3562E-06,  0.4464E-06,  0.5387E-06,  0.6333E-06, &
315        0.7301E-06,  0.8291E-06,  0.9306E-06,  0.1034E-05,  0.1140E-05, &
316        0.1249E-05,  0.1360E-05,  0.1474E-05,  0.1855E-05,  0.2357E-05, &
317        0.2866E-05,  0.3383E-05,  0.3906E-05,  0.4437E-05,  0.4975E-05, &
318        0.5513E-05,  0.6815E-05,  0.8157E-05,  0.1008E-04,  0.1200E-04, &
319        0.1242E-04,  0.1250E-04,  0.1157E-04,  0.1010E-04,  0.9063E-05, &
320        0.8836E-05,  0.8632E-05,  0.8391E-05,  0.7224E-05,  0.6054E-05, &
321        0.4503E-05,  0.3204E-05,  0.2278E-05,  0.1833E-05,  0.1433E-05, &
322        0.9996E-06,  0.7440E-06,  0.5471E-06,  0.3944E-06,  0.2852E-06, &
323        0.1977E-06,  0.1559E-06,  0.1333E-06,  0.1126E-06,  0.9441E-07, &
324        0.7678E-07,  0.7054E-07,  0.6684E-07,  0.6323E-07,  0.6028E-07, &
325        0.5746E-07,  0.5468E-07,  0.5227E-07,  0.5006E-07,  0.4789E-07, &
326        0.4576E-07,  0.4402E-07,  0.4230E-07,  0.4062E-07,  0.3897E-07, &
327        0.3793E-07,  0.3697E-07,  0.3602E-07,  0.3506E-07,  0.3413E-07, &
328        0.3326E-07,  0.3239E-07,  0.3153E-07,  0.3069E-07,  0.2987E-07/
329
330!--------------------------------------------------------------------------------
331!   data set 4
332!   tropical (75 levels) :   p(mb)  o3(g/g)
333!   surface temp = 300.0
334!
335      data (pres(i,5),i=1,np)/ &
336          0.0006244,   0.0008759,   0.0012286,   0.0017234,   0.0024174, &
337          0.0033909,   0.0047565,   0.0066720,   0.0093589,   0.0131278, &
338          0.0184145,   0.0258302,   0.0362323,   0.0508234,   0.0712906, &
339          0.1000000,   0.1402710,   0.1967600,   0.2759970,   0.3871430, &
340          0.5430,    0.7617,    1.0685,    1.4988,    2.1024,    2.9490, &
341          4.1366,    5.8025,    8.1392,   11.4170,   16.0147,   22.4640, &
342         31.5105,   44.2001,   62.0000,   85.7750,  109.5500,  133.3250, &
343        157.1000,  180.8750,  204.6500,  228.4250,  252.2000,  275.9750, &
344        299.7500,  323.5250,  347.3000,  371.0750,  394.8500,  418.6250, &
345        442.4000,  466.1750,  489.9500,  513.7250,  537.5000,  561.2750, &
346        585.0500,  608.8250,  632.6000,  656.3750,  680.1500,  703.9250, &
347        727.7000,  751.4750,  775.2500,  799.0250,  822.8000,  846.5750, &
348        870.3500,  894.1250,  917.9000,  941.6750,  965.4500,  989.2250, &
349       1013.0000/
350!
351      data (ozone(i,5),i=1,np)/ &
352        0.1993E-06,  0.2521E-06,  0.3051E-06,  0.3585E-06,  0.4121E-06, &
353        0.4661E-06,  0.5203E-06,  0.5748E-06,  0.6296E-06,  0.6847E-06, &
354        0.7402E-06,  0.7959E-06,  0.8519E-06,  0.9096E-06,  0.1125E-05, &
355        0.1450E-05,  0.1794E-05,  0.2156E-05,  0.2538E-05,  0.2939E-05, &
356        0.3362E-05,  0.3785E-05,  0.4753E-05,  0.6005E-05,  0.7804E-05, &
357        0.9635E-05,  0.1023E-04,  0.1067E-04,  0.1177E-04,  0.1290E-04, &
358        0.1134E-04,  0.9223E-05,  0.6667E-05,  0.3644E-05,  0.1545E-05, &
359        0.5355E-06,  0.2523E-06,  0.2062E-06,  0.1734E-06,  0.1548E-06, &
360        0.1360E-06,  0.1204E-06,  0.1074E-06,  0.9707E-07,  0.8960E-07, &
361        0.8419E-07,  0.7962E-07,  0.7542E-07,  0.7290E-07,  0.7109E-07, &
362        0.6940E-07,  0.6786E-07,  0.6635E-07,  0.6500E-07,  0.6370E-07, &
363        0.6244E-07,  0.6132E-07,  0.6022E-07,  0.5914E-07,  0.5884E-07, &
364        0.5855E-07,  0.5823E-07,  0.5772E-07,  0.5703E-07,  0.5635E-07, &
365        0.5570E-07,  0.5492E-07,  0.5412E-07,  0.5335E-07,  0.5260E-07, &
366        0.5167E-07,  0.5063E-07,  0.4961E-07,  0.4860E-07,  0.4761E-07/
367
368!--------------------------------------------------------------------------------
369
370#ifdef AER_RA_FEEDBACK   
371   IF ( .NOT. &
372      ( PRESENT(tauaer300) .AND. &
373        PRESENT(tauaer400) .AND. &
374        PRESENT(tauaer600) .AND. &
375        PRESENT(tauaer999) .AND. &
376        PRESENT(gaer300) .AND. &
377        PRESENT(gaer400) .AND. &
378        PRESENT(gaer600) .AND. &
379        PRESENT(gaer999) .AND. &
380        PRESENT(waer300) .AND. &
381        PRESENT(waer400) .AND. &
382        PRESENT(waer600) .AND. &
383        PRESENT(waer999) ) ) THEN
384      CALL wrf_error_fatal ( 'Warning: missing fields required for aerosol radiation' )
385   ENDIF
386#endif
387   cldwater = .true.
388   overcast = .false.
389
390   mix=ite-its+1
391   mkx=kte-kts+1
392
393   is_summer=80
394   ie_summer=265
395
396! testing, need to change iprof, which is function of lat and julian day
397!  iprof = 1  :  mid-latitude summer profile
398!        = 2  :  mid-latitude winter profile
399!        = 3  :  sub-arctic   summer profile
400!        = 4  :  sub-arctic   winter profile
401!        = 5  :  tropical profile
402
403   IF (abs(center_lat) .le. 30. ) THEN ! tropic
404      iprof = 5
405   ELSE
406      IF (center_lat .gt.  0.) THEN
407         IF (center_lat .gt. 60. ) THEN !  arctic
408            IF (JULDAY .gt. is_summer .and. JULDAY .lt. ie_summer ) THEN
409               ! arctic summer
410               iprof = 3
411            ELSE
412               ! arctic winter
413               iprof = 4
414            ENDIF
415         ELSE        ! midlatitude
416            IF (JULDAY .gt. is_summer .and. JULDAY .lt. ie_summer ) THEN
417               ! north midlatitude summer
418               iprof = 1
419            ELSE
420               ! north midlatitude winter
421               iprof = 2
422            ENDIF
423         ENDIF
424
425      ELSE
426         IF (center_lat .lt. -60. ) THEN !  antarctic
427            IF (JULDAY .lt. is_summer .or. JULDAY .gt. ie_summer ) THEN
428               ! antarctic summer
429               iprof = 3
430            ELSE
431               ! antarctic winter
432               iprof = 4
433            ENDIF
434         ELSE        ! midlatitude
435            IF (JULDAY .lt. is_summer .or. JULDAY .gt. ie_summer ) THEN
436               ! south midlatitude summer
437               iprof = 1
438            ELSE
439               ! south midlatitude winter
440               iprof = 2
441            ENDIF
442         ENDIF
443
444      ENDIF
445   ENDIF
446
447
448   j_loop: DO J=jts,jte
449
450      DO K=kts,kte         
451      DO I=its,ite         
452         cwc(i,k,1) = 0.
453         cwc(i,k,2) = 0.
454      ENDDO
455      ENDDO
456
457      DO K=1,np
458         p(k)=pres(k,iprof)
459      ENDDO
460
461      do k = kts,kte+1
462      do i = its,ite
463      if(k.eq.kts)then
464        phyd(i,k)=p8w3d(i,kts,j)
465      else
466        phyd(i,k)=phyd(i,k-1) - g*rho_phy(i,k-1,j)*dz8w(i,k-1,j)
467        phydmid(i,k-1)=0.5*(phyd(i,k-1)+phyd(i,k))
468      endif
469      enddo
470      enddo
471
472! reverse vars
473!
474      DO K=kts,kte+1
475      DO I=its,ite
476         NK=kme-K+kms
477         P8W2D(I,K)=phyd(I,NK)*0.01   ! P8w2D is in mb
478      ENDDO
479      ENDDO
480
481      DO I=its,ite
482         P8W2D(I,0)=.0
483      ENDDO
484!
485      DO K=kts,kte
486      DO I=its,ite
487         NK=kme-1-K+kms
488         TTEN2D(I,K)=0.
489         T2D(I,K)=T3D(I,NK,J)
490
491! SH2D specific humidity
492         SH2D(I,K)=QV3D(I,NK,J)/(1.+QV3D(I,NK,J))
493         SH2D(I,K)=max(0.,SH2D(I,K))
494         cwc(I,K,2)=QC3D(I,NK,J)
495         cwc(I,K,2)=max(0.,cwc(I,K,2))
496
497         P2D(I,K)=phydmid(I,NK)*0.01      ! P2D is in mb
498         fcld2D(I,K)=CLDFRA3D(I,NK,J)
499      ENDDO
500      ENDDO
501
502! This logic is tortured because cannot test F_QI unless
503! it is present, and order of evaluation of expressions
504! is not specified in Fortran
505
506      IF ( PRESENT ( F_QI ) ) THEN
507        predicate = F_QI
508      ELSE
509        predicate = .FALSE.
510      ENDIF
511
512      IF (.NOT. warm_rain .AND. .NOT. predicate ) THEN
513         DO K=kts,kte
514         DO I=its,ite
515            IF (T2D(I,K) .lt. 273.15) THEN
516               cwc(I,K,1)=cwc(I,K,2)
517               cwc(I,K,2)=0.
518            ENDIF
519         ENDDO
520         ENDDO
521      ENDIF
522
523      DO I=its,ite
524         TTEN2D(I,0)=0.
525         T2D(I,0)=T2D(I,1)
526! SH2D specific humidity
527         SH2D(I,0)=0.5*SH2D(i,1)
528         cwc(I,0,2)=0.
529         cwc(I,0,1)=0.
530         P2D(I,0)=0.5*(P8W2D(I,0)+P8W2D(I,1))
531         fcld2D(I,0)=0.
532      ENDDO
533!
534      IF ( PRESENT( F_QI ) .AND. PRESENT( qi3d)  ) THEN
535         IF ( (F_QI) ) THEN
536            DO K=kts,kte         
537            DO I=its,ite         
538               NK=kme-1-K+kms
539               cwc(I,K,1)=QI3D(I,NK,J)
540               cwc(I,K,1)=max(0.,cwc(I,K,1))
541            ENDDO
542            ENDDO
543         ENDIF
544      ENDIF
545!
546! ... Vertical profiles for ozone
547!
548      call o3prof (np, p, ozone(1,iprof), its, ite, kts-1, kte, P2D, O3)
549
550! ... Vertical profiles for effective particle size
551!
552      do k = kts-1, kte
553      do i = its, ite
554         reff(i,k,2) = 10.
555         reff(i,k,1) = 80.
556      end do
557      end do
558!
559! ... Level indices separating high, middle and low clouds
560!
561      do i = its, ite
562         p400(i) = 1.e5
563         p700(i) = 1.e5
564      enddo
565
566      do k = kts-1,kte+1
567         do i = its, ite
568            if (abs(P8W2D(i,k) - 400.) .lt. p400(i)) then
569               p400(i) = abs(P8W2D(i,k) - 400.)
570               ict(i) = k
571            endif
572            if (abs(P8W2D(i,k) - 700.) .lt. p700(i)) then
573               p700(i) = abs(P8W2D(i,k) - 700.)
574               icb(i) = k
575            endif
576        end do
577      end do
578
579!wig beg
580! ... Aerosol effects. Added aerosol feedbacks with MOSAIC, Dec. 2005.
581!
582      do ib = 1, 11
583      do k = kts-1,kte
584      do i = its,ite
585         taual(i,k,ib) = 0.
586         ssaal(i,k,ib) = 0.
587         asyal(i,k,ib) = 0.
588      end do
589      end do
590      end do
591
592#ifdef AER_RA_FEEDBACK
593!wig end
594      do ib = 1, 11
595      do k = kts-1,kte-1      !wig
596      do i = its,ite
597
598!        taual(i,kte-k,ib) = 0.
599!        ssaal(i,kte-k,ib) = 0.
600!        asyal(i,kte-k,ib) = 0.
601
602!jcb beg
603! convert optical properties at 300,400,600, and 999 to conform to the band wavelengths
604! these are: 200,235,270,287.5,302.5,305,362.5,550,1920,1745,6135; why the emphasis on the UV?
605! taual - use angstrom exponent
606        if(tauaer300(i,k+1,j).gt.thresh .and. tauaer999(i,k+1,j).gt.thresh) then
607           ang=log(tauaer300(i,k+1,j)/tauaer999(i,k+1,j))/log(999./300.)
608!       write(6,*)i,k,ang,tauaer300(i,k+1,j),tauaer999(i,k+1,j)
609           taual(i,kte-k,ib)=tauaer400(i,k+1,j)*(0.4/midbands(ib))**ang ! notice reserved variable
610!       write(6,10001)i,k,ang,tauaer300(i,k+1,j),tauaer999(i,k+1,j),midbands(ib),taual(i,k,ib)
611!10001      format(i3,i3,5f12.6)
612
613! ssa - linear interpolation; extrapolation
614           slope=(waer600(i,k+1,j)-waer400(i,k+1,j))/.2
615           ssaal(i,kte-k,ib) = slope*(midbands(ib)-.6)+waer600(i,k+1,j) ! notice reversed variables
616           if(ssaal(i,kte-k,ib).lt.0.4) ssaal(i,kte-k,ib)=0.4
617           if(ssaal(i,kte-k,ib).ge.0.9) ssaal(i,kte-k,ib)=0.9
618
619! g - linear interpolation;extrapolation
620           slope=(gaer600(i,k+1,j)-gaer400(i,k+1,j))/.2
621           asyal(i,kte-k,ib) = slope*(midbands(ib)-.6)+gaer600(i,k+1,j) ! notice reversed varaibles
622           if(asyal(i,kte-k,ib).lt.0.5) asyal(i,kte-k,ib)=0.5
623           if(asyal(i,kte-k,ib).ge.1.0) asyal(i,kte-k,ib)=1.0
624        endif
625!jcb end
626      end do
627      end do
628      end do
629
630!wig beg
631      do ib = 1, 11
632      do i = its,ite
633         slope = 0.  !use slope as a sum holder
634         do k = kts-1,kte
635            slope = slope + taual(i,k,ib)
636         end do
637         if( slope < 0. ) then
638            write(msg,'("ERROR: Negative total optical depth of ",f8.2," at point i,j,ib=",3i5)') slope,i,j,ib
639            call wrf_error_fatal(msg)
640         else if( slope > 5. ) then
641            call wrf_message("-------------------------")
642            write(msg,'("WARNING: Large total optical depth of ",f8.2," at point i,j,ib=",3i5)') slope,i,j,ib
643            call wrf_message(msg)
644
645            call wrf_message("Diagnostics 1: k, tauaer300, tauaer400, tauaer600, tauaer999")
646            do k=kts,kte
647               write(msg,'(i4,4f8.2)') k, tauaer300(i,k,j), tauaer400(i,k,j), &
648                    tauaer600(i,k,j), tauaer999(i,k,j)
649               call wrf_message(msg)
650            end do
651
652            call wrf_message("Diagnostics 2: k, gaer300, gaer400, gaer600, gaer999")
653            do k=kts,kte
654               write(msg,'(i4,4f8.2)') k, gaer300(i,k,j), gaer400(i,k,j), &
655                    gaer600(i,k,j), gaer999(i,k,j)
656               call wrf_message(msg)
657            end do
658
659            call wrf_message("Diagnostics 3: k, waer300, waer400, waer600, waer999")
660            do k=kts,kte
661               write(msg,'(i4,4f8.2)') k, waer300(i,k,j), waer400(i,k,j), &
662                    waer600(i,k,j), waer999(i,k,j)
663               call wrf_message(msg)
664            end do
665
666            call wrf_message("Diagnostics 4: k, ssaal, asyal, taual")
667            do k=kts-1,kte
668               write(msg,'(i4,3f8.2)') k, ssaal(i,k,ib), asyal(i,k,ib), taual(i,k,ib)
669               call wrf_message(msg)
670            end do
671            call wrf_message("-------------------------")
672         end if
673      end do
674      end do
675!wig end
676#endif
677!
678! ... Initialize output arrays
679!
680      do ib = 1, 2
681      do k = kts-1, kte
682      do i = its, ite
683         taucld(i,k,ib) = 0.
684      end do
685      end do
686      end do
687!
688      do k = kts-1,kte+1
689      do i = its,ite
690         flx(i,k)   = 0.
691         flxd(i,k)  = 0.
692      end do
693      end do
694!
695! ... Solar zenith angle
696!
697      do i = its,ite
698        xt24 = mod(xtime + radfrq * 0.5, 1440.)
699        tloctm = GMT + xt24 / 60. + XLONG(i,j) / 15.
700        hrang = 15. * (tloctm - 12.) * degrad
701        xxlat = XLAT(i,j) * degrad
702        cosz(i) = sin(xxlat) * sin(declin) + &
703                  cos(xxlat) * cos(declin) * cos(hrang)
704!urban
705       if(present(COSZ_URB2D)) COSZ_URB2D(i,j)=cosz(i)  !urban
706       if(present(OMG_URB2D)) OMG_URB2D(i,j)=hrang     !urban
707        rsuvbm(i) = ALB(i,j)
708        rsuvdf(i) = ALB(i,j)
709        rsirbm(i) = ALB(i,j)
710        rsirdf(i) = ALB(i,j)
711      end do
712                                 
713      call sorad (mix,1,1,mkx+1,p8w2D,t2D,sh2D,o3,                 &
714                  overcast,cldwater,cwc,taucld,reff,fcld2D,ict,icb,&
715                  taual,ssaal,asyal,                               &
716                  cosz,rsuvbm,rsuvdf,rsirbm,rsirdf,                &
717                  flx,flxd)
718!
719! ... Convert the units of flx and flc from fraction to w/m^2
720!
721      do k = kts, kte
722      do i = its, ite
723         nk=kme-1-k+kms
724         taucldc(i,nk,j)=taucld(i,k,2)
725         taucldi(i,nk,j)=taucld(i,k,1)
726      enddo
727      enddo
728 
729      do k = kts, kte+1
730        do i = its, ite
731          if (cosz(i) .lt. thresh) then
732            flx(i,k) = 0.
733          else
734            flx(i,k) = flx(i,k) * SOLCON * cosz(i)
735          endif
736        end do
737      end do
738!
739! ... Calculate heating rate (deg/sec)
740!
741      fac = .01 * g / Cp
742      do k = kts, kte
743      do i = its, ite
744         if (cosz(i) .gt. thresh) then
745             TTEN2D(i,k) = - fac * (flx(i,k) - flx(i,k+1))/ &
746                           (p8w2d(i,k)-p8w2d(i,k+1))
747         endif
748      end do
749      end do
750
751!
752! ... Absorbed part in surface energy budget
753!
754      do i = its, ite
755        if (cosz(i) .le. thresh) then
756          GSW(i,j) = 0.
757        else
758          GSW(i,j) = (1. - rsuvbm(i)) * flxd(i,kte+1) * SOLCON * cosz(i)
759        endif
760      end do
761
762      DO K=kts,kte         
763         NK=kme-1-K+kms
764         DO I=its,ite
765            RTHRATEN(I,K,J)=RTHRATEN(I,K,J)+TTEN2D(I,NK)/pi3D(I,K,J)
766         ENDDO
767      ENDDO
768!
769   ENDDO j_loop                                         
770
771   END SUBROUTINE GSFCSWRAD
772
773!*********************   Version Solar-6 (May 8, 1997)  *****************
774
775      subroutine sorad (m,n,ndim,np,pl,ta,wa,oa,                        &
776                        overcast,cldwater,cwc,taucld,reff,fcld,ict,icb, &
777                        taual,ssaal,asyal,                              &
778                        cosz,rsuvbm,rsuvdf,rsirbm,rsirdf,               &
779                        flx,flxd)
780
781!************************************************************************
782!
783!                        Version Solar-6 (May 8, 1997)
784!
785!  New feature of this version is:
786!   (1) An option is added for scaling the cloud optical thickness. If
787!       the fractional cloud cover, fcld, in an atmospheric model is alway
788!       either 1 or 0 (i.e. partly cloudy sky is not allowed), it does
789!       not require the scaling of cloud optical thickness, and the
790!       option "overcast" can be set to .true.  Computation is faster
791!       with this option than with overcast=.false.
792!
793!**********************************************************************
794!
795!                        Version Solar-5 (April 1997)
796!
797!  New features of this version are:
798!   (1) Cloud optical properties can be computed from cloud water/ice
799!       amount and the effective particle size.
800!   (2) Aerosol optical properties are functions of height and band.
801!   (3) A maximum-random cloud overlapping approximation is applied.
802!
803!*********************************************************************
804
805! This routine computes solar fluxes due to the absoption by water
806!  vapor, ozone, co2, o2, clouds, and aerosols and due to the
807!  scattering by clouds, aerosols, and gases.
808!
809! The solar spectrum is divided into one UV+visible band and three IR
810!  bands separated by the wavelength 0.7 micron.  The UV+visible band
811!  is further divided into eight sub-bands.
812!
813! This is a vectorized code. It computes fluxes simultaneously for
814!  (m x n) soundings, which is a subset of (m x ndim) soundings.
815!  In a global climate model, m and ndim correspond to the numbers of
816!  grid boxes in the zonal and meridional directions, respectively.
817!
818! Ice and liquid cloud particles are allowed to co-exist in a layer.
819!
820! There is an option of providing either cloud ice/water mixing ratio
821!  (cwc) or thickness (taucld).  If the former is provided, set
822!  cldwater=.true., and taucld will be computed from cwc and reff as a
823!  function of spectra band. Otherwise, set cldwater=.false., and
824!  specify taucld, independent of spectral band.
825!
826! If no information is available for reff, a default value of
827!  10 micron for liquid water and 75 micron for ice can be used.
828!  For a clear layer, reff can be set to any values except zero.
829!
830! The maximum-random assumption is applied for treating cloud
831!  overlapping.
832
833! Clouds are grouped into high, middle, and low clouds separated by
834!  the level indices ict and icb.  For detail, see subroutine cldscale.
835!
836! In a high spatial-resolution atmospheric model, fractional cloud cover
837!  might be computed to be either 0 or 1.  In such a case, scaling of the
838!  cloud optical thickness is not necessary, and the computation can be
839!  made faster by setting overcast=.true.  The option overcast=.false.
840!  can be applied to any values of the fractional cloud cover, but the
841!  computation is slower.
842!
843! Aerosol optical thickness, single-scattering albaedo, and asymmtry
844!  factor can be specified as functions of height and spectral band.
845!
846!----- Input parameters:                           
847!                                                   units      size
848!  number of soundings in zonal direction (m)       n/d        1
849!  number of soundings in meridional direction (n)  n/d        1
850!  maximum number of soundings in                   n/d        1
851!         meridional direction (ndim>=n)
852!  number of atmospheric layers (np)                n/d        1
853!  level pressure (pl)                              mb     m*ndim*(np+1)
854!  layer temperature (ta)                           k        m*ndim*np
855!  layer specific humidity (wa)                     gm/gm    m*ndim*np
856!  layer ozone concentration (oa)                   gm/gm    m*ndim*np
857!  co2 mixing ratio by volumn (co2)                 pppv       1
858!  option for scaling cloud optical thickness       n/d        1
859!        overcast="true" if scaling is NOT required
860!        overcast="fasle" if scaling is required
861!  option for cloud optical thickness               n/d        1
862!        cldwater="true" if cwc is provided
863!        cldwater="false" if taucld is provided
864!  cloud water mixing ratio (cwc)                  gm/gm     m*ndim*np*2
865!        index 1 for ice particles
866!        index 2 for liquid drops
867!  cloud optical thickness (taucld)                 n/d      m*ndim*np*2
868!        index 1 for ice particles
869!        index 2 for liquid drops
870!  effective cloud-particle size (reff)          micrometer m*ndim*np*2
871!        index 1 for ice particles
872!        index 2 for liquid drops
873!  cloud amount (fcld)                            fraction   m*ndim*np
874!  level index separating high and middle           n/d        1
875!        clouds (ict)
876!  level index separating middle and low            n/d        1
877!          clouds (icb)
878!  aerosol optical thickness (taual)                n/d    m*ndim*np*11
879!  aerosol single-scattering albedo (ssaal)         n/d    m*ndim*np*11
880!  aerosol asymmetry factor (asyal)                 n/d    m*ndim*np*11
881!        in the uv region :
882!           index  1 for the 0.175-0.225 micron band
883!           index  2 for the 0.225-0.245; 0.260-0.280 micron band
884!           index  3 for the 0.245-0.260 micron band
885!           index  4 for the 0.280-0.295 micron band
886!           index  5 for the 0.295-0.310 micron band
887!           index  6 for the 0.310-0.320 micron band
888!           index  7 for the 0.325-0.400 micron band
889!        in the par region :
890!           index  8 for the 0.400-0.700 micron band
891!        in the infrared region :
892!           index  9 for the 0.700-1.220 micron band
893!           index 10 for the 1.220-2.270 micron band
894!           index 11 for the 2.270-10.00 micron band
895!   cosine of solar zenith angle (cosz)              n/d      m*ndim
896!   uv+visible sfc albedo for beam radiation
897!        for wavelengths<0.7 micron (rsuvbm)    fraction   m*ndim
898!   uv+visible sfc albedo for diffuse radiation
899!        for wavelengths<0.7 micron (rsuvdf)    fraction   m*ndim
900!   ir sfc albedo for beam radiation
901!        for wavelengths>0.7 micron  (rsirbm)   fraction   m*ndim
902!   ir sfc albedo for diffuse radiation (rsirdf)   fraction   m*ndim
903!
904!----- Output parameters
905!
906!   all-sky flux (downward minus upward) (flx)    fraction m*ndim*(np+1)
907!   clear-sky flux (downward minus upward) (flc)  fraction m*ndim*(np+1)
908!   all-sky direct downward uv (0.175-0.4 micron)
909!                flux at the surface (fdiruv)      fraction   m*ndim
910!   all-sky diffuse downward uv flux at
911!                the surface (fdifuv)              fraction   m*ndim
912!   all-sky direct downward par (0.4-0.7 micron)
913!                flux at the surface (fdirpar)     fraction   m*ndim
914!   all-sky diffuse downward par flux at
915!                the surface (fdifpar)             fraction   m*ndim
916!   all-sky direct downward ir (0.7-10 micron)
917!                flux at the surface (fdirir)      fraction   m*ndim
918!   all-sky diffuse downward ir flux at
919!                the surface (fdifir)              fraction   m*ndim
920!
921!----- Notes:
922!
923!    (1) The unit of "flux" is fraction of the incoming solar radiation
924!        at the top of the atmosphere.  Therefore, fluxes should
925!        be equal to "flux" multiplied by the extra-terrestrial solar
926!        flux and the cosine of solar zenith angle.
927!    (2) pl(i,j,1) is the pressure at the top of the model, and
928!        pl(i,j,np+1) is the surface pressure.
929!    (3) the pressure levels ict and icb correspond approximately
930!        to 400 and 700 mb.
931!    (4) if overcast='true', the clear-sky flux, flc, is not computed.
932!       
933!**************************************************************************
934      implicit none
935!**************************************************************************
936
937!-----input parameters
938
939      integer m,n,ndim,np
940      integer ict(m,ndim),icb(m,ndim)
941      real pl(m,ndim,np+1),ta(m,ndim,np),wa(m,ndim,np),oa(m,ndim,np)
942      real cwc(m,ndim,np,2),taucld(m,ndim,np,2),reff(m,ndim,np,2), &
943             fcld(m,ndim,np)
944      real taual(m,ndim,np,11),ssaal(m,ndim,np,11),asyal(m,ndim,np,11)
945      real cosz(m,ndim),rsuvbm(m,ndim),rsuvdf(m,ndim), &
946             rsirbm(m,ndim),rsirdf(m,ndim)           
947      logical overcast,cldwater
948
949!-----output parameters
950
951      real flx(m,ndim,np+1),flc(m,ndim,np+1)
952      real flxu(m,ndim,np+1),flxd(m,ndim,np+1)
953      real fdiruv (m,ndim),fdifuv (m,ndim)
954      real fdirpar(m,ndim),fdifpar(m,ndim)
955      real fdirir (m,ndim),fdifir (m,ndim)
956
957!-----temporary array
958 
959      integer i,j,k
960      real cwp(m,n,np,2)
961      real dp(m,n,np),wh(m,n,np),oh(m,n,np),scal(m,n,np)
962      real swh(m,n,np+1),so2(m,n,np+1),df(m,n,np+1)
963      real sdf(m,n),sclr(m,n),csm(m,n),x
964 
965      do j= 1, n
966       do i= 1, m
967          if (pl(i,j,1) .eq. 0.0) then
968              pl(i,j,1)=1.0e-4
969          endif
970       enddo
971      enddo
972
973      do j= 1, n
974       do i= 1, m
975
976         swh(i,j,1)=0.
977         so2(i,j,1)=0.
978
979!-----csm is the effective secant of the solar zenith angle
980!     see equation (12) of Lacis and Hansen (1974, JAS)   
981 
982         csm(i,j)=35./sqrt(1224.*cosz(i,j)*cosz(i,j)+1.)
983
984       enddo
985      enddo
986
987      do k= 1, np
988       do j= 1, n
989         do i= 1, m
990
991!-----compute layer thickness and pressure-scaling function.
992!     indices for the surface level and surface layer
993!     are np+1 and np, respectively.
994 
995          dp(i,j,k)=pl(i,j,k+1)-pl(i,j,k)
996          scal(i,j,k)=dp(i,j,k)*(.5*(pl(i,j,k)+pl(i,j,k+1))/300.)**.8
997 
998!-----compute scaled water vapor amount, unit is g/cm**2
999!     note: the sign prior to the constant 0.00135 was incorrectly
1000!           set to negative in the previous version
1001
1002          wh(i,j,k)=1.02*wa(i,j,k)*scal(i,j,k)* &
1003                    (1.+0.00135*(ta(i,j,k)-240.)) +1.e-11
1004          swh(i,j,k+1)=swh(i,j,k)+wh(i,j,k)
1005
1006!-----compute ozone amount, unit is (cm-atm)stp
1007!     the number 466.7 is a conversion factor from g/cm**2 to (cm-atm)stp
1008 
1009          oh(i,j,k)=1.02*oa(i,j,k)*dp(i,j,k)*466.7 +1.e-11
1010
1011!-----compute layer cloud water amount (gm/m**2)
1012!     the index is 1 for ice crystals and 2 for liquid drops
1013
1014          cwp(i,j,k,1)=1.02*10000.*cwc(i,j,k,1)*dp(i,j,k)
1015          cwp(i,j,k,2)=1.02*10000.*cwc(i,j,k,2)*dp(i,j,k)
1016
1017        enddo
1018       enddo
1019      enddo
1020
1021!-----initialize fluxes for all-sky (flx), clear-sky (flc), and
1022!     flux reduction (df)
1023
1024      do k=1, np+1
1025       do j=1, n
1026        do i=1, m
1027          flx(i,j,k)=0.
1028          flc(i,j,k)=0.
1029          flxu(i,j,k)=0.
1030          flxd(i,j,k)=0.
1031          df(i,j,k)=0.
1032        enddo
1033       enddo
1034      enddo
1035
1036!-----compute solar uv and par fluxes
1037
1038      call soluv (m,n,ndim,np,oh,dp,overcast,cldwater,  &
1039                  cwp,taucld,reff,ict,icb,fcld,cosz,    &
1040                  taual,ssaal,asyal,csm,rsuvbm,rsuvdf,  &
1041                  flx,flc,flxu,flxd,fdiruv,fdifuv,fdirpar,fdifpar)
1042
1043!-----compute and update solar ir fluxes
1044
1045      call solir (m,n,ndim,np,wh,overcast,cldwater,     &
1046                  cwp,taucld,reff,ict,icb,fcld,cosz,    &
1047                  taual,ssaal,asyal,csm,rsirbm,rsirdf,  &
1048                  flx,flc,flxu,flxd,fdirir,fdifir)
1049
1050!-----compute scaled o2 amount, unit is (cm-atm)stp.
1051
1052      do k= 1, np
1053       do j= 1, n
1054        do i= 1, m
1055          so2(i,j,k+1)=so2(i,j,k)+165.22*scal(i,j,k)
1056        enddo
1057       enddo
1058      enddo
1059
1060!-----compute flux reduction due to oxygen following
1061!      chou (J. climate, 1990). The fraction 0.0287 is the
1062!      extraterrestrial solar flux in the o2 bands.
1063
1064       do k= 2, np+1
1065        do j= 1, n
1066         do i= 1, m
1067           x=so2(i,j,k)*csm(i,j)
1068           df(i,j,k)=df(i,j,k)+0.0287*(1.-exp(-0.00027*sqrt(x)))
1069         enddo
1070        enddo
1071       enddo         
1072
1073!-----compute scaled co2 amounts. unit is (cm-atm)stp.
1074
1075      do k= 1, np
1076       do j= 1, n
1077        do i= 1, m
1078         so2(i,j,k+1)=so2(i,j,k)+co2*789.*scal(i,j,k)+1.e-11
1079        enddo
1080       enddo
1081      enddo
1082
1083!-----compute and update flux reduction due to co2 following
1084!     chou (J. Climate, 1990)
1085
1086      call flxco2(m,n,np,so2,swh,csm,df)
1087
1088!-----adjust for the effect of o2 cnd co2 on clear-sky fluxes.
1089
1090      do k= 2, np+1
1091       do j= 1, n
1092        do i= 1, m
1093          flc(i,j,k)=flc(i,j,k)-df(i,j,k)
1094        enddo
1095       enddo
1096      enddo
1097
1098!-----adjust for the all-sky fluxes due to o2 and co2.  It is
1099!     assumed that o2 and co2 have no effects on solar radiation
1100!     below clouds.
1101
1102      do j=1,n
1103       do i=1,m
1104        sdf(i,j)=0.0
1105        sclr(i,j)=1.0
1106       enddo
1107      enddo
1108
1109      do k=1,np
1110       do j=1,n
1111        do i=1,m
1112
1113!-----sclr is the fraction of clear sky.
1114!     sdf is the flux reduction below clouds.
1115
1116         if(fcld(i,j,k).gt.0.01) then
1117          sdf(i,j)=sdf(i,j)+df(i,j,k)*sclr(i,j)*fcld(i,j,k)
1118          sclr(i,j)=sclr(i,j)*(1.-fcld(i,j,k))
1119         endif
1120          flx(i,j,k+1)=flx(i,j,k+1)-sdf(i,j)-df(i,j,k+1)*sclr(i,j)
1121          flxu(i,j,k+1)=flxu(i,j,k+1)-sdf(i,j)-df(i,j,k+1)*sclr(i,j)
1122          flxd(i,j,k+1)=flxd(i,j,k+1)-sdf(i,j)-df(i,j,k+1)*sclr(i,j)
1123
1124        enddo
1125       enddo
1126      enddo
1127
1128!-----adjustment for the direct downward ir flux.
1129
1130      do j= 1, n
1131       do i= 1, m
1132        flc(i,j,np+1)=flc(i,j,np+1)+df(i,j,np+1)*rsirbm(i,j)
1133        flx(i,j,np+1)=flx(i,j,np+1)+(sdf(i,j)+ &
1134                         df(i,j,np+1)*sclr(i,j))*rsirbm(i,j)
1135        flxu(i,j,np+1)=flxu(i,j,np+1)+(sdf(i,j)+ &
1136                         df(i,j,np+1)*sclr(i,j))*rsirbm(i,j)
1137        flxd(i,j,np+1)=flxd(i,j,np+1)+(sdf(i,j)+ &
1138                         df(i,j,np+1)*sclr(i,j))*rsirbm(i,j)
1139        fdirir(i,j)=fdirir(i,j)-(sdf(i,j)+df(i,j,np+1)*sclr(i,j))
1140       enddo
1141      enddo
1142
1143      end subroutine sorad
1144
1145!************************************************************************
1146
1147      subroutine soluv (m,n,ndim,np,oh,dp,overcast,cldwater,            &
1148                cwp,taucld,reff,ict,icb,fcld,cosz,                      &
1149                taual,ssaal,asyal,csm,rsuvbm,rsuvdf,                    &
1150                flx,flc,flxu,flxd,fdiruv,fdifuv,fdirpar,fdifpar)
1151
1152!************************************************************************
1153!  compute solar fluxes in the uv+par region. the spectrum is
1154!  grouped into 8 bands:
1155
1156!              Band     Micrometer
1157!
1158!       UV-C    1.     .175 - .225
1159!               2.     .225 - .245
1160!                      .260 - .280
1161!               3.     .245 - .260
1162!
1163!       UV-B    4.     .280 - .295
1164!               5.     .295 - .310
1165!               6.     .310 - .320
1166!     
1167!       UV-A    7.     .320 - .400
1168!     
1169!       PAR     8.     .400 - .700
1170!
1171!----- Input parameters:                            units      size
1172!
1173!  number of soundings in zonal direction (m)       n/d        1
1174!  number of soundings in meridional direction (n)  n/d        1
1175!  maximum number of soundings in                   n/d        1
1176!        meridional direction (ndim)
1177!  number of atmospheric layers (np)                n/d        1
1178!  layer ozone content (oh)                      (cm-atm)stp m*n*np
1179!  layer pressure thickness (dp)                    mb       m*n*np
1180!  option for scaling cloud optical thickness       n/d        1
1181!        overcast="true" if scaling is NOT required
1182!        overcast="fasle" if scaling is required
1183!  input option for cloud optical thickness         n/d        1
1184!        cldwater="true" if taucld is provided
1185!        cldwater="false" if cwp is provided
1186!  cloud water amount (cwp)                        gm/m**2   m*n*np*2
1187!        index 1 for ice particles
1188!        index 2 for liquid drops
1189!  cloud optical thickness (taucld)                 n/d     m*ndim*np*2
1190!       index 1 for ice paticles
1191!       index 2 for liquid particles
1192!  effective cloud-particle size (reff)          micrometer m*ndim*np*2
1193!       index 1 for ice paticles
1194!       index 2 for liquid particles
1195!  level indiex separating high and                 n/d      m*n
1196!       middle clouds (ict)
1197!  level indiex separating middle and               n/d      m*n
1198!       low clouds (icb)
1199!  cloud amount (fcld)                            fraction   m*ndim*np
1200!  cosine of solar zenith angle (cosz)              n/d      m*ndim
1201!  aerosol optical thickness (taual)                n/d    m*ndim*np*11
1202!  aerosol single-scattering albedo (ssaal)         n/d    m*ndim*np*11
1203!  aerosol asymmetry factor (asyal)                 n/d    m*ndim*np*11
1204!  cosecant of the solar zenith angle (csm)         n/d      m*n
1205!  uv+par surface albedo for beam                 fraction   m*ndim
1206!       radiation (rsuvbm)
1207!  uv+par surface albedo for diffuse              fraction   m*ndim
1208!       radiation (rsuvdf)
1209!
1210!---- temporary array
1211!
1212!  scaled cloud optical thickness                   n/d      m*n*np
1213!       for beam radiation (tauclb)
1214!  scaled cloud optical thickness                   n/d      m*n*np
1215!       for diffuse radiation  (tauclf)     
1216!
1217!----- output (updated) parameters:
1218!
1219!  all-sky net downward flux (flx)               fraction  m*ndim*(np+1)
1220!  clear-sky net downward flux (flc)             fraction  m*ndim*(np+1)
1221!  all-sky direct downward uv flux at
1222!       the surface (fdiruv)                     fraction    m*ndim
1223!  all-sky diffuse downward uv flux at
1224!       the surface (fdifuv)                     fraction    m*ndim
1225!  all-sky direct downward par flux at
1226!       the surface (fdirpar)                    fraction    m*ndim
1227!  all-sky diffuse downward par flux at
1228!       the surface (fdifpar)                    fraction    m*ndim
1229!
1230!***********************************************************************
1231      implicit none
1232!***********************************************************************
1233
1234!-----input parameters
1235
1236      integer m,n,ndim,np
1237      integer ict(m,ndim),icb(m,ndim)
1238      real taucld(m,ndim,np,2),reff(m,ndim,np,2),fcld(m,ndim,np)
1239      real cc(m,n,3),cosz(m,ndim)
1240      real cwp(m,n,np,2),oh(m,n,np),dp(m,n,np)
1241      real taual(m,ndim,np,11),ssaal(m,ndim,np,11),asyal(m,ndim,np,11)
1242      real rsuvbm(m,ndim),rsuvdf(m,ndim),csm(m,n)
1243      logical overcast,cldwater
1244
1245!-----output (updated) parameter
1246
1247      real flx(m,ndim,np+1),flc(m,ndim,np+1)
1248      real flxu(m,ndim,np+1),flxd(m,ndim,np+1)
1249      real fdiruv (m,ndim),fdifuv (m,ndim)
1250      real fdirpar(m,ndim),fdifpar(m,ndim)
1251
1252!-----static parameters
1253
1254      integer nband
1255      parameter (nband=8)
1256      real hk(nband),xk(nband),ry(nband)
1257      real aig(3),awg(3)
1258
1259!-----temporary array
1260
1261      integer i,j,k,ib
1262      real tauclb(m,n,np),tauclf(m,n,np),asycl(m,n,np)
1263      real taurs,tauoz,tausto,ssatau,asysto,tauto,ssato,asyto
1264      real taux,reff1,reff2,g1,g2
1265      real td(m,n,np+1,2),rr(m,n,np+1,2),tt(m,n,np+1,2), &
1266             rs(m,n,np+1,2),ts(m,n,np+1,2)
1267      real fall(m,n,np+1),fclr(m,n,np+1),fsdir(m,n),fsdif(m,n)
1268      real fallu(m,n,np+1),falld(m,n,np+1)
1269      real asyclt(m,n)
1270      real rr1t(m,n),tt1t(m,n),td1t(m,n),rs1t(m,n),ts1t(m,n)
1271      real rr2t(m,n),tt2t(m,n),td2t(m,n),rs2t(m,n),ts2t(m,n)
1272
1273!-----hk is the fractional extra-terrestrial solar flux in each
1274!     of the 8 bands.  the sum of hk is 0.47074.
1275
1276      data hk/.00057, .00367, .00083, .00417,  &
1277              .00600, .00556, .05913, .39081/
1278
1279!-----xk is the ozone absorption coefficient. unit: /(cm-atm)stp
1280
1281      data xk /30.47, 187.2,  301.9,   42.83, &
1282               7.09,  1.25,   0.0345,  0.0539/
1283
1284!-----ry is the extinction coefficient for Rayleigh scattering.
1285!     unit: /mb.
1286
1287      data ry /.00604, .00170, .00222, .00132, &
1288               .00107, .00091, .00055, .00012/
1289
1290!-----coefficients for computing the asymmetry factor of ice clouds
1291!     from asycl=aig(*,1)+aig(*,2)*reff+aig(*,3)*reff**2, independent
1292!     of spectral band.
1293
1294      data aig/.74625000,.00105410,-.00000264/
1295
1296!-----coefficients for computing the asymmetry factor of liquid
1297!     clouds from asycl=awg(*,1)+awg(*,2)*reff+awg(*,3)*reff**2,
1298!     independent of spectral band.
1299
1300      data awg/.82562000,.00529000,-.00014866/
1301
1302!-----initialize fdiruv, fdifuv, surface reflectances and transmittances.
1303!     cc is the maximum cloud cover in each of the three cloud groups.
1304           
1305      do j= 1, n
1306       do i= 1, m                   
1307         fdiruv(i,j)=0.0
1308         fdifuv(i,j)=0.0
1309         rr(i,j,np+1,1)=rsuvbm(i,j)
1310         rr(i,j,np+1,2)=rsuvbm(i,j)
1311         rs(i,j,np+1,1)=rsuvdf(i,j)
1312         rs(i,j,np+1,2)=rsuvdf(i,j)
1313         td(i,j,np+1,1)=0.0
1314         td(i,j,np+1,2)=0.0
1315         tt(i,j,np+1,1)=0.0
1316         tt(i,j,np+1,2)=0.0
1317         ts(i,j,np+1,1)=0.0
1318         ts(i,j,np+1,2)=0.0
1319         cc(i,j,1)=0.0
1320         cc(i,j,2)=0.0
1321         cc(i,j,3)=0.0
1322       enddo
1323      enddo
1324
1325
1326!-----compute cloud optical thickness
1327
1328      if (cldwater) then
1329
1330       do k= 1, np
1331        do j= 1, n
1332         do i= 1, m
1333          taucld(i,j,k,1)=cwp(i,j,k,1)*( 3.33e-4+2.52/reff(i,j,k,1))
1334          taucld(i,j,k,2)=cwp(i,j,k,2)*(-6.59e-3+1.65/reff(i,j,k,2))
1335         enddo
1336        enddo
1337       enddo
1338
1339      endif
1340
1341!-----options for scaling cloud optical thickness
1342
1343      if (overcast) then
1344
1345       do k= 1, np
1346        do j= 1, n
1347         do i= 1, m
1348          tauclb(i,j,k)=taucld(i,j,k,1)+taucld(i,j,k,2)
1349          tauclf(i,j,k)=tauclb(i,j,k)
1350         enddo
1351        enddo
1352       enddo
1353
1354       do k= 1, 3
1355        do j= 1, n
1356         do i= 1, m
1357           cc(i,j,k)=1.0
1358         enddo
1359        enddo
1360       enddo
1361
1362      else
1363
1364!-----scale cloud optical thickness in each layer from taucld (with
1365!     cloud amount fcld) to tauclb and tauclf (with cloud amount cc).
1366!     tauclb is the scaled optical thickness for beam radiation and
1367!     tauclf is for diffuse radiation.
1368
1369       call cldscale(m,n,ndim,np,cosz,fcld,taucld,ict,icb,  &
1370                    cc,tauclb,tauclf)
1371
1372      endif
1373
1374!-----compute cloud asymmetry factor for a mixture of
1375!     liquid and ice particles.  unit of reff is micrometers.
1376
1377      do k= 1, np
1378
1379       do j= 1, n
1380        do i= 1, m
1381
1382           asyclt(i,j)=1.0
1383
1384           taux=taucld(i,j,k,1)+taucld(i,j,k,2)
1385          if (taux.gt.0.05 .and. fcld(i,j,k).gt.0.01) then
1386
1387           reff1=min(reff(i,j,k,1),130.)
1388           reff2=min(reff(i,j,k,2),20.0)
1389
1390           g1=(aig(1)+(aig(2)+aig(3)*reff1)*reff1)*taucld(i,j,k,1)
1391           g2=(awg(1)+(awg(2)+awg(3)*reff2)*reff2)*taucld(i,j,k,2)
1392           asyclt(i,j)=(g1+g2)/taux
1393
1394          endif
1395
1396        enddo
1397       enddo
1398
1399       do j=1,n
1400        do i=1,m
1401           asycl(i,j,k)=asyclt(i,j)
1402        enddo
1403       enddo
1404
1405      enddo
1406
1407!-----integration over spectral bands
1408
1409      do 100 ib=1,nband
1410
1411       do 300 k= 1, np
1412
1413        do j= 1, n
1414         do i= 1, m
1415
1416!-----compute ozone and rayleigh optical thicknesses
1417
1418          taurs=ry(ib)*dp(i,j,k)
1419          tauoz=xk(ib)*oh(i,j,k)
1420 
1421!-----compute clear-sky optical thickness, single scattering albedo,
1422!     and asymmetry factor
1423
1424          tausto=taurs+tauoz+taual(i,j,k,ib)+1.0e-8
1425          ssatau=ssaal(i,j,k,ib)*taual(i,j,k,ib)+taurs
1426          asysto=asyal(i,j,k,ib)*ssaal(i,j,k,ib)*taual(i,j,k,ib)
1427
1428          tauto=tausto
1429          ssato=ssatau/tauto+1.0e-8
1430          ssato=min(ssato,0.999999)
1431          asyto=asysto/(ssato*tauto)
1432
1433!-----compute reflectance and transmittance for cloudless layers
1434
1435!-                 for direct incident radiation
1436
1437          call deledd (tauto,ssato,asyto,csm(i,j),  &
1438                       rr1t(i,j),tt1t(i,j),td1t(i,j))
1439
1440!-                 for diffuse incident radiation
1441
1442          call sagpol (tauto,ssato,asyto,rs1t(i,j),ts1t(i,j))
1443
1444!-----compute reflectance and transmittance for cloud layers
1445
1446         if (tauclb(i,j,k).lt.0.01 .or. fcld(i,j,k).lt.0.01) then
1447
1448          rr2t(i,j)=rr1t(i,j)
1449          tt2t(i,j)=tt1t(i,j)
1450          td2t(i,j)=td1t(i,j)
1451          rs2t(i,j)=rs1t(i,j)
1452          ts2t(i,j)=ts1t(i,j)
1453
1454         else
1455
1456!--                for direct incident radiation
1457
1458          tauto=tausto+tauclb(i,j,k)
1459          ssato=(ssatau+tauclb(i,j,k))/tauto+1.0e-8
1460          ssato=min(ssato,0.999999)
1461          asyto=(asysto+asycl(i,j,k)*tauclb(i,j,k))/(ssato*tauto)
1462
1463          call deledd (tauto,ssato,asyto,csm(i,j),  &
1464                       rr2t(i,j),tt2t(i,j),td2t(i,j))
1465
1466!--                for diffuse incident radiation
1467
1468          tauto=tausto+tauclf(i,j,k)
1469          ssato=(ssatau+tauclf(i,j,k))/tauto+1.0e-8
1470          ssato=min(ssato,0.999999)
1471          asyto=(asysto+asycl(i,j,k)*tauclf(i,j,k))/(ssato*tauto)
1472
1473          call sagpol (tauto,ssato,asyto,rs2t(i,j),ts2t(i,j))
1474
1475         endif
1476
1477        enddo
1478       enddo
1479
1480        do j=1,n
1481         do i=1,m
1482            rr(i,j,k,1)=rr1t(i,j)
1483         enddo
1484        enddo
1485        do j=1,n
1486         do i=1,m
1487            tt(i,j,k,1)=tt1t(i,j)
1488         enddo
1489        enddo
1490        do j=1,n
1491         do i=1,m
1492            td(i,j,k,1)=td1t(i,j)
1493         enddo
1494        enddo
1495        do j=1,n
1496         do i=1,m
1497            rs(i,j,k,1)=rs1t(i,j)
1498         enddo
1499        enddo
1500        do j=1,n
1501         do i=1,m
1502            ts(i,j,k,1)=ts1t(i,j)
1503         enddo
1504        enddo
1505
1506        do j=1,n
1507         do i=1,m
1508            rr(i,j,k,2)=rr2t(i,j)
1509         enddo
1510        enddo
1511        do j=1,n
1512         do i=1,m
1513            tt(i,j,k,2)=tt2t(i,j)
1514         enddo
1515        enddo
1516        do j=1,n
1517         do i=1,m
1518            td(i,j,k,2)=td2t(i,j)
1519         enddo
1520        enddo
1521        do j=1,n
1522         do i=1,m
1523            rs(i,j,k,2)=rs2t(i,j)
1524         enddo
1525        enddo
1526        do j=1,n
1527         do i=1,m
1528            ts(i,j,k,2)=ts2t(i,j)
1529         enddo
1530        enddo
1531
1532 300  continue
1533
1534!-----flux calculations
1535 
1536        call cldflx (m,n,np,ict,icb,overcast,cc,rr,tt,td,rs,ts, &
1537                     fclr,fall,fallu,falld,fsdir,fsdif)
1538
1539       do k= 1, np+1
1540        do j= 1, n
1541         do i= 1, m
1542          flx(i,j,k)=flx(i,j,k)+fall(i,j,k)*hk(ib)
1543          flxu(i,j,k)=flxu(i,j,k)+fallu(i,j,k)*hk(ib)
1544          flxd(i,j,k)=flxd(i,j,k)+falld(i,j,k)*hk(ib)
1545         enddo
1546        enddo
1547        do j= 1, n
1548         do i= 1, m
1549          flc(i,j,k)=flc(i,j,k)+fclr(i,j,k)*hk(ib)
1550         enddo
1551        enddo
1552       enddo
1553
1554!-----compute downward surface fluxes in the UV and par regions
1555
1556       if(ib.lt.8) then
1557         do j=1,n
1558          do i=1,m
1559           fdiruv(i,j)=fdiruv(i,j)+fsdir(i,j)*hk(ib)
1560           fdifuv(i,j)=fdifuv(i,j)+fsdif(i,j)*hk(ib)
1561         enddo
1562        enddo
1563       else
1564         do j=1,n
1565          do i=1,m
1566           fdirpar(i,j)=fsdir(i,j)*hk(ib)
1567           fdifpar(i,j)=fsdif(i,j)*hk(ib)
1568         enddo
1569        enddo
1570       endif
1571
1572 100  continue
1573
1574      end subroutine soluv
1575
1576!************************************************************************
1577
1578      subroutine solir (m,n,ndim,np,wh,overcast,cldwater,               &
1579                        cwp,taucld,reff,ict,icb,fcld,cosz,              &
1580                        taual,ssaal,asyal,csm,rsirbm,rsirdf,            &
1581                        flx,flc,flxu,flxd,fdirir,fdifir)
1582
1583!************************************************************************
1584!  compute solar flux in the infrared region. The spectrum is divided
1585!   into three bands:
1586!
1587!          band   wavenumber(/cm)  wavelength (micron)
1588!          1( 9)    14300-8200         0.70-1.22
1589!          2(10)     8200-4400         1.22-2.27
1590!          3(11)     4400-1000         2.27-10.0
1591!
1592!----- Input parameters:                            units      size
1593!
1594!  number of soundings in zonal direction (m)       n/d        1
1595!  number of soundings in meridional direction (n)  n/d        1
1596!  maximum number of soundings in                   n/d        1
1597!         meridional direction (ndim)
1598!  number of atmospheric layers (np)                n/d        1
1599!  layer scaled-water vapor content (wh)          gm/cm^2    m*n*np
1600!  option for scaling cloud optical thickness       n/d        1
1601!        overcast="true" if scaling is NOT required
1602!        overcast="fasle" if scaling is required
1603!  input option for cloud optical thickness         n/d        1
1604!        cldwater="true" if taucld is provided
1605!        cldwater="false" if cwp is provided
1606!  cloud water concentration (cwp)                gm/m**2    m*n*np*2
1607!        index 1 for ice particles
1608!        index 2 for liquid drops
1609!  cloud optical thickness (taucld)                 n/d      m*ndim*np*2
1610!        index 1 for ice paticles
1611!  effective cloud-particle size (reff)           micrometer m*ndim*np*2
1612!        index 1 for ice paticles
1613!        index 2 for liquid particles
1614!  level index separating high and                  n/d      m*n
1615!        middle clouds (ict)
1616!  level index separating middle and                n/d      m*n
1617!        low clouds (icb)
1618!  cloud amount (fcld)                            fraction   m*ndim*np
1619!  aerosol optical thickness (taual)                n/d      m*ndim*np*11
1620!  aerosol single-scattering albedo (ssaal)         n/d      m*ndim*np*11
1621!  aerosol asymmetry factor (asyal)                 n/d      m*ndim*np*11
1622!  cosecant of the solar zenith angle (csm)         n/d      m*n
1623!  near ir surface albedo for beam                fraction   m*ndim
1624!        radiation (rsirbm)
1625!  near ir surface albedo for diffuse             fraction   m*ndim
1626!        radiation (rsirdf)
1627!
1628!---- temporary array
1629!
1630!  scaled cloud optical thickness                   n/d      m*n*np
1631!          for beam radiation (tauclb)
1632!  scaled cloud optical thickness                   n/d      m*n*np
1633!          for diffuse radiation  (tauclf)     
1634!
1635!----- output (updated) parameters:
1636!
1637!  all-sky flux (downward-upward) (flx)           fraction   m*ndim*(np+1)
1638!  clear-sky flux (downward-upward) (flc)         fraction   m*ndim*(np+1)
1639!  all-sky direct downward ir flux at
1640!          the surface (fdirir)                    fraction   m*ndim
1641!  all-sky diffuse downward ir flux at
1642!          the surface (fdifir)                    fraction   m*ndim
1643!
1644!**********************************************************************
1645      implicit none
1646!**********************************************************************
1647
1648!-----input parameters
1649
1650      integer m,n,ndim,np
1651      integer ict(m,ndim),icb(m,ndim)
1652      real cwp(m,n,np,2),taucld(m,ndim,np,2),reff(m,ndim,np,2)
1653      real fcld(m,ndim,np),cc(m,n,3),cosz(m,ndim)
1654      real rsirbm(m,ndim),rsirdf(m,ndim)
1655      real taual(m,ndim,np,11),ssaal(m,ndim,np,11),asyal(m,ndim,np,11)
1656      real wh(m,n,np),csm(m,n)
1657      logical overcast,cldwater
1658
1659!-----output (updated) parameters
1660
1661      real flx(m,ndim,np+1),flc(m,ndim,np+1)
1662      real flxu(m,ndim,np+1),flxd(m,ndim,np+1)
1663      real fdirir(m,ndim),fdifir(m,ndim)
1664
1665!-----static parameters
1666
1667      integer nk,nband
1668      parameter (nk=10,nband=3)
1669      real xk(nk),hk(nband,nk),aib(nband,2),awb(nband,2)
1670      real aia(nband,3),awa(nband,3),aig(nband,3),awg(nband,3)
1671
1672!-----temporary array
1673
1674      integer ib,iv,ik,i,j,k
1675      real tauclb(m,n,np),tauclf(m,n,np)
1676      real ssacl(m,n,np),asycl(m,n,np)
1677      real rr(m,n,np+1,2),tt(m,n,np+1,2),td(m,n,np+1,2), &
1678             rs(m,n,np+1,2),ts(m,n,np+1,2)
1679      real fall(m,n,np+1),fclr(m,n,np+1)
1680      real fallu(m,n,np+1),falld(m,n,np+1)
1681      real fsdir(m,n),fsdif(m,n)
1682
1683      real tauwv,tausto,ssatau,asysto,tauto,ssato,asyto
1684      real taux,reff1,reff2,w1,w2,g1,g2
1685      real ssaclt(m,n),asyclt(m,n)
1686      real rr1t(m,n),tt1t(m,n),td1t(m,n),rs1t(m,n),ts1t(m,n)
1687      real rr2t(m,n),tt2t(m,n),td2t(m,n),rs2t(m,n),ts2t(m,n)
1688
1689!-----water vapor absorption coefficient for 10 k-intervals.
1690!     unit: cm^2/gm
1691
1692      data xk/  &
1693        0.0010, 0.0133, 0.0422, 0.1334, 0.4217, &
1694        1.334,  5.623,  31.62,  177.8,  1000.0/ 
1695
1696!-----water vapor k-distribution function,
1697!     the sum of hk is 0.52926. unit: fraction
1698
1699      data hk/  &
1700       .20673,.08236,.01074,  .03497,.01157,.00360, &
1701       .03011,.01133,.00411,  .02260,.01143,.00421, &
1702       .01336,.01240,.00389,  .00696,.01258,.00326, &
1703       .00441,.01381,.00499,  .00115,.00650,.00465, &
1704       .00026,.00244,.00245,  .00000,.00094,.00145/
1705
1706!-----coefficients for computing the extinction coefficient of
1707!     ice clouds from b=aib(*,1)+aib(*,2)/reff
1708
1709      data aib/ &
1710        .000333, .000333, .000333, &
1711           2.52,    2.52,    2.52/
1712
1713!-----coefficients for computing the extinction coefficient of
1714!     water clouds from b=awb(*,1)+awb(*,2)/reff
1715
1716      data awb/ &
1717        -0.0101, -0.0166, -0.0339, &
1718           1.72,    1.85,    2.16/
1719
1720
1721!-----coefficients for computing the single scattering albedo of
1722!     ice clouds from ssa=1-(aia(*,1)+aia(*,2)*reff+aia(*,3)*reff**2)
1723
1724      data aia/ &
1725       -.00000260, .00215346, .08938331, &
1726        .00000746, .00073709, .00299387, &
1727        .00000000,-.00000134,-.00001038/
1728
1729!-----coefficients for computing the single scattering albedo of
1730!     liquid clouds from ssa=1-(awa(*,1)+awa(*,2)*reff+awa(*,3)*reff**2)
1731
1732      data awa/ &
1733        .00000007,-.00019934, .01209318, &
1734        .00000845, .00088757, .01784739, &
1735       -.00000004,-.00000650,-.00036910/
1736
1737!-----coefficients for computing the asymmetry factor of ice clouds
1738!     from asycl=aig(*,1)+aig(*,2)*reff+aig(*,3)*reff**2
1739
1740      data aig/ &
1741        .74935228, .76098937, .84090400, &
1742        .00119715, .00141864, .00126222, &
1743       -.00000367,-.00000396,-.00000385/
1744
1745!-----coefficients for computing the asymmetry factor of liquid clouds
1746!     from asycl=awg(*,1)+awg(*,2)*reff+awg(*,3)*reff**2
1747
1748      data awg/ &
1749        .79375035, .74513197, .83530748, &
1750        .00832441, .01370071, .00257181, &
1751       -.00023263,-.00038203, .00005519/
1752
1753!-----initialize surface fluxes, reflectances, and transmittances.
1754!     cc is the maximum cloud cover in each of the three cloud groups.
1755
1756      do j= 1, n
1757       do i= 1, m
1758         fdirir(i,j)=0.0
1759         fdifir(i,j)=0.0
1760         rr(i,j,np+1,1)=rsirbm(i,j)
1761         rr(i,j,np+1,2)=rsirbm(i,j)
1762         rs(i,j,np+1,1)=rsirdf(i,j)
1763         rs(i,j,np+1,2)=rsirdf(i,j)
1764         td(i,j,np+1,1)=0.0
1765         td(i,j,np+1,2)=0.0
1766         tt(i,j,np+1,1)=0.0
1767         tt(i,j,np+1,2)=0.0
1768         ts(i,j,np+1,1)=0.0
1769         ts(i,j,np+1,2)=0.0
1770         cc(i,j,1)=0.0
1771         cc(i,j,2)=0.0
1772         cc(i,j,3)=0.0
1773       enddo
1774      enddo
1775
1776!-----integration over spectral bands
1777
1778      do 100 ib=1,nband
1779
1780       iv=ib+8
1781
1782!-----compute cloud optical thickness
1783
1784      if (cldwater) then
1785
1786       do k= 1, np
1787        do j= 1, n
1788         do i= 1, m
1789          taucld(i,j,k,1)=cwp(i,j,k,1)*(aib(ib,1) &
1790                          +aib(ib,2)/reff(i,j,k,1))
1791          taucld(i,j,k,2)=cwp(i,j,k,2)*(awb(ib,1) &
1792                          +awb(ib,2)/reff(i,j,k,2))
1793         enddo
1794        enddo
1795       enddo
1796
1797      endif
1798
1799!-----options for scaling cloud optical thickness
1800
1801      if (overcast) then
1802
1803       do k= 1, np
1804        do j= 1, n
1805         do i= 1, m
1806          tauclb(i,j,k)=taucld(i,j,k,1)+taucld(i,j,k,2)
1807          tauclf(i,j,k)=tauclb(i,j,k)
1808         enddo
1809        enddo
1810       enddo
1811
1812       do k= 1, 3
1813        do j= 1, n
1814         do i= 1, m
1815           cc(i,j,k)=1.0
1816         enddo
1817        enddo
1818       enddo
1819
1820      else
1821
1822!-----scale cloud optical thickness in each layer from taucld (with
1823!     cloud amount fcld) to tauclb and tauclf (with cloud amount cc).
1824!     tauclb is the scaled optical thickness for beam radiation and
1825!     tauclf is for diffuse radiation.
1826
1827       call cldscale(m,n,ndim,np,cosz,fcld,taucld,ict,icb, &
1828                    cc,tauclb,tauclf)
1829
1830      endif
1831
1832!-----compute cloud single scattering albedo and asymmetry factor
1833!     for a mixture of ice and liquid particles.
1834
1835       do k= 1, np
1836
1837        do j= 1, n
1838         do i= 1, m
1839
1840           ssaclt(i,j)=1.0
1841           asyclt(i,j)=1.0
1842
1843           taux=taucld(i,j,k,1)+taucld(i,j,k,2)
1844          if (taux.gt.0.05 .and. fcld(i,j,k).gt.0.01) then
1845
1846           reff1=min(reff(i,j,k,1),130.)
1847           reff2=min(reff(i,j,k,2),20.0)
1848
1849           w1=(1.-(aia(ib,1)+(aia(ib,2)+ &
1850               aia(ib,3)*reff1)*reff1))*taucld(i,j,k,1)
1851           w2=(1.-(awa(ib,1)+(awa(ib,2)+ &
1852               awa(ib,3)*reff2)*reff2))*taucld(i,j,k,2)
1853           ssaclt(i,j)=(w1+w2)/taux
1854
1855           g1=(aig(ib,1)+(aig(ib,2)+aig(ib,3)*reff1)*reff1)*w1
1856           g2=(awg(ib,1)+(awg(ib,2)+awg(ib,3)*reff2)*reff2)*w2
1857           asyclt(i,j)=(g1+g2)/(w1+w2)
1858
1859          endif
1860
1861         enddo
1862        enddo
1863
1864        do j=1,n
1865         do i=1,m
1866            ssacl(i,j,k)=ssaclt(i,j)
1867         enddo
1868        enddo
1869        do j=1,n
1870         do i=1,m
1871            asycl(i,j,k)=asyclt(i,j)
1872         enddo
1873        enddo
1874
1875       enddo
1876
1877!-----integration over the k-distribution function
1878
1879         do 200 ik=1,nk
1880
1881          do 300 k= 1, np
1882
1883           do j= 1, n
1884            do i= 1, m
1885
1886             tauwv=xk(ik)*wh(i,j,k)
1887 
1888!-----compute clear-sky optical thickness, single scattering albedo,
1889!     and asymmetry factor.
1890 
1891             tausto=tauwv+taual(i,j,k,iv)+1.0e-8
1892             ssatau=ssaal(i,j,k,iv)*taual(i,j,k,iv)
1893             asysto=asyal(i,j,k,iv)*ssaal(i,j,k,iv)*taual(i,j,k,iv)
1894 
1895!-----compute reflectance and transmittance for cloudless layers
1896
1897             tauto=tausto
1898             ssato=ssatau/tauto+1.0e-8
1899
1900            if (ssato .gt. 0.001) then
1901
1902             ssato=min(ssato,0.999999)
1903             asyto=asysto/(ssato*tauto)
1904
1905!-                 for direct incident radiation
1906
1907             call deledd (tauto,ssato,asyto,csm(i,j),  &
1908                          rr1t(i,j),tt1t(i,j),td1t(i,j))
1909
1910!-                 for diffuse incident radiation
1911
1912             call sagpol (tauto,ssato,asyto,rs1t(i,j),ts1t(i,j))
1913
1914            else
1915
1916             td1t(i,j)=exp(-tauto*csm(i,j))
1917             ts1t(i,j)=exp(-1.66*tauto)
1918             tt1t(i,j)=0.0
1919             rr1t(i,j)=0.0
1920             rs1t(i,j)=0.0
1921
1922            endif
1923
1924!-----compute reflectance and transmittance for cloud layers
1925
1926            if (tauclb(i,j,k).lt.0.01 .or. fcld(i,j,k).lt.0.01) then
1927
1928             rr2t(i,j)=rr1t(i,j)
1929             tt2t(i,j)=tt1t(i,j)
1930             td2t(i,j)=td1t(i,j)
1931             rs2t(i,j)=rs1t(i,j)
1932             ts2t(i,j)=ts1t(i,j)
1933
1934            else
1935
1936!-                 for direct incident radiation
1937
1938             tauto=tausto+tauclb(i,j,k)
1939             ssato=(ssatau+ssacl(i,j,k)*tauclb(i,j,k))/tauto+1.0e-8
1940             ssato=min(ssato,0.999999)
1941             asyto=(asysto+asycl(i,j,k)*ssacl(i,j,k)*tauclb(i,j,k))/ &
1942                   (ssato*tauto)
1943
1944             call deledd (tauto,ssato,asyto,csm(i,j),  &
1945                          rr2t(i,j),tt2t(i,j),td2t(i,j))
1946
1947!-                 for diffuse incident radiation
1948
1949             tauto=tausto+tauclf(i,j,k)
1950             ssato=(ssatau+ssacl(i,j,k)*tauclf(i,j,k))/tauto+1.0e-8
1951             ssato=min(ssato,0.999999)
1952             asyto=(asysto+asycl(i,j,k)*ssacl(i,j,k)*tauclf(i,j,k))/ &
1953                   (ssato*tauto)
1954
1955             call sagpol (tauto,ssato,asyto,rs2t(i,j),ts2t(i,j))
1956
1957            endif
1958
1959           enddo
1960          enddo
1961
1962           do j=1,n
1963            do i=1,m
1964               rr(i,j,k,1)=rr1t(i,j)
1965            enddo
1966           enddo
1967           do j=1,n
1968            do i=1,m
1969               tt(i,j,k,1)=tt1t(i,j)
1970            enddo
1971           enddo
1972           do j=1,n
1973            do i=1,m
1974               td(i,j,k,1)=td1t(i,j)
1975            enddo
1976           enddo
1977           do j=1,n
1978            do i=1,m
1979               rs(i,j,k,1)=rs1t(i,j)
1980            enddo
1981           enddo
1982           do j=1,n
1983            do i=1,m
1984               ts(i,j,k,1)=ts1t(i,j)
1985            enddo
1986           enddo
1987 
1988           do j=1,n
1989            do i=1,m
1990               rr(i,j,k,2)=rr2t(i,j)
1991            enddo
1992           enddo
1993           do j=1,n
1994            do i=1,m
1995               tt(i,j,k,2)=tt2t(i,j)
1996            enddo
1997           enddo
1998           do j=1,n
1999            do i=1,m
2000               td(i,j,k,2)=td2t(i,j)
2001            enddo
2002           enddo
2003           do j=1,n
2004            do i=1,m
2005               rs(i,j,k,2)=rs2t(i,j)
2006            enddo
2007           enddo
2008           do j=1,n
2009            do i=1,m
2010               ts(i,j,k,2)=ts2t(i,j)
2011            enddo
2012           enddo
2013
2014 300  continue
2015
2016!-----flux calculations
2017
2018        call cldflx (m,n,np,ict,icb,overcast,cc,rr,tt,td,rs,ts, &
2019                     fclr,fall,fallu,falld,fsdir,fsdif)
2020
2021       do k= 1, np+1
2022        do j= 1, n
2023         do i= 1, m
2024          flx(i,j,k) = flx(i,j,k)+fall(i,j,k)*hk(ib,ik)
2025          flxu(i,j,k) = flxu(i,j,k)+fallu(i,j,k)*hk(ib,ik)
2026          flxd(i,j,k) = flxd(i,j,k)+falld(i,j,k)*hk(ib,ik)
2027         enddo
2028        enddo
2029        do j= 1, n
2030         do i= 1, m
2031          flc(i,j,k) = flc(i,j,k)+fclr(i,j,k)*hk(ib,ik)
2032         enddo
2033        enddo
2034       enddo
2035
2036!-----compute downward surface fluxes in the ir region
2037
2038       do j= 1, n
2039        do i= 1, m
2040          fdirir(i,j) = fdirir(i,j)+fsdir(i,j)*hk(ib,ik)
2041          fdifir(i,j) = fdifir(i,j)+fsdif(i,j)*hk(ib,ik)
2042        enddo
2043       enddo
2044
2045  200 continue
2046  100 continue
2047 
2048      end subroutine solir
2049
2050!********************************************************************
2051
2052      subroutine cldscale (m,n,ndim,np,cosz,fcld,taucld,ict,icb,    &
2053                           cc,tauclb,tauclf)
2054
2055!********************************************************************
2056!
2057!   This subroutine computes the high, middle, and
2058!    low cloud amounts and scales the cloud optical thickness.
2059!
2060!   To simplify calculations in a cloudy atmosphere, clouds are
2061!    grouped into high, middle and low clouds separated by the levels
2062!    ict and icb (level 1 is the top of the model atmosphere).
2063!
2064!   Within each of the three groups, clouds are assumed maximally
2065!    overlapped, and the cloud cover (cc) of a group is the maximum
2066!    cloud cover of all the layers in the group.  The optical thickness
2067!    (taucld) of a given layer is then scaled to new values (tauclb and
2068!    tauclf) so that the layer reflectance corresponding to the cloud
2069!    cover cc is the same as the original reflectance with optical
2070!    thickness taucld and cloud cover fcld.
2071!
2072!---input parameters
2073!
2074!    number of grid intervals in zonal direction (m)
2075!    number of grid intervals in meridional direction (n)
2076!    maximum number of grid intervals in meridional direction (ndim)
2077!    number of atmospheric layers (np)
2078!    cosine of the solar zenith angle (cosz)
2079!    fractional cloud cover (fcld)
2080!    cloud optical thickness (taucld)
2081!    index separating high and middle clouds (ict)
2082!    index separating middle and low clouds (icb)
2083!
2084!---output parameters
2085!
2086!    fractional cover of high, middle, and low clouds (cc)
2087!    scaled cloud optical thickness for beam radiation (tauclb)
2088!    scaled cloud optical thickness for diffuse radiation (tauclf)
2089!
2090!********************************************************************
2091      implicit none
2092!********************************************************************
2093
2094!-----input parameters
2095
2096      integer m,n,ndim,np
2097      integer ict(m,ndim),icb(m,ndim)
2098      real cosz(m,ndim),fcld(m,ndim,np),taucld(m,ndim,np,2)
2099
2100!-----output parameters
2101
2102      real cc(m,n,3),tauclb(m,n,np),tauclf(m,n,np)
2103
2104!-----temporary variables
2105
2106      integer i,j,k,im,it,ia,kk
2107      real  fm,ft,fa,xai,taux
2108
2109!-----pre-computed table
2110
2111      integer   nm,nt,na
2112      parameter (nm=11,nt=9,na=11)
2113      real  dm,dt,da,t1,caib(nm,nt,na),caif(nt,na)
2114      parameter (dm=0.1,dt=0.30103,da=0.1,t1=-0.9031)
2115
2116!-----include the pre-computed table of mcai for scaling the cloud optical
2117!     thickness under the assumption that clouds are maximally overlapped
2118!
2119!     caib is for scaling the cloud optical thickness for direct radiation
2120!     caif is for scaling the cloud optical thickness for diffuse radiation
2121
2122
2123      data ((caib(1,i,j),j=1,11),i=1,9)/  &
2124       .000,0.068,0.140,0.216,0.298,0.385,0.481,0.586,0.705,0.840,1.000, &
2125       .000,0.052,0.106,0.166,0.230,0.302,0.383,0.478,0.595,0.752,1.000, &
2126       .000,0.038,0.078,0.120,0.166,0.218,0.276,0.346,0.438,0.582,1.000, &
2127       .000,0.030,0.060,0.092,0.126,0.164,0.206,0.255,0.322,0.442,1.000, &
2128       .000,0.025,0.051,0.078,0.106,0.136,0.170,0.209,0.266,0.462,1.000, &
2129       .000,0.023,0.046,0.070,0.095,0.122,0.150,0.187,0.278,0.577,1.000, &
2130       .000,0.022,0.043,0.066,0.089,0.114,0.141,0.187,0.354,0.603,1.000, &
2131       .000,0.021,0.042,0.063,0.086,0.108,0.135,0.214,0.349,0.565,1.000, &
2132       .000,0.021,0.041,0.062,0.083,0.105,0.134,0.202,0.302,0.479,1.000/
2133      data ((caib(2,i,j),j=1,11),i=1,9)/ &
2134       .000,0.088,0.179,0.272,0.367,0.465,0.566,0.669,0.776,0.886,1.000, &
2135       .000,0.079,0.161,0.247,0.337,0.431,0.531,0.637,0.749,0.870,1.000, &
2136       .000,0.065,0.134,0.207,0.286,0.372,0.466,0.572,0.692,0.831,1.000, &
2137       .000,0.049,0.102,0.158,0.221,0.290,0.370,0.465,0.583,0.745,1.000, &
2138       .000,0.037,0.076,0.118,0.165,0.217,0.278,0.354,0.459,0.638,1.000, &
2139       .000,0.030,0.061,0.094,0.130,0.171,0.221,0.286,0.398,0.631,1.000, &
2140       .000,0.026,0.052,0.081,0.111,0.146,0.189,0.259,0.407,0.643,1.000, &
2141       .000,0.023,0.047,0.072,0.098,0.129,0.170,0.250,0.387,0.598,1.000, &
2142       .000,0.022,0.044,0.066,0.090,0.118,0.156,0.224,0.328,0.508,1.000/
2143      data ((caib(3,i,j),j=1,11),i=1,9)/ &
2144       .000,0.094,0.189,0.285,0.383,0.482,0.582,0.685,0.788,0.894,1.000, &
2145       .000,0.088,0.178,0.271,0.366,0.465,0.565,0.669,0.776,0.886,1.000, &
2146       .000,0.079,0.161,0.247,0.337,0.431,0.531,0.637,0.750,0.870,1.000, &
2147       .000,0.066,0.134,0.209,0.289,0.375,0.470,0.577,0.697,0.835,1.000, &
2148       .000,0.050,0.104,0.163,0.227,0.300,0.383,0.483,0.606,0.770,1.000, &
2149       .000,0.038,0.080,0.125,0.175,0.233,0.302,0.391,0.518,0.710,1.000, &
2150       .000,0.031,0.064,0.100,0.141,0.188,0.249,0.336,0.476,0.689,1.000, &
2151       .000,0.026,0.054,0.084,0.118,0.158,0.213,0.298,0.433,0.638,1.000, &
2152       .000,0.023,0.048,0.074,0.102,0.136,0.182,0.254,0.360,0.542,1.000/
2153      data ((caib(4,i,j),j=1,11),i=1,9)/ &
2154       .000,0.096,0.193,0.290,0.389,0.488,0.589,0.690,0.792,0.896,1.000, &
2155       .000,0.092,0.186,0.281,0.378,0.477,0.578,0.680,0.785,0.891,1.000, &
2156       .000,0.086,0.174,0.264,0.358,0.455,0.556,0.660,0.769,0.882,1.000, &
2157       .000,0.074,0.153,0.235,0.323,0.416,0.514,0.622,0.737,0.862,1.000, &
2158       .000,0.061,0.126,0.195,0.271,0.355,0.449,0.555,0.678,0.823,1.000, &
2159       .000,0.047,0.098,0.153,0.215,0.286,0.370,0.471,0.600,0.770,1.000, &
2160       .000,0.037,0.077,0.120,0.170,0.230,0.303,0.401,0.537,0.729,1.000, &
2161       .000,0.030,0.062,0.098,0.138,0.187,0.252,0.343,0.476,0.673,1.000, &
2162       .000,0.026,0.053,0.082,0.114,0.154,0.207,0.282,0.391,0.574,1.000/
2163      data ((caib(5,i,j),j=1,11),i=1,9)/ &
2164       .000,0.097,0.194,0.293,0.392,0.492,0.592,0.693,0.794,0.897,1.000, &
2165       .000,0.094,0.190,0.286,0.384,0.483,0.584,0.686,0.789,0.894,1.000, &
2166       .000,0.090,0.181,0.274,0.370,0.468,0.569,0.672,0.778,0.887,1.000, &
2167       .000,0.081,0.165,0.252,0.343,0.439,0.539,0.645,0.757,0.874,1.000, &
2168       .000,0.069,0.142,0.218,0.302,0.392,0.490,0.598,0.717,0.850,1.000, &
2169       .000,0.054,0.114,0.178,0.250,0.330,0.422,0.529,0.656,0.810,1.000, &
2170       .000,0.042,0.090,0.141,0.200,0.269,0.351,0.455,0.589,0.764,1.000, &
2171       .000,0.034,0.070,0.112,0.159,0.217,0.289,0.384,0.515,0.703,1.000, &
2172       .000,0.028,0.058,0.090,0.128,0.174,0.231,0.309,0.420,0.602,1.000/
2173      data ((caib(6,i,j),j=1,11),i=1,9)/ &
2174       .000,0.098,0.196,0.295,0.394,0.494,0.594,0.695,0.796,0.898,1.000, &
2175       .000,0.096,0.193,0.290,0.389,0.488,0.588,0.690,0.792,0.895,1.000, &
2176       .000,0.092,0.186,0.281,0.378,0.477,0.577,0.680,0.784,0.891,1.000, &
2177       .000,0.086,0.174,0.264,0.358,0.455,0.556,0.661,0.769,0.882,1.000, &
2178       .000,0.075,0.154,0.237,0.325,0.419,0.518,0.626,0.741,0.865,1.000, &
2179       .000,0.062,0.129,0.201,0.279,0.366,0.462,0.571,0.694,0.836,1.000, &
2180       .000,0.049,0.102,0.162,0.229,0.305,0.394,0.501,0.631,0.793,1.000, &
2181       .000,0.038,0.080,0.127,0.182,0.245,0.323,0.422,0.550,0.730,1.000, &
2182       .000,0.030,0.064,0.100,0.142,0.192,0.254,0.334,0.448,0.627,1.000/
2183      data ((caib(7,i,j),j=1,11),i=1,9)/ &
2184       .000,0.098,0.198,0.296,0.396,0.496,0.596,0.696,0.797,0.898,1.000, &
2185       .000,0.097,0.194,0.293,0.392,0.491,0.591,0.693,0.794,0.897,1.000, &
2186       .000,0.094,0.190,0.286,0.384,0.483,0.583,0.686,0.789,0.894,1.000, &
2187       .000,0.089,0.180,0.274,0.369,0.467,0.568,0.672,0.778,0.887,1.000, &
2188       .000,0.081,0.165,0.252,0.344,0.440,0.541,0.646,0.758,0.875,1.000, &
2189       .000,0.069,0.142,0.221,0.306,0.397,0.496,0.604,0.722,0.854,1.000, &
2190       .000,0.056,0.116,0.182,0.256,0.338,0.432,0.540,0.666,0.816,1.000, &
2191       .000,0.043,0.090,0.143,0.203,0.273,0.355,0.455,0.583,0.754,1.000, &
2192       .000,0.034,0.070,0.111,0.157,0.210,0.276,0.359,0.474,0.650,1.000/
2193      data ((caib(8,i,j),j=1,11),i=1,9)/ &
2194       .000,0.099,0.198,0.298,0.398,0.497,0.598,0.698,0.798,0.899,1.000, &
2195       .000,0.098,0.196,0.295,0.394,0.494,0.594,0.695,0.796,0.898,1.000, &
2196       .000,0.096,0.193,0.290,0.390,0.489,0.589,0.690,0.793,0.896,1.000, &
2197       .000,0.093,0.186,0.282,0.379,0.478,0.578,0.681,0.786,0.892,1.000, &
2198       .000,0.086,0.175,0.266,0.361,0.458,0.558,0.663,0.771,0.883,1.000, &
2199       .000,0.076,0.156,0.240,0.330,0.423,0.523,0.630,0.744,0.867,1.000, &
2200       .000,0.063,0.130,0.203,0.282,0.369,0.465,0.572,0.694,0.834,1.000, &
2201       .000,0.049,0.102,0.161,0.226,0.299,0.385,0.486,0.611,0.774,1.000, &
2202       .000,0.038,0.078,0.122,0.172,0.229,0.297,0.382,0.498,0.672,1.000/
2203      data ((caib(9,i,j),j=1,11),i=1,9)/ &
2204       .000,0.099,0.199,0.298,0.398,0.498,0.598,0.699,0.799,0.899,1.000, &
2205       .000,0.099,0.198,0.298,0.398,0.497,0.598,0.698,0.798,0.899,1.000, &
2206       .000,0.098,0.196,0.295,0.394,0.494,0.594,0.695,0.796,0.898,1.000, &
2207       .000,0.096,0.193,0.290,0.389,0.488,0.588,0.690,0.792,0.895,1.000, &
2208       .000,0.092,0.185,0.280,0.376,0.474,0.575,0.678,0.782,0.890,1.000, &
2209       .000,0.084,0.170,0.259,0.351,0.447,0.547,0.652,0.762,0.878,1.000, &
2210       .000,0.071,0.146,0.224,0.308,0.398,0.494,0.601,0.718,0.850,1.000, &
2211       .000,0.056,0.114,0.178,0.248,0.325,0.412,0.514,0.638,0.793,1.000, &
2212       .000,0.042,0.086,0.134,0.186,0.246,0.318,0.405,0.521,0.691,1.000/
2213      data ((caib(10,i,j),j=1,11),i=1,9)/ &
2214       .000,0.100,0.200,0.300,0.400,0.500,0.600,0.700,0.800,0.900,1.000, &
2215       .000,0.100,0.200,0.300,0.400,0.500,0.600,0.700,0.800,0.900,1.000, &
2216       .000,0.100,0.200,0.300,0.400,0.500,0.600,0.700,0.800,0.900,1.000, &
2217       .000,0.100,0.199,0.298,0.398,0.498,0.598,0.698,0.798,0.899,1.000, &
2218       .000,0.098,0.196,0.294,0.392,0.491,0.590,0.691,0.793,0.896,1.000, &
2219       .000,0.092,0.185,0.278,0.374,0.470,0.570,0.671,0.777,0.886,1.000, &
2220       .000,0.081,0.162,0.246,0.333,0.424,0.521,0.625,0.738,0.862,1.000, &
2221       .000,0.063,0.128,0.196,0.270,0.349,0.438,0.540,0.661,0.809,1.000, &
2222       .000,0.046,0.094,0.146,0.202,0.264,0.337,0.426,0.542,0.710,1.000/
2223      data ((caib(11,i,j),j=1,11),i=1,9)/ &
2224       .000,0.101,0.202,0.302,0.402,0.502,0.602,0.702,0.802,0.901,1.000, &
2225       .000,0.102,0.202,0.303,0.404,0.504,0.604,0.703,0.802,0.902,1.000, &
2226       .000,0.102,0.205,0.306,0.406,0.506,0.606,0.706,0.804,0.902,1.000, &
2227       .000,0.104,0.207,0.309,0.410,0.510,0.609,0.707,0.805,0.902,1.000, &
2228       .000,0.106,0.208,0.309,0.409,0.508,0.606,0.705,0.803,0.902,1.000, &
2229       .000,0.102,0.202,0.298,0.395,0.493,0.590,0.690,0.790,0.894,1.000, &
2230       .000,0.091,0.179,0.267,0.357,0.449,0.545,0.647,0.755,0.872,1.000, &
2231       .000,0.073,0.142,0.214,0.290,0.372,0.462,0.563,0.681,0.822,1.000, &
2232       .000,0.053,0.104,0.158,0.217,0.281,0.356,0.446,0.562,0.726,1.000/
2233      data ((caif(i,j),j=1,11),i=1,9)/ &
2234       .000,0.099,0.198,0.297,0.397,0.496,0.597,0.697,0.798,0.899,1.000, &
2235       .000,0.098,0.196,0.294,0.394,0.494,0.594,0.694,0.796,0.898,1.000, &
2236       .000,0.096,0.192,0.290,0.388,0.487,0.587,0.689,0.792,0.895,1.000, &
2237       .000,0.092,0.185,0.280,0.376,0.476,0.576,0.678,0.783,0.890,1.000, &
2238       .000,0.085,0.173,0.263,0.357,0.454,0.555,0.659,0.768,0.881,1.000, &
2239       .000,0.076,0.154,0.237,0.324,0.418,0.517,0.624,0.738,0.864,1.000, &
2240       .000,0.063,0.131,0.203,0.281,0.366,0.461,0.567,0.688,0.830,1.000, &
2241       .000,0.052,0.107,0.166,0.232,0.305,0.389,0.488,0.610,0.770,1.000, &
2242       .000,0.043,0.088,0.136,0.189,0.248,0.317,0.400,0.510,0.675,1.000/
2243
2244!-----clouds within each of the high, middle, and low clouds are assumed
2245!     to be maximally overlapped, and the cloud cover (cc) for a group
2246!     (high, middle, or low) is the maximum cloud cover of all the layers
2247!     within a group
2248
2249      do j=1,n
2250       do i=1,m
2251         cc(i,j,1)=0.0
2252         cc(i,j,2)=0.0
2253         cc(i,j,3)=0.0
2254       enddo
2255      enddo
2256      do j=1,n
2257       do i=1,m
2258        do k=1,ict(i,j)-1
2259          cc(i,j,1)=max(cc(i,j,1),fcld(i,j,k))
2260        enddo
2261       enddo
2262      enddo
2263
2264      do j=1,n
2265       do i=1,m
2266        do k=ict(i,j),icb(i,j)-1
2267          cc(i,j,2)=max(cc(i,j,2),fcld(i,j,k))
2268        enddo
2269       enddo
2270      enddo
2271
2272      do j=1,n
2273       do i=1,m
2274        do k=icb(i,j),np
2275          cc(i,j,3)=max(cc(i,j,3),fcld(i,j,k))
2276        enddo
2277       enddo
2278      enddo
2279
2280!-----scale the cloud optical thickness.
2281!     taucld(i,j,k,1) is the optical thickness for ice particles, and
2282!     taucld(i,j,k,2) is the optical thickness for liquid particles.
2283     
2284      do j=1,n
2285       do i=1,m
2286
2287        do k=1,np
2288
2289         if(k.lt.ict(i,j)) then
2290            kk=1
2291         elseif(k.ge.ict(i,j) .and. k.lt.icb(i,j)) then
2292            kk=2
2293         else
2294            kk=3
2295         endif
2296
2297         tauclb(i,j,k) = 0.0
2298         tauclf(i,j,k) = 0.0
2299
2300         taux=taucld(i,j,k,1)+taucld(i,j,k,2)
2301         if (taux.gt.0.05 .and. fcld(i,j,k).gt.0.01) then
2302
2303!-----normalize cloud cover
2304
2305           fa=fcld(i,j,k)/cc(i,j,kk)
2306
2307!-----table look-up
2308
2309           taux=min(taux,32.)
2310
2311           fm=cosz(i,j)/dm
2312           ft=(log10(taux)-t1)/dt
2313           fa=fa/da
2314 
2315           im=int(fm+1.5)
2316           it=int(ft+1.5)
2317           ia=int(fa+1.5)
2318 
2319           im=max(im,2)
2320           it=max(it,2)
2321           ia=max(ia,2)
2322     
2323           im=min(im,nm-1)
2324           it=min(it,nt-1)
2325           ia=min(ia,na-1)
2326
2327           fm=fm-float(im-1)
2328           ft=ft-float(it-1)
2329           fa=fa-float(ia-1)
2330
2331!-----scale cloud optical thickness for beam radiation.
2332!     the scaling factor, xai, is a function of the solar zenith
2333!     angle, optical thickness, and cloud cover.
2334 
2335           xai=    (-caib(im-1,it,ia)*(1.-fm)+ &
2336            caib(im+1,it,ia)*(1.+fm))*fm*.5+caib(im,it,ia)*(1.-fm*fm)
2337         
2338           xai=xai+(-caib(im,it-1,ia)*(1.-ft)+ &
2339            caib(im,it+1,ia)*(1.+ft))*ft*.5+caib(im,it,ia)*(1.-ft*ft)
2340
2341           xai=xai+(-caib(im,it,ia-1)*(1.-fa)+ &
2342           caib(im,it,ia+1)*(1.+fa))*fa*.5+caib(im,it,ia)*(1.-fa*fa)
2343
2344           xai= xai-2.*caib(im,it,ia)
2345           xai=max(xai,0.0)
2346     
2347           tauclb(i,j,k) = taux*xai
2348
2349!-----scale cloud optical thickness for diffuse radiation.
2350!     the scaling factor, xai, is a function of the cloud optical
2351!     thickness and cover but not the solar zenith angle.
2352
2353           xai=    (-caif(it-1,ia)*(1.-ft)+ &
2354            caif(it+1,ia)*(1.+ft))*ft*.5+caif(it,ia)*(1.-ft*ft)
2355
2356           xai=xai+(-caif(it,ia-1)*(1.-fa)+ &
2357            caif(it,ia+1)*(1.+fa))*fa*.5+caif(it,ia)*(1.-fa*fa)
2358
2359           xai= xai-caif(it,ia)
2360           xai=max(xai,0.0)
2361     
2362           tauclf(i,j,k) = taux*xai
2363
2364         endif
2365
2366        enddo
2367       enddo
2368      enddo
2369
2370      end subroutine cldscale
2371
2372!*********************************************************************
2373
2374      subroutine deledd(tau,ssc,g0,csm,rr,tt,td)
2375
2376!*********************************************************************
2377!
2378!-----uses the delta-eddington approximation to compute the
2379!     bulk scattering properties of a single layer
2380!     coded following King and Harshvardhan (JAS, 1986)
2381!
2382!  inputs:
2383!
2384!     tau: the effective optical thickness
2385!     ssc: the effective single scattering albedo
2386!     g0:  the effective asymmetry factor
2387!     csm: the effective secant of the zenith angle
2388!
2389!  outputs:
2390!
2391!     rr: the layer reflection of the direct beam
2392!     tt: the layer diffuse transmission of the direct beam
2393!     td: the layer direct transmission of the direct beam
2394!
2395!*********************************************************************
2396      implicit none
2397!*********************************************************************
2398
2399      real zero,one,two,three,four,fourth,seven,thresh
2400      parameter (one =1., three=3.)
2401      parameter (two =2., seven=7.)
2402      parameter (four=4., fourth=.25)
2403      parameter (zero=0., thresh=1.e-8)
2404
2405!-----input parameters
2406      real tau,ssc,g0,csm
2407
2408!-----output parameters
2409      real rr,tt,td
2410
2411!-----temporary parameters
2412
2413      real zth,ff,xx,taup,sscp,gp,gm1,gm2,gm3,akk,alf1,alf2, &
2414           all,bll,st7,st8,cll,dll,fll,ell,st1,st2,st3,st4
2415 
2416!---------------------------------------------------------------------
2417
2418                zth = one / csm
2419 
2420!  delta-eddington scaling of single scattering albedo,
2421!  optical thickness, and asymmetry factor,
2422!  K & H eqs(27-29)
2423
2424                ff  = g0*g0
2425                xx  = one-ff*ssc
2426                taup= tau*xx
2427                sscp= ssc*(one-ff)/xx
2428                gp  = g0/(one+g0)
2429 
2430!  gamma1, gamma2, and gamma3. see table 2 and eq(26) K & H
2431!  ssc and gp are the d-s single scattering
2432!  albedo and asymmetry factor.
2433
2434                xx  =  three*gp
2435                gm1 =  (seven - sscp*(four+xx))*fourth
2436                gm2 = -(one   - sscp*(four-xx))*fourth
2437 
2438!  akk is k as defined in eq(25) of K & H
2439 
2440                akk = sqrt((gm1+gm2)*(gm1-gm2))
2441 
2442                xx  = akk * zth
2443                st7 = one - xx
2444                st8 = one + xx
2445                st3 = st7 * st8
2446
2447                if (abs(st3) .lt. thresh) then
2448                    zth = zth + 0.001
2449                    xx  = akk * zth
2450                    st7 = one - xx
2451                    st8 = one + xx
2452                    st3 = st7 * st8
2453                endif
2454
2455!  extinction of the direct beam transmission
2456 
2457                td  = exp(-taup/zth)
2458
2459!  alf1 and alf2 are alpha1 and alpha2 from eqs (23) & (24) of K & H
2460 
2461                gm3  = (two - zth*three*gp)*fourth
2462                xx   = gm1 - gm2
2463                alf1 = gm1 - gm3 * xx
2464                alf2 = gm2 + gm3 * xx
2465 
2466!  all is last term in eq(21) of K & H
2467!  bll is last term in eq(22) of K & H
2468 
2469                xx  = akk * two
2470                all = (gm3 - alf2 * zth    )*xx*td
2471                bll = (one - gm3 + alf1*zth)*xx
2472 
2473                xx  = akk * gm3
2474                cll = (alf2 + xx) * st7
2475                dll = (alf2 - xx) * st8
2476 
2477                xx  = akk * (one-gm3)
2478                fll = (alf1 + xx) * st8
2479                ell = (alf1 - xx) * st7
2480 
2481                st2 = exp(-akk*taup)
2482                st4 = st2 * st2
2483 
2484                st1 =  sscp / ((akk+gm1 + (akk-gm1)*st4) * st3)
2485 
2486!  rr is r-hat of eq(21) of K & H
2487!  tt is diffuse part of t-hat of eq(22) of K & H
2488 
2489                rr =   ( cll-dll*st4    -all*st2)*st1
2490                tt = - ((fll-ell*st4)*td-bll*st2)*st1
2491 
2492                rr = max(rr,zero)
2493                tt = max(tt,zero)
2494
2495      end subroutine deledd
2496
2497!*********************************************************************
2498
2499      subroutine sagpol(tau,ssc,g0,rll,tll)
2500
2501!*********************************************************************
2502!-----transmittance (tll) and reflectance (rll) of diffuse radiation
2503!     follows Sagan and Pollock (JGR, 1967).
2504!     also, eq.(31) of Lacis and Hansen (JAS, 1974).
2505!
2506!-----input parameters:
2507!
2508!      tau: the effective optical thickness
2509!      ssc: the effective single scattering albedo
2510!      g0:  the effective asymmetry factor
2511!
2512!-----output parameters:
2513!
2514!      rll: the layer reflection of diffuse radiation
2515!      tll: the layer transmission of diffuse radiation
2516!
2517!*********************************************************************
2518      implicit none
2519!*********************************************************************
2520
2521      real one,three,four
2522      parameter (one=1., three=3., four=4.)
2523
2524!-----output parameters:
2525
2526      real tau,ssc,g0
2527
2528!-----output parameters:
2529
2530      real rll,tll
2531
2532!-----temporary arrays
2533
2534      real xx,uuu,ttt,emt,up1,um1,st1
2535
2536             xx  = one-ssc*g0
2537             uuu = sqrt( xx/(one-ssc))
2538             ttt = sqrt( xx*(one-ssc)*three )*tau
2539             emt = exp(-ttt)
2540             up1 = uuu + one
2541             um1 = uuu - one
2542             xx  = um1*emt
2543             st1 = one / ((up1+xx) * (up1-xx))
2544             rll = up1*um1*(one-emt*emt)*st1
2545             tll = uuu*four*emt         *st1
2546
2547      end subroutine sagpol
2548
2549!*******************************************************************
2550
2551      subroutine cldflx (m,n,np,ict,icb,overcast,cc,rr,tt,td,rs,ts,&
2552                 fclr,fall,fallu,falld,fsdir,fsdif)
2553
2554!*******************************************************************
2555!  compute upward and downward fluxes using a two-stream adding method
2556!  following equations (3)-(5) of Chou (1992, JAS).
2557!
2558!  clouds are grouped into high, middle, and low clouds which are
2559!  assumed randomly overlapped. It involves eight sets of calculations.
2560!  In each set of calculations, each atmospheric layer is homogeneous,
2561!  either totally filled with clouds or without clouds.
2562
2563!  input parameters:
2564!
2565!     m:   number of soundings in zonal direction
2566!     n:   number of soundings in meridional direction
2567!     np:  number of atmospheric layers
2568!     ict: the level separating high and middle clouds
2569!     icb: the level separating middle and low clouds
2570!     cc:  effective cloud covers for high, middle and low clouds
2571!     tt:  diffuse transmission of a layer illuminated by beam radiation
2572!     td:  direct beam tranmssion
2573!     ts:  transmission of a layer illuminated by diffuse radiation
2574!     rr:  reflection of a layer illuminated by beam radiation
2575!     rs:  reflection of a layer illuminated by diffuse radiation
2576!
2577!  output parameters:
2578!
2579!     fclr:  clear-sky flux (downward minus upward)
2580!     fall:  all-sky flux (downward minus upward)
2581!     fsdir: surface direct downward flux
2582!     fsdif: surface diffuse downward flux
2583!
2584!*********************************************************************c
2585      implicit none
2586!*********************************************************************c
2587
2588!-----input parameters
2589
2590      integer m,n,np
2591      integer ict(m,n),icb(m,n)
2592
2593      real rr(m,n,np+1,2),tt(m,n,np+1,2),td(m,n,np+1,2)
2594      real rs(m,n,np+1,2),ts(m,n,np+1,2)
2595      real cc(m,n,3)
2596      logical overcast
2597
2598!-----temporary array
2599
2600      integer i,j,k,ih,im,is,itm
2601      real rra(m,n,np+1,2,2),tta(m,n,np+1,2,2),tda(m,n,np+1,2,2)
2602      real rsa(m,n,np+1,2,2),rxa(m,n,np+1,2,2)
2603      real ch(m,n),cm(m,n),ct(m,n),flxdn(m,n,np+1)
2604      real flxdnu(m,n,np+1),flxdnd(m,n,np+1)
2605      real fdndir(m,n),fdndif(m,n),fupdif
2606      real denm,xx
2607
2608!-----output parameters
2609
2610      real fclr(m,n,np+1),fall(m,n,np+1)
2611      real fallu(m,n,np+1),falld(m,n,np+1)
2612      real fsdir(m,n),fsdif(m,n)
2613
2614!-----initialize all-sky flux (fall) and surface downward fluxes
2615
2616      do k=1,np+1
2617       do j=1,n
2618        do i=1,m
2619           fclr(i,j,k)=0.0
2620           fall(i,j,k)=0.0
2621           fallu(i,j,k)=0.0
2622           falld(i,j,k)=0.0
2623        enddo
2624       enddo
2625      enddo
2626
2627       do j=1,n
2628        do i=1,m
2629           fsdir(i,j)=0.0
2630           fsdif(i,j)=0.0
2631        enddo
2632       enddo
2633
2634!-----compute transmittances and reflectances for a composite of
2635!     layers. layers are added one at a time, going down from the top.
2636!     tda is the composite transmittance illuminated by beam radiation
2637!     tta is the composite diffuse transmittance illuminated by
2638!         beam radiation
2639!     rsa is the composite reflectance illuminated from below
2640!         by diffuse radiation
2641!     tta and rsa are computed from eqs. (4b) and (3b) of Chou
2642
2643      itm=1
2644
2645!-----if overcas.=.true., set itm=2, and only one set of fluxes is computed
2646
2647      if (overcast) itm=2
2648
2649!-----for high clouds. indices 1 and 2 denote clear and cloudy
2650!     situations, respectively.
2651
2652      do 10 ih=itm,2
2653
2654       do j= 1, n
2655        do i= 1, m
2656          tda(i,j,1,ih,1)=td(i,j,1,ih)
2657          tta(i,j,1,ih,1)=tt(i,j,1,ih)
2658          rsa(i,j,1,ih,1)=rs(i,j,1,ih)
2659          tda(i,j,1,ih,2)=td(i,j,1,ih)
2660          tta(i,j,1,ih,2)=tt(i,j,1,ih)
2661          rsa(i,j,1,ih,2)=rs(i,j,1,ih)
2662        enddo
2663       enddo
2664
2665       do j= 1, n
2666        do i= 1, m
2667         do k= 2, ict(i,j)-1
2668          denm = ts(i,j,k,ih)/( 1.-rsa(i,j,k-1,ih,1)*rs(i,j,k,ih))
2669          tda(i,j,k,ih,1)= tda(i,j,k-1,ih,1)*td(i,j,k,ih)
2670          tta(i,j,k,ih,1)= tda(i,j,k-1,ih,1)*tt(i,j,k,ih) &
2671                        +(tda(i,j,k-1,ih,1)*rr(i,j,k,ih)  &
2672                        *rsa(i,j,k-1,ih,1)+tta(i,j,k-1,ih,1))*denm
2673          rsa(i,j,k,ih,1)= rs(i,j,k,ih)+ts(i,j,k,ih) &
2674                        *rsa(i,j,k-1,ih,1)*denm
2675          tda(i,j,k,ih,2)= tda(i,j,k,ih,1)
2676          tta(i,j,k,ih,2)= tta(i,j,k,ih,1)
2677          rsa(i,j,k,ih,2)= rsa(i,j,k,ih,1)
2678         enddo
2679        enddo
2680       enddo
2681
2682!-----for middle clouds
2683
2684      do 10 im=itm,2
2685
2686      do j= 1, n
2687       do i= 1, m
2688        do k= ict(i,j), icb(i,j)-1
2689          denm = ts(i,j,k,im)/( 1.-rsa(i,j,k-1,ih,im)*rs(i,j,k,im))
2690          tda(i,j,k,ih,im)= tda(i,j,k-1,ih,im)*td(i,j,k,im)
2691          tta(i,j,k,ih,im)= tda(i,j,k-1,ih,im)*tt(i,j,k,im) &
2692                        +(tda(i,j,k-1,ih,im)*rr(i,j,k,im)   &
2693                        *rsa(i,j,k-1,ih,im)+tta(i,j,k-1,ih,im))*denm
2694          rsa(i,j,k,ih,im)= rs(i,j,k,im)+ts(i,j,k,im)  &
2695                        *rsa(i,j,k-1,ih,im)*denm
2696         enddo
2697        enddo
2698       enddo
2699
2700  10  continue
2701
2702!-----layers are added one at a time, going up from the surface.
2703!     rra is the composite reflectance illuminated by beam radiation
2704!     rxa is the composite reflectance illuminated from above
2705!         by diffuse radiation
2706!     rra and rxa are computed from eqs. (4a) and (3a) of Chou
2707 
2708!-----for the low clouds
2709
2710      do 20 is=itm,2
2711
2712       do j= 1, n
2713        do i= 1, m
2714         rra(i,j,np+1,1,is)=rr(i,j,np+1,is)
2715         rxa(i,j,np+1,1,is)=rs(i,j,np+1,is)
2716         rra(i,j,np+1,2,is)=rr(i,j,np+1,is)
2717         rxa(i,j,np+1,2,is)=rs(i,j,np+1,is)
2718        enddo
2719       enddo
2720
2721       do j= 1, n
2722        do i= 1, m
2723         do k=np,icb(i,j),-1
2724          denm=ts(i,j,k,is)/( 1.-rs(i,j,k,is)*rxa(i,j,k+1,1,is) )
2725          rra(i,j,k,1,is)=rr(i,j,k,is)+(td(i,j,k,is) &
2726              *rra(i,j,k+1,1,is)+tt(i,j,k,is)*rxa(i,j,k+1,1,is))*denm
2727          rxa(i,j,k,1,is)= rs(i,j,k,is)+ts(i,j,k,is) &
2728              *rxa(i,j,k+1,1,is)*denm
2729          rra(i,j,k,2,is)=rra(i,j,k,1,is)
2730          rxa(i,j,k,2,is)=rxa(i,j,k,1,is)
2731         enddo
2732        enddo
2733       enddo
2734
2735!-----for middle clouds
2736
2737      do 20 im=itm,2
2738
2739       do j= 1, n
2740        do i= 1, m
2741         do k= icb(i,j)-1,ict(i,j),-1
2742          denm=ts(i,j,k,im)/( 1.-rs(i,j,k,im)*rxa(i,j,k+1,im,is) )
2743          rra(i,j,k,im,is)= rr(i,j,k,im)+(td(i,j,k,im)  &
2744              *rra(i,j,k+1,im,is)+tt(i,j,k,im)*rxa(i,j,k+1,im,is))*denm
2745          rxa(i,j,k,im,is)= rs(i,j,k,im)+ts(i,j,k,im)   &
2746              *rxa(i,j,k+1,im,is)*denm
2747         enddo
2748        enddo
2749       enddo
2750
2751  20  continue
2752
2753!-----integration over eight sky situations.
2754!     ih, im, is denotes high, middle and low cloud groups.
2755
2756      do 100 ih=itm,2
2757
2758!-----clear portion
2759
2760         if(ih.eq.1) then
2761           do j=1,n
2762            do i=1,m
2763             ch(i,j)=1.0-cc(i,j,1)
2764            enddo
2765           enddo
2766
2767          else
2768
2769!-----cloudy portion
2770
2771           do j=1,n
2772            do i=1,m
2773             ch(i,j)=cc(i,j,1)
2774            enddo
2775           enddo
2776
2777          endif
2778
2779      do 100 im=itm,2
2780
2781!-----clear portion
2782
2783         if(im.eq.1) then
2784
2785           do j=1,n
2786            do i=1,m
2787              cm(i,j)=ch(i,j)*(1.0-cc(i,j,2))
2788            enddo
2789           enddo
2790
2791         else
2792
2793!-----cloudy portion
2794
2795           do j=1,n
2796            do i=1,m
2797              cm(i,j)=ch(i,j)*cc(i,j,2)
2798            enddo
2799           enddo
2800
2801         endif
2802
2803      do 100 is=itm,2
2804
2805!-----clear portion
2806
2807         if(is.eq.1) then
2808
2809           do j=1,n
2810            do i=1,m
2811             ct(i,j)=cm(i,j)*(1.0-cc(i,j,3))
2812            enddo
2813           enddo
2814
2815         else
2816
2817!-----cloudy portion
2818
2819           do j=1,n
2820            do i=1,m
2821             ct(i,j)=cm(i,j)*cc(i,j,3)
2822            enddo
2823           enddo
2824
2825         endif
2826
2827!-----add one layer at a time, going down.
2828
2829       do j= 1, n
2830        do i= 1, m
2831         do k= icb(i,j), np
2832          denm = ts(i,j,k,is)/( 1.-rsa(i,j,k-1,ih,im)*rs(i,j,k,is) )
2833          tda(i,j,k,ih,im)= tda(i,j,k-1,ih,im)*td(i,j,k,is)
2834          tta(i,j,k,ih,im)=  tda(i,j,k-1,ih,im)*tt(i,j,k,is) &
2835               +(tda(i,j,k-1,ih,im)*rr(i,j,k,is) &
2836               *rsa(i,j,k-1,ih,im)+tta(i,j,k-1,ih,im))*denm
2837          rsa(i,j,k,ih,im)= rs(i,j,k,is)+ts(i,j,k,is) &
2838               *rsa(i,j,k-1,ih,im)*denm
2839         enddo
2840        enddo
2841       enddo
2842
2843!-----add one layer at a time, going up.
2844
2845       do j= 1, n
2846        do i= 1, m
2847         do k= ict(i,j)-1,1,-1
2848          denm =ts(i,j,k,ih)/(1.-rs(i,j,k,ih)*rxa(i,j,k+1,im,is))
2849          rra(i,j,k,im,is)= rr(i,j,k,ih)+(td(i,j,k,ih)  &
2850              *rra(i,j,k+1,im,is)+tt(i,j,k,ih)*rxa(i,j,k+1,im,is))*denm
2851          rxa(i,j,k,im,is)= rs(i,j,k,ih)+ts(i,j,k,ih)   &
2852              *rxa(i,j,k+1,im,is)*denm
2853         enddo
2854        enddo
2855       enddo
2856
2857!-----compute fluxes following eq (5) of Chou (1992)
2858 
2859!     fdndir is the direct  downward flux
2860!     fdndif is the diffuse downward flux
2861!     fupdif is the diffuse upward flux
2862
2863      do k=2,np+1
2864       do j=1, n
2865        do i=1, m
2866         denm= 1./(1.- rxa(i,j,k,im,is)*rsa(i,j,k-1,ih,im))
2867         fdndir(i,j)= tda(i,j,k-1,ih,im)
2868         xx = tda(i,j,k-1,ih,im)*rra(i,j,k,im,is)
2869         fdndif(i,j)= (xx*rsa(i,j,k-1,ih,im)+tta(i,j,k-1,ih,im))*denm
2870         fupdif= (xx+tta(i,j,k-1,ih,im)*rxa(i,j,k,im,is))*denm
2871         flxdn(i,j,k)=fdndir(i,j)+fdndif(i,j)-fupdif
2872         flxdnu(i,j,k)=-fupdif
2873         flxdnd(i,j,k)=fdndir(i,j)+fdndif(i,j)
2874        enddo
2875       enddo
2876      enddo
2877
2878       do j=1, n
2879        do i=1, m
2880         flxdn(i,j,1)=1.0-rra(i,j,1,im,is)
2881         flxdnu(i,j,1)=-rra(i,j,1,im,is)
2882         flxdnd(i,j,1)=1.0
2883        enddo
2884       enddo
2885
2886!-----summation of fluxes over all (eight) sky situations.
2887
2888       do k=1,np+1
2889        do j=1,n
2890         do i=1,m
2891           if(ih.eq.1 .and. im.eq.1 .and. is.eq.1) then
2892             fclr(i,j,k)=flxdn(i,j,k)
2893           endif
2894             fall(i,j,k)=fall(i,j,k)+flxdn(i,j,k)*ct(i,j)
2895             fallu(i,j,k)=fallu(i,j,k)+flxdnu(i,j,k)*ct(i,j)
2896             falld(i,j,k)=falld(i,j,k)+flxdnd(i,j,k)*ct(i,j)
2897         enddo
2898        enddo
2899       enddo
2900
2901        do j=1,n
2902         do i=1,m
2903            fsdir(i,j)=fsdir(i,j)+fdndir(i,j)*ct(i,j)
2904            fsdif(i,j)=fsdif(i,j)+fdndif(i,j)*ct(i,j)
2905         enddo
2906        enddo
2907
2908  100 continue
2909
2910      end subroutine cldflx
2911
2912!*****************************************************************
2913
2914      subroutine flxco2(m,n,np,swc,swh,csm,df)
2915
2916!*****************************************************************
2917
2918!-----compute the reduction of clear-sky downward solar flux
2919!     due to co2 absorption.
2920
2921      implicit none
2922
2923!-----input parameters
2924
2925      integer m,n,np
2926      real csm(m,n),swc(m,n,np+1),swh(m,n,np+1),cah(22,19)
2927
2928!-----output (undated) parameter
2929
2930      real df(m,n,np+1)
2931
2932!-----temporary array
2933
2934      integer i,j,k,ic,iw
2935      real xx,clog,wlog,dc,dw,x1,x2,y2
2936
2937!********************************************************************
2938!-----include co2 look-up table
2939
2940      data ((cah(i,j),i=1,22),j= 1, 5)/ &                                     
2941       0.9923, 0.9922, 0.9921, 0.9920, 0.9916, 0.9910, 0.9899, 0.9882, &     
2942       0.9856, 0.9818, 0.9761, 0.9678, 0.9558, 0.9395, 0.9188, 0.8945, &     
2943       0.8675, 0.8376, 0.8029, 0.7621, 0.7154, 0.6647, 0.9876, 0.9876, &     
2944       0.9875, 0.9873, 0.9870, 0.9864, 0.9854, 0.9837, 0.9811, 0.9773, &     
2945       0.9718, 0.9636, 0.9518, 0.9358, 0.9153, 0.8913, 0.8647, 0.8350, &     
2946       0.8005, 0.7599, 0.7133, 0.6627, 0.9808, 0.9807, 0.9806, 0.9805, &     
2947       0.9802, 0.9796, 0.9786, 0.9769, 0.9744, 0.9707, 0.9653, 0.9573, &     
2948       0.9459, 0.9302, 0.9102, 0.8866, 0.8604, 0.8311, 0.7969, 0.7565, &     
2949       0.7101, 0.6596, 0.9708, 0.9708, 0.9707, 0.9705, 0.9702, 0.9697, &     
2950       0.9687, 0.9671, 0.9647, 0.9612, 0.9560, 0.9483, 0.9372, 0.9221, &     
2951       0.9027, 0.8798, 0.8542, 0.8253, 0.7916, 0.7515, 0.7054, 0.6551, &     
2952       0.9568, 0.9568, 0.9567, 0.9565, 0.9562, 0.9557, 0.9548, 0.9533, &     
2953       0.9510, 0.9477, 0.9428, 0.9355, 0.9250, 0.9106, 0.8921, 0.8700, &     
2954       0.8452, 0.8171, 0.7839, 0.7443, 0.6986, 0.6486/                       
2955 
2956      data ((cah(i,j),i=1,22),j= 6,10)/  &                                   
2957       0.9377, 0.9377, 0.9376, 0.9375, 0.9372, 0.9367, 0.9359, 0.9345, &     
2958       0.9324, 0.9294, 0.9248, 0.9181, 0.9083, 0.8948, 0.8774, 0.8565, &     
2959       0.8328, 0.8055, 0.7731, 0.7342, 0.6890, 0.6395, 0.9126, 0.9126, &     
2960       0.9125, 0.9124, 0.9121, 0.9117, 0.9110, 0.9098, 0.9079, 0.9052, &     
2961       0.9012, 0.8951, 0.8862, 0.8739, 0.8579, 0.8385, 0.8161, 0.7900, &     
2962       0.7585, 0.7205, 0.6760, 0.6270, 0.8809, 0.8809, 0.8808, 0.8807, &     
2963       0.8805, 0.8802, 0.8796, 0.8786, 0.8770, 0.8747, 0.8712, 0.8659, &     
2964       0.8582, 0.8473, 0.8329, 0.8153, 0.7945, 0.7697, 0.7394, 0.7024, &     
2965       0.6588, 0.6105, 0.8427, 0.8427, 0.8427, 0.8426, 0.8424, 0.8422, &     
2966       0.8417, 0.8409, 0.8397, 0.8378, 0.8350, 0.8306, 0.8241, 0.8148, &     
2967       0.8023, 0.7866, 0.7676, 0.7444, 0.7154, 0.6796, 0.6370, 0.5897, &     
2968       0.7990, 0.7990, 0.7990, 0.7989, 0.7988, 0.7987, 0.7983, 0.7978, &     
2969       0.7969, 0.7955, 0.7933, 0.7899, 0.7846, 0.7769, 0.7664, 0.7528, &     
2970       0.7357, 0.7141, 0.6866, 0.6520, 0.6108, 0.5646/                       
2971 
2972      data ((cah(i,j),i=1,22),j=11,15)/  &                                   
2973       0.7515, 0.7515, 0.7515, 0.7515, 0.7514, 0.7513, 0.7511, 0.7507, &     
2974       0.7501, 0.7491, 0.7476, 0.7450, 0.7409, 0.7347, 0.7261, 0.7144, &     
2975       0.6992, 0.6793, 0.6533, 0.6203, 0.5805, 0.5357, 0.7020, 0.7020, &     
2976       0.7020, 0.7019, 0.7019, 0.7018, 0.7017, 0.7015, 0.7011, 0.7005, &     
2977       0.6993, 0.6974, 0.6943, 0.6894, 0.6823, 0.6723, 0.6588, 0.6406, &     
2978       0.6161, 0.5847, 0.5466, 0.5034, 0.6518, 0.6518, 0.6518, 0.6518, &     
2979       0.6518, 0.6517, 0.6517, 0.6515, 0.6513, 0.6508, 0.6500, 0.6485, &     
2980       0.6459, 0.6419, 0.6359, 0.6273, 0.6151, 0.5983, 0.5755, 0.5458, &     
2981       0.5095, 0.4681, 0.6017, 0.6017, 0.6017, 0.6017, 0.6016, 0.6016, &     
2982       0.6016, 0.6015, 0.6013, 0.6009, 0.6002, 0.5989, 0.5967, 0.5932, &     
2983       0.5879, 0.5801, 0.5691, 0.5535, 0.5322, 0.5043, 0.4700, 0.4308, &     
2984       0.5518, 0.5518, 0.5518, 0.5518, 0.5518, 0.5518, 0.5517, 0.5516, &     
2985       0.5514, 0.5511, 0.5505, 0.5493, 0.5473, 0.5441, 0.5393, 0.5322, &     
2986       0.5220, 0.5076, 0.4878, 0.4617, 0.4297, 0.3929/                       
2987 
2988      data ((cah(i,j),i=1,22),j=16,19)/ &                                     
2989       0.5031, 0.5031, 0.5031, 0.5031, 0.5031, 0.5030, 0.5030, 0.5029, &     
2990       0.5028, 0.5025, 0.5019, 0.5008, 0.4990, 0.4960, 0.4916, 0.4850, &     
2991       0.4757, 0.4624, 0.4441, 0.4201, 0.3904, 0.3564, 0.4565, 0.4565, &     
2992       0.4565, 0.4564, 0.4564, 0.4564, 0.4564, 0.4563, 0.4562, 0.4559, &     
2993       0.4553, 0.4544, 0.4527, 0.4500, 0.4460, 0.4400, 0.4315, 0.4194, &     
2994       0.4028, 0.3809, 0.3538, 0.3227, 0.4122, 0.4122, 0.4122, 0.4122, &     
2995       0.4122, 0.4122, 0.4122, 0.4121, 0.4120, 0.4117, 0.4112, 0.4104, &     
2996       0.4089, 0.4065, 0.4029, 0.3976, 0.3900, 0.3792, 0.3643, 0.3447, &     
2997       0.3203, 0.2923, 0.3696, 0.3696, 0.3696, 0.3696, 0.3696, 0.3696, &     
2998       0.3695, 0.3695, 0.3694, 0.3691, 0.3687, 0.3680, 0.3667, 0.3647, &     
2999       0.3615, 0.3570, 0.3504, 0.3409, 0.3279, 0.3106, 0.2892, 0.2642/       
3000
3001!********************************************************************
3002!-----table look-up for the reduction of clear-sky solar
3003!     radiation due to co2. The fraction 0.0343 is the
3004!     extraterrestrial solar flux in the co2 bands.
3005
3006      do k= 2, np+1
3007       do j= 1, n
3008        do i= 1, m
3009          xx=1./.3
3010          clog=log10(swc(i,j,k)*csm(i,j))
3011          wlog=log10(swh(i,j,k)*csm(i,j))
3012          ic=int( (clog+3.15)*xx+1.)
3013          iw=int( (wlog+4.15)*xx+1.)
3014          if(ic.lt.2)ic=2
3015          if(iw.lt.2)iw=2
3016          if(ic.gt.22)ic=22
3017          if(iw.gt.19)iw=19     
3018          dc=clog-float(ic-2)*.3+3.
3019          dw=wlog-float(iw-2)*.3+4.   
3020          x1=cah(1,iw-1)+(cah(1,iw)-cah(1,iw-1))*xx*dw
3021          x2=cah(ic-1,iw-1)+(cah(ic-1,iw)-cah(ic-1,iw-1))*xx*dw
3022          y2=x2+(cah(ic,iw-1)-cah(ic-1,iw-1))*xx*dc
3023          if (x1.lt.y2) x1=y2
3024          df(i,j,k)=df(i,j,k)+0.0343*(x1-y2)
3025        enddo     
3026       enddo     
3027      enddo     
3028
3029      end subroutine flxco2
3030
3031!*****************************************************************
3032
3033      subroutine o3prof (np, pres, ozone, its, ite, kts, kte, p, o3)
3034
3035!*****************************************************************
3036      implicit none
3037!*****************************************************************
3038!
3039      integer iprof,m,np,its,ite,kts,kte
3040      integer i,k,ko,kk
3041      real pres(np),ozone(np)
3042      real p(its:ite,kts:kte),o3(its:ite,kts:kte)
3043 
3044!     Statement function
3045 
3046      real Linear, x1, y1, x2, y2, x
3047      Linear(x1, y1, x2, y2, x) =  &
3048            (y1 * (x2 - x) + y2 * (x - x1)) / (x2 - x1)
3049!
3050      do k = 1,np
3051        pres(k) = alog(pres(k))
3052      enddo
3053      do k = kts,kte
3054        do i = its, ite
3055          p(i,k) = alog(p(i,k))
3056        end do
3057      end do
3058
3059! assume the pressure at model top is greater than pres(1)
3060! if it is not, this part needs to change
3061
3062      do i = its, ite
3063        ko = 1
3064        do k = kts+1, kte
3065          do while (ko .lt. np .and. p(i,k) .gt. pres(ko))
3066            ko = ko + 1
3067          end do
3068          o3(i,k) =  Linear (pres(ko),   ozone(ko),    &
3069                             pres(ko-1), ozone(ko-1),  &
3070                             p(i,k))
3071          ko = ko - 1
3072        end do
3073      end do
3074
3075! calculate top lay O3
3076
3077      do i = its, ite
3078        ko = 1
3079        k = kts
3080        do while (ko .le. np .and. p(i,k) .gt. pres(ko))
3081           ko = ko + 1
3082        end do
3083        IF (ko-1 .le. 1) then
3084           O3(i,k)=ozone(k)
3085        ELSE
3086           O3(i,k)=0.
3087           do kk=ko-2,1,-1
3088              O3(i,k)=O3(i,k)+ozone(kk)*(pres(kk+1)-pres(kk))
3089           enddo
3090           O3(i,k)=O3(i,k)/(pres(ko-1)-pres(1))
3091        ENDIF
3092!       print*,'O3=',i,k,ko,O3(i,k),p(i,k),ko,pres(ko),pres(ko-1)
3093      end do
3094     
3095      end subroutine o3prof
3096
3097!-----------------------------------------
3098    SUBROUTINE gsfc_swinit(cen_lat, allowed_to_read)
3099
3100    REAL, INTENT(IN    )      ::        cen_lat
3101    LOGICAL, INTENT(IN    )   ::       allowed_to_read
3102
3103        center_lat=cen_lat
3104
3105    END SUBROUTINE gsfc_swinit
3106
3107
3108END MODULE module_ra_gsfcsw
Note: See TracBrowser for help on using the repository browser.