1 | !*************************************************************************** |
---|
2 | ! * |
---|
3 | ! RRTM : RAPID RADIATIVE TRANSFER MODEL * |
---|
4 | ! * |
---|
5 | ! ATMOSPHERIC AND ENVIRONMENTAL RESEARCH, INC. * |
---|
6 | ! 840 MEMORIAL DRIVE * |
---|
7 | ! CAMBRIDGE, MA 02139 * |
---|
8 | ! * |
---|
9 | ! ELI J. MLAWER * |
---|
10 | ! STEVEN J. TAUBMAN~ * |
---|
11 | ! SHEPARD A. CLOUGH * |
---|
12 | ! * |
---|
13 | ! ~currently at GFDL * |
---|
14 | ! * |
---|
15 | ! email: mlawer@aer.com * |
---|
16 | ! * |
---|
17 | ! The authors wish to acknowledge the contributions of the * |
---|
18 | ! following people: Patrick D. Brown, Michael J. Iacono, * |
---|
19 | ! Ronald E. Farren, Luke Chen, Robert Bergstrom. * |
---|
20 | ! * |
---|
21 | !*************************************************************************** |
---|
22 | ! Reformatted for F90 by JJMorcrette, ECMWF, 980714 * |
---|
23 | ! * |
---|
24 | !*************************************************************************** |
---|
25 | ! *** mji *** |
---|
26 | ! *** This version of RRTM has been altered to interface with either |
---|
27 | ! the ECMWF numerical weather prediction model or the ECMWF column |
---|
28 | ! radiation model (ECRT) package. |
---|
29 | |
---|
30 | ! Revised, April, 1997; Michael J. Iacono, AER, Inc. |
---|
31 | ! - initial implementation of RRTM in ECRT code |
---|
32 | ! Revised, June, 1999; Michael J. Iacono and Eli J. Mlawer, AER, Inc. |
---|
33 | ! - to implement generalized maximum/random cloud overlap |
---|
34 | |
---|
35 | SUBROUTINE RRTM_RRTM_140GP & |
---|
36 | & ( KIDIA , KFDIA , KLON , KLEV,& |
---|
37 | & PAER , PAPH , PAP,& |
---|
38 | & PTS , PTH , PT,& |
---|
39 | & P_ZEMIS , P_ZEMIW,& |
---|
40 | & PQ , PCCO2 , POZN,& |
---|
41 | & PCLDF , PTAUCLD,& |
---|
42 | & PTAU_LW,& |
---|
43 | & PEMIT , PFLUX , PFLUC, PTCLEAR & |
---|
44 | & ) |
---|
45 | |
---|
46 | ! *** This program is the driver for RRTM, the AER rapid model. |
---|
47 | ! For each atmosphere the user wishes to analyze, this routine |
---|
48 | ! a) calls ECRTATM to read in the atmospheric profile |
---|
49 | ! b) calls SETCOEF to calculate various quantities needed for |
---|
50 | ! the radiative transfer algorithm |
---|
51 | ! c) calls RTRN to do the radiative transfer calculation for |
---|
52 | ! clear or cloudy sky |
---|
53 | ! d) writes out the upward, downward, and net flux for each |
---|
54 | ! level and the heating rate for each layer |
---|
55 | |
---|
56 | USE PARKIND1 ,ONLY : JPIM ,JPRB |
---|
57 | USE YOMHOOK ,ONLY : LHOOK, DR_HOOK |
---|
58 | USE YOERAD ,ONLY : NLW |
---|
59 | USE PARRRTM , ONLY : JPBAND ,JPXSEC ,JPGPT ,JPLAY ,& |
---|
60 | & JPINPX |
---|
61 | !------------------------------Arguments-------------------------------- |
---|
62 | |
---|
63 | ! Input arguments |
---|
64 | |
---|
65 | IMPLICIT NONE |
---|
66 | INTEGER(KIND=JPIM),INTENT(IN) :: KLON! Number of atmospheres (longitudes) |
---|
67 | INTEGER(KIND=JPIM),INTENT(IN) :: KLEV! Number of atmospheric layers |
---|
68 | INTEGER(KIND=JPIM),INTENT(IN) :: KIDIA ! First atmosphere index |
---|
69 | INTEGER(KIND=JPIM),INTENT(IN) :: KFDIA ! Last atmosphere index |
---|
70 | REAL(KIND=JPRB) ,INTENT(IN) :: PAER(KLON,6,KLEV) ! Aerosol optical thickness |
---|
71 | REAL(KIND=JPRB) ,INTENT(IN) :: PAPH(KLON,KLEV+1) ! Interface pressures (Pa) |
---|
72 | REAL(KIND=JPRB) ,INTENT(IN) :: PAP(KLON,KLEV) ! Layer pressures (Pa) |
---|
73 | REAL(KIND=JPRB) ,INTENT(IN) :: PTS(KLON) ! Surface temperature (I_K) |
---|
74 | REAL(KIND=JPRB) ,INTENT(IN) :: PTH(KLON,KLEV+1) ! Interface temperatures (I_K) |
---|
75 | REAL(KIND=JPRB) ,INTENT(IN) :: PT(KLON,KLEV) ! Layer temperature (I_K) |
---|
76 | REAL(KIND=JPRB) ,INTENT(IN) :: P_ZEMIS(KLON) ! Non-window surface emissivity |
---|
77 | REAL(KIND=JPRB) ,INTENT(IN) :: P_ZEMIW(KLON) ! Window surface emissivity |
---|
78 | REAL(KIND=JPRB) ,INTENT(IN) :: PQ(KLON,KLEV) ! H2O specific humidity (mmr) |
---|
79 | REAL(KIND=JPRB) ,INTENT(IN) :: PCCO2 ! CO2 mass mixing ratio |
---|
80 | REAL(KIND=JPRB) ,INTENT(IN) :: POZN(KLON,KLEV) ! O3 mass mixing ratio |
---|
81 | REAL(KIND=JPRB) ,INTENT(IN) :: PCLDF(KLON,KLEV) ! Cloud fraction |
---|
82 | REAL(KIND=JPRB) ,INTENT(IN) :: PTAUCLD(KLON,KLEV,JPBAND) ! Cloud optical depth |
---|
83 | !--C.Kleinschmitt |
---|
84 | REAL(KIND=JPRB) ,INTENT(IN) :: PTAU_LW(KLON,KLEV,NLW) ! LW Optical depth of aerosols |
---|
85 | !--end |
---|
86 | REAL(KIND=JPRB) ,INTENT(OUT) :: PEMIT(KLON) ! Surface LW emissivity |
---|
87 | REAL(KIND=JPRB) ,INTENT(OUT) :: PFLUX(KLON,2,KLEV+1) ! LW total sky flux (1=up, 2=down) |
---|
88 | REAL(KIND=JPRB) ,INTENT(OUT) :: PFLUC(KLON,2,KLEV+1) ! LW clear sky flux (1=up, 2=down) |
---|
89 | REAL(KIND=JPRB) ,INTENT(OUT) :: PTCLEAR(KLON) ! clear-sky fraction of column |
---|
90 | INTEGER(KIND=JPIM) :: ICLDLYR(JPLAY) ! Cloud indicator |
---|
91 | REAL(KIND=JPRB) :: Z_CLDFRAC(JPLAY) ! Cloud fraction |
---|
92 | REAL(KIND=JPRB) :: Z_TAUCLD(JPLAY,JPBAND) ! Spectral optical thickness |
---|
93 | |
---|
94 | REAL(KIND=JPRB) :: Z_ABSS1 (JPGPT*JPLAY) |
---|
95 | REAL(KIND=JPRB) :: Z_ATR1 (JPGPT,JPLAY) |
---|
96 | EQUIVALENCE (Z_ABSS1(1),Z_ATR1(1,1)) |
---|
97 | |
---|
98 | REAL(KIND=JPRB) :: Z_OD (JPGPT,JPLAY) |
---|
99 | |
---|
100 | REAL(KIND=JPRB) :: Z_TAUSF1(JPGPT*JPLAY) |
---|
101 | REAL(KIND=JPRB) :: Z_TF1 (JPGPT,JPLAY) |
---|
102 | EQUIVALENCE (Z_TAUSF1(1),Z_TF1(1,1)) |
---|
103 | |
---|
104 | REAL(KIND=JPRB) :: Z_COLDRY(JPLAY) |
---|
105 | REAL(KIND=JPRB) :: Z_WKL(JPINPX,JPLAY) |
---|
106 | |
---|
107 | REAL(KIND=JPRB) :: Z_WX(JPXSEC,JPLAY) ! Amount of trace gases |
---|
108 | |
---|
109 | REAL(KIND=JPRB) :: Z_CLFNET (0:JPLAY) |
---|
110 | REAL(KIND=JPRB) :: Z_CLHTR (0:JPLAY) |
---|
111 | REAL(KIND=JPRB) :: Z_FNET (0:JPLAY) |
---|
112 | REAL(KIND=JPRB) :: Z_HTR (0:JPLAY) |
---|
113 | REAL(KIND=JPRB) :: Z_TOTDFLUC(0:JPLAY) |
---|
114 | REAL(KIND=JPRB) :: Z_TOTDFLUX(0:JPLAY) |
---|
115 | REAL(KIND=JPRB) :: Z_TOTUFLUC(0:JPLAY) |
---|
116 | REAL(KIND=JPRB) :: Z_TOTUFLUX(0:JPLAY) |
---|
117 | |
---|
118 | INTEGER(KIND=JPIM) :: i, icld, iplon, I_K |
---|
119 | INTEGER(KIND=JPIM) :: ISTART |
---|
120 | INTEGER(KIND=JPIM) :: IEND |
---|
121 | |
---|
122 | REAL(KIND=JPRB) :: Z_FLUXFAC, Z_HEATFAC, Z_PI, ZEPSEC, ZTCLEAR |
---|
123 | |
---|
124 | !- from AER |
---|
125 | REAL(KIND=JPRB) :: Z_TAUAERL(JPLAY,JPBAND) |
---|
126 | |
---|
127 | !- from INTFAC |
---|
128 | REAL(KIND=JPRB) :: Z_FAC00(JPLAY) |
---|
129 | REAL(KIND=JPRB) :: Z_FAC01(JPLAY) |
---|
130 | REAL(KIND=JPRB) :: Z_FAC10(JPLAY) |
---|
131 | REAL(KIND=JPRB) :: Z_FAC11(JPLAY) |
---|
132 | REAL(KIND=JPRB) :: Z_FORFAC(JPLAY) |
---|
133 | |
---|
134 | !- from INTIND |
---|
135 | INTEGER(KIND=JPIM) :: JP(JPLAY) |
---|
136 | INTEGER(KIND=JPIM) :: JT(JPLAY) |
---|
137 | INTEGER(KIND=JPIM) :: JT1(JPLAY) |
---|
138 | |
---|
139 | !- from PRECISE |
---|
140 | REAL(KIND=JPRB) :: Z_ONEMINUS |
---|
141 | |
---|
142 | !- from PROFDATA |
---|
143 | REAL(KIND=JPRB) :: Z_COLH2O(JPLAY) |
---|
144 | REAL(KIND=JPRB) :: Z_COLCO2(JPLAY) |
---|
145 | REAL(KIND=JPRB) :: Z_COLO3 (JPLAY) |
---|
146 | REAL(KIND=JPRB) :: Z_COLN2O(JPLAY) |
---|
147 | REAL(KIND=JPRB) :: Z_COLCH4(JPLAY) |
---|
148 | REAL(KIND=JPRB) :: Z_COLO2 (JPLAY) |
---|
149 | REAL(KIND=JPRB) :: Z_CO2MULT(JPLAY) |
---|
150 | INTEGER(KIND=JPIM) :: I_LAYTROP |
---|
151 | INTEGER(KIND=JPIM) :: I_LAYSWTCH |
---|
152 | INTEGER(KIND=JPIM) :: I_LAYLOW |
---|
153 | |
---|
154 | !- from PROFILE |
---|
155 | REAL(KIND=JPRB) :: Z_PAVEL(JPLAY) |
---|
156 | REAL(KIND=JPRB) :: Z_TAVEL(JPLAY) |
---|
157 | REAL(KIND=JPRB) :: Z_PZ(0:JPLAY) |
---|
158 | REAL(KIND=JPRB) :: Z_TZ(0:JPLAY) |
---|
159 | REAL(KIND=JPRB) :: Z_TBOUND |
---|
160 | INTEGER(KIND=JPIM) :: I_NLAYERS |
---|
161 | |
---|
162 | !- from SELF |
---|
163 | REAL(KIND=JPRB) :: Z_SELFFAC(JPLAY) |
---|
164 | REAL(KIND=JPRB) :: Z_SELFFRAC(JPLAY) |
---|
165 | INTEGER(KIND=JPIM) :: INDSELF(JPLAY) |
---|
166 | |
---|
167 | !- from SP |
---|
168 | REAL(KIND=JPRB) :: Z_PFRAC(JPGPT,JPLAY) |
---|
169 | |
---|
170 | !- from SURFACE |
---|
171 | REAL(KIND=JPRB) :: Z_SEMISS(JPBAND) |
---|
172 | REAL(KIND=JPRB) :: Z_SEMISLW |
---|
173 | INTEGER(KIND=JPIM) :: IREFLECT |
---|
174 | REAL(KIND=JPRB) :: ZHOOK_HANDLE |
---|
175 | |
---|
176 | #include "rrtm_ecrt_140gp.intfb.h" |
---|
177 | #include "rrtm_gasabs1a_140gp.intfb.h" |
---|
178 | #include "rrtm_rtrn1a_140gp.intfb.h" |
---|
179 | #include "rrtm_setcoef_140gp.intfb.h" |
---|
180 | |
---|
181 | ! HEATFAC is the factor by which one must multiply delta-flux/ |
---|
182 | ! delta-pressure, with flux in w/m-2 and pressure in mbar, to get |
---|
183 | ! the heating rate in units of degrees/day. It is equal to |
---|
184 | ! (g)x(#sec/day)x(1e-5)/(specific heat of air at const. p) |
---|
185 | ! = (9.8066)(86400)(1e-5)/(1.004) |
---|
186 | |
---|
187 | IF (LHOOK) CALL DR_HOOK('RRTM_RRTM_140GP',0,ZHOOK_HANDLE) |
---|
188 | ZEPSEC = 1.E-06_JPRB |
---|
189 | Z_ONEMINUS = 1.0_JPRB - ZEPSEC |
---|
190 | Z_PI = 2.0_JPRB*ASIN(1.0_JPRB) |
---|
191 | Z_FLUXFAC = Z_PI * 2.D4 |
---|
192 | Z_HEATFAC = 8.4391_JPRB |
---|
193 | |
---|
194 | ! *** mji *** |
---|
195 | ! For use with ECRT, this loop is over atmospheres (or longitudes) |
---|
196 | DO iplon = kidia,kfdia |
---|
197 | |
---|
198 | ! *** mji *** |
---|
199 | !- Prepare atmospheric profile from ECRT for use in RRTM, and define |
---|
200 | ! other RRTM input parameters. Arrays are passed back through the |
---|
201 | ! existing RRTM commons and arrays. |
---|
202 | ZTCLEAR=1.0_JPRB |
---|
203 | |
---|
204 | CALL RRTM_ECRT_140GP & |
---|
205 | & ( iplon, klon , klev, icld,& |
---|
206 | & paer , paph , pap,& |
---|
207 | & pts , pth , pt,& |
---|
208 | & P_ZEMIS, P_ZEMIW,& |
---|
209 | & pq , pcco2, pozn, pcldf, ptaucld, ztclear,& |
---|
210 | & Z_CLDFRAC,Z_TAUCLD,& |
---|
211 | & PTAU_LW,& |
---|
212 | & Z_COLDRY,Z_WKL,Z_WX,& |
---|
213 | & Z_TAUAERL,Z_PAVEL,Z_TAVEL,Z_PZ,Z_TZ,Z_TBOUND,I_NLAYERS,Z_SEMISS,IREFLECT) |
---|
214 | |
---|
215 | PTCLEAR(iplon)=ztclear |
---|
216 | |
---|
217 | ISTART = 1 |
---|
218 | IEND = 16 |
---|
219 | |
---|
220 | ! Calculate information needed by the radiative transfer routine |
---|
221 | ! that is specific to this atmosphere, especially some of the |
---|
222 | ! coefficients and indices needed to compute the optical depths |
---|
223 | ! by interpolating data from stored reference atmospheres. |
---|
224 | |
---|
225 | CALL RRTM_SETCOEF_140GP (KLEV,Z_COLDRY,Z_WKL,& |
---|
226 | & Z_FAC00,Z_FAC01,Z_FAC10,Z_FAC11,Z_FORFAC,JP,JT,JT1,& |
---|
227 | & Z_COLH2O,Z_COLCO2,Z_COLO3,Z_COLN2O,Z_COLCH4,Z_COLO2,Z_CO2MULT,& |
---|
228 | & I_LAYTROP,I_LAYSWTCH,I_LAYLOW,Z_PAVEL,Z_TAVEL,Z_SELFFAC,Z_SELFFRAC,INDSELF) |
---|
229 | |
---|
230 | CALL RRTM_GASABS1A_140GP (KLEV,Z_ATR1,Z_OD,Z_TF1,Z_COLDRY,Z_WX,& |
---|
231 | & Z_TAUAERL,Z_FAC00,Z_FAC01,Z_FAC10,Z_FAC11,Z_FORFAC,JP,JT,JT1,Z_ONEMINUS,& |
---|
232 | & Z_COLH2O,Z_COLCO2,Z_COLO3,Z_COLN2O,Z_COLCH4,Z_COLO2,Z_CO2MULT,& |
---|
233 | & I_LAYTROP,I_LAYSWTCH,I_LAYLOW,Z_SELFFAC,Z_SELFFRAC,INDSELF,Z_PFRAC) |
---|
234 | |
---|
235 | !- Call the radiative transfer routine. |
---|
236 | |
---|
237 | ! *** mji *** |
---|
238 | ! Check for cloud in column. Use ECRT threshold set as flag icld in |
---|
239 | ! routine ECRTATM. If icld=1 then column is cloudy, otherwise it is |
---|
240 | ! clear. Also, set up flag array, icldlyr, for use in radiative |
---|
241 | ! transfer. Set icldlyr to one for each layer with non-zero cloud |
---|
242 | ! fraction. |
---|
243 | |
---|
244 | DO I_K = 1, KLEV |
---|
245 | IF (ICLD == 1.AND.Z_CLDFRAC(I_K) > ZEPSEC) THEN |
---|
246 | ICLDLYR(I_K) = 1 |
---|
247 | ELSE |
---|
248 | ICLDLYR(I_K) = 0 |
---|
249 | ENDIF |
---|
250 | ENDDO |
---|
251 | |
---|
252 | ! Clear and cloudy parts of column are treated together in RTRN. |
---|
253 | ! Clear radiative transfer is done for clear layers and cloudy radiative |
---|
254 | ! transfer is done for cloudy layers as identified by icldlyr. |
---|
255 | |
---|
256 | CALL RRTM_RTRN1A_140GP (KLEV,ISTART,IEND,ICLDLYR,Z_CLDFRAC,Z_TAUCLD,Z_ABSS1,& |
---|
257 | & Z_OD,Z_TAUSF1,Z_CLFNET,Z_CLHTR,Z_FNET,Z_HTR,Z_TOTDFLUC,Z_TOTDFLUX,Z_TOTUFLUC,Z_TOTUFLUX,& |
---|
258 | & Z_TAVEL,Z_PZ,Z_TZ,Z_TBOUND,Z_PFRAC,Z_SEMISS,Z_SEMISLW,IREFLECT) |
---|
259 | |
---|
260 | ! *** Pass clear sky and total sky up and down flux profiles to ECRT |
---|
261 | ! output arrays (zflux, zfluc). Array indexing from bottom to top |
---|
262 | ! is preserved for ECRT. |
---|
263 | ! Invert down flux arrays for consistency with ECRT sign conventions. |
---|
264 | |
---|
265 | pemit(iplon) = Z_SEMISLW |
---|
266 | DO i = 0, KLEV |
---|
267 | PFLUC(iplon,1,i+1) = Z_TOTUFLUC(i)*Z_FLUXFAC |
---|
268 | PFLUC(iplon,2,i+1) = -Z_TOTDFLUC(i)*Z_FLUXFAC |
---|
269 | PFLUX(iplon,1,i+1) = Z_TOTUFLUX(i)*Z_FLUXFAC |
---|
270 | PFLUX(iplon,2,i+1) = -Z_TOTDFLUX(i)*Z_FLUXFAC |
---|
271 | ENDDO |
---|
272 | ENDDO |
---|
273 | |
---|
274 | IF (LHOOK) CALL DR_HOOK('RRTM_RRTM_140GP',1,ZHOOK_HANDLE) |
---|
275 | END SUBROUTINE RRTM_RRTM_140GP |
---|