CCPP SciDoc v7.0.0  v7.0.0
Common Community Physics Package Developed at DTC
 
Loading...
Searching...
No Matches
rrtmgp_lw_main.F90
1
3
6 use mpi_f08
7 use machine, only: kind_phys, kind_dbl_prec
8 use mo_optical_props, only: ty_optical_props_1scl, ty_optical_props_2str
9 use mo_cloud_optics, only: ty_cloud_optics
10 use mo_rte_lw, only: rte_lw
11 use mo_gas_optics_rrtmgp, only: ty_gas_optics_rrtmgp
12 use mo_gas_concentrations, only: ty_gas_concs
13 use mo_fluxes_byband, only: ty_fluxes_byband
14 use mo_source_functions, only: ty_source_func_lw
15 use radiation_tools, only: check_error_msg
16 use rrtmgp_lw_gas_optics, only: lw_gas_props,rrtmgp_lw_gas_optics_init
17 use rrtmgp_lw_cloud_optics, only: lw_cloud_props, rrtmgp_lw_cloud_optics_init, abssnow0, &
18 abssnow1, absrain
19 use gfs_rrtmgp_pre, only: istr_h2o, istr_co2, istr_o3, istr_n2o, istr_ch4, &
20 istr_o2, istr_ccl4, istr_cfc11, istr_cfc12, istr_cfc22, &
21 eps, oneminus, ftiny
23 use rrtmgp_sampling, only: sampled_mask, draw_samples
24 implicit none
25
26 public rrtmgp_lw_main_init, rrtmgp_lw_main_run
27contains
28
32 subroutine rrtmgp_lw_main_init(rrtmgp_root_dir, rrtmgp_lw_file_gas, rrtmgp_lw_file_clouds,&
33 active_gases_array, doGP_cldoptics_PADE, doGP_cldoptics_LUT, doGP_sgs_pbl, &
34 doGP_sgs_cnv, nrghice, mpicomm, mpirank, mpiroot, nLay, rrtmgp_phys_blksz, &
35 errmsg, errflg)
36
37 ! Inputs
38 character(len=128),intent(in) :: &
39 rrtmgp_root_dir, & !< RTE-RRTMGP root directory
40 rrtmgp_lw_file_clouds, & !< RRTMGP file containing coefficients used to compute
41
42 rrtmgp_lw_file_gas
44 character(len=*), dimension(:), intent(in), optional :: &
45 active_gases_array
46 logical, intent(in) :: &
47 dogp_cldoptics_pade, & !< Use RRTMGP cloud-optics: PADE approximation?
48 dogp_cldoptics_lut, & !< Use RRTMGP cloud-optics: LUTs?
49 dogp_sgs_pbl, & !< Flag to include sgs PBL clouds
50 dogp_sgs_cnv
51 integer, intent(inout) :: &
52 nrghice
53 type(mpi_comm),intent(in) :: &
54 mpicomm
55 integer,intent(in) :: &
56 mpirank, & !< Current MPI rank
57 mpiroot, & !< Master MPI rank
58 rrtmgp_phys_blksz, & !< Number of horizontal points to process at once.
59 nlay
60
61 ! Outputs
62 character(len=*), intent(out) :: &
63 errmsg
64 integer, intent(out) :: &
65 errflg
66
67 ! Initialize CCPP error handling variables
68 errmsg = ''
69 errflg = 0
70
71 ! RRTMGP longwave gas-optics (k-distribution) initialization
72 call rrtmgp_lw_gas_optics_init(rrtmgp_root_dir, rrtmgp_lw_file_gas, &
73 active_gases_array, mpicomm, mpirank, mpiroot, errmsg, errflg)
74
75 ! RRTMGP longwave cloud-optics initialization
76 call rrtmgp_lw_cloud_optics_init(rrtmgp_root_dir, rrtmgp_lw_file_clouds, &
77 dogp_cldoptics_pade, dogp_cldoptics_lut, nrghice, mpicomm, mpirank, mpiroot, &
78 errmsg, errflg)
79
80 end subroutine rrtmgp_lw_main_init
81
85 subroutine rrtmgp_lw_main_run(doLWrad, doLWclrsky, top_at_1, doGP_lwscat, &
86 use_LW_jacobian, doGP_sgs_cnv, doGP_sgs_pbl, nCol, nLay, nGases,rrtmgp_phys_blksz,&
87 nGauss_angles, icseed_lw, iovr, iovr_convcld, iovr_max, iovr_maxrand, iovr_rand, &
88 iovr_dcorr, iovr_exp, iovr_exprand, isubc_lw, semis, tsfg, p_lay, p_lev, t_lay, &
89 t_lev, vmr_o2, vmr_h2o, vmr_o3, vmr_ch4, vmr_n2o, vmr_co2, &
90 cld_frac, cld_lwp, cld_reliq, cld_iwp, cld_reice, cld_swp, cld_resnow, &
91 cld_rwp, cld_rerain, precip_frac, cld_cnv_lwp, cld_cnv_reliq, cld_cnv_iwp, &
92 cld_cnv_reice, cld_pbl_lwp, cld_pbl_reliq, cld_pbl_iwp, cld_pbl_reice, &
93 cloud_overlap_param, active_gases_array, aerlw_tau, aerlw_ssa, aerlw_g, &
94 fluxlwUP_allsky, fluxlwDOWN_allsky, fluxlwUP_clrsky, fluxlwDOWN_clrsky, &
95 fluxlwUP_jac, fluxlwUP_radtime, fluxlwDOWN_radtime, errmsg, errflg)
96
97 ! Inputs
98 logical, intent(in) :: &
99 dolwrad, & ! Flag to perform longwave calculation
100 dolwclrsky, & ! Flag to compute clear-sky fluxes
101 top_at_1, & ! Flag for vertical ordering convention
102 use_lw_jacobian, & ! Flag to compute Jacobian of longwave surface flux
103 dogp_sgs_pbl, & ! Flag to include sgs PBL clouds
104 dogp_sgs_cnv, & ! Flag to include sgs convective clouds
105 dogp_lwscat ! Flag to include scattering in clouds
106 integer,intent(in) :: &
107 ncol, & ! Number of horizontal points
108 nlay, & ! Number of vertical grid points.
109 ngases, & ! Number of active gases
110 rrtmgp_phys_blksz, & ! Number of horizontal points to process at once.
111 ngauss_angles, & ! Number of gaussian quadrature angles used
112 iovr, & ! Choice of cloud-overlap method
113 iovr_convcld, & ! Choice of convective cloud-overlap
114 iovr_max, & ! Flag for maximum cloud overlap method
115 iovr_maxrand, & ! Flag for maximum-random cloud overlap method
116 iovr_rand, & ! Flag for random cloud overlap method
117 iovr_dcorr, & ! Flag for decorrelation-length cloud overlap method
118 iovr_exp, & ! Flag for exponential cloud overlap method
119 iovr_exprand, & ! Flag for exponential-random cloud overlap method
120 isubc_lw ! Flag for cloud-seeding (rng) for cloud-sampling
121 integer,intent(in),dimension(:), optional :: &
122 icseed_lw ! Seed for random number generation for longwave radiation
123 real(kind_phys), dimension(:), intent(in) :: &
124 semis, & ! Surface-emissivity (1)
125 tsfg ! Skin temperature (K)
126 real(kind_phys), dimension(:,:), intent(in), optional :: &
127 p_lay, & ! Pressure @ model layer-centers (Pa)
128 t_lay, & ! Temperature (K)
129 p_lev, & ! Pressure @ model layer-interfaces (Pa)
130 t_lev, & ! Temperature @ model levels (K)
131 vmr_o2, & ! Molar-mixing ratio oxygen
132 vmr_h2o, & ! Molar-mixing ratio water vapor
133 vmr_o3, & ! Molar-mixing ratio ozone
134 vmr_ch4, & ! Molar-mixing ratio methane
135 vmr_n2o, & ! Molar-mixing ratio nitrous oxide
136 vmr_co2 ! Molar-mixing ratio carbon dioxide
137 real(kind_phys), dimension(:,:), intent(in) :: &
138 cld_frac, & ! Cloud-fraction for stratiform clouds
139 cld_lwp, & ! Water path for stratiform liquid cloud-particles
140 cld_reliq, & ! Effective radius for stratiform liquid cloud-particles
141 cld_iwp, & ! Water path for stratiform ice cloud-particles
142 cld_reice, & ! Effective radius for stratiform ice cloud-particles
143 cld_swp, & ! Water path for snow hydrometeors
144 cld_resnow, & ! Effective radius for snow hydrometeors
145 cld_rwp, & ! Water path for rain hydrometeors
146 cld_rerain ! Effective radius for rain hydrometeors
147 real(kind_phys), dimension(:,:), intent(in), optional :: &
148 precip_frac, & ! Precipitation fraction (not active, currently precipitation optics uses cloud-fraction)
149 cld_cnv_lwp, & ! Water path for convective liquid cloud-particles
150 cld_cnv_reliq, & ! Effective radius for convective liquid cloud-particles
151 cld_cnv_iwp, & ! Water path for convective ice cloud-particles
152 cld_cnv_reice, & ! Effective radius for convective ice cloud-particles
153 cld_pbl_lwp, & ! Water path for PBL liquid cloud-particles
154 cld_pbl_reliq, & ! Effective radius for PBL liquid cloud-particles
155 cld_pbl_iwp, & ! Water path for PBL ice cloud-particles
156 cld_pbl_reice, & ! Effective radius for PBL ice cloud-particles
157 cloud_overlap_param ! Cloud overlap parameter
158 real(kind_phys), dimension(:,:,:), intent(in) :: &
159 aerlw_tau, & ! Aerosol optical depth
160 aerlw_ssa, & ! Aerosol single scattering albedo
161 aerlw_g ! Aerosol asymmetry paramter
162 character(len=*), dimension(:), intent(in), optional :: &
163 active_gases_array ! List of active gases from namelist as array
164
165 ! Outputs
166 real(kind_phys), dimension(:,:), intent(inout), optional :: &
167 fluxlwup_jac, & ! Jacobian of upwelling LW surface radiation (W/m2/K)
168 fluxlwup_allsky, & ! All-sky flux (W/m2)
169 fluxlwdown_allsky, & ! All-sky flux (W/m2)
170 fluxlwup_clrsky, & ! Clear-sky flux (W/m2)
171 fluxlwdown_clrsky, & ! All-sky flux (W/m2)
172 fluxlwup_radtime, & ! Copy of fluxes (Used for coupling)
173 fluxlwdown_radtime !
174 character(len=*), intent(out) :: &
175 errmsg ! CCPP error message
176 integer, intent(out) :: &
177 errflg ! CCPP error flag
178
179 ! Local variables
180 type(ty_fluxes_byband) :: flux_allsky, flux_clrsky
181 integer :: icol, ilay, igas, iband, icol2, ix, iblck
182 integer, dimension(rrtmgp_phys_blksz) :: ipseed_lw
183 type(random_stat) :: rng_stat
184 real(kind_phys), dimension(rrtmgp_phys_blksz) :: zcf0, zcf1
185 logical, dimension(rrtmgp_phys_blksz,nLay,lw_gas_props%get_ngpt()) :: maskmcica
186 real(kind_phys), dimension(rrtmgp_phys_blksz) :: tau_rain, tau_snow
187 real(kind_dbl_prec), dimension(lw_gas_props%get_ngpt()) :: rng1d
188 real(kind_dbl_prec), dimension(lw_gas_props%get_ngpt(),nLay,rrtmgp_phys_blksz) :: rng3d,rng3d2
189 real(kind_dbl_prec), dimension(lw_gas_props%get_ngpt()*nLay) :: rng2d
190 real(kind_phys), dimension(rrtmgp_phys_blksz,nLay+1,lw_gas_props%get_nband()),target :: &
191 fluxlw_up_allsky, fluxlw_up_clrsky, fluxlw_dn_allsky, fluxlw_dn_clrsky
192 real(kind_phys), dimension(rrtmgp_phys_blksz,lw_gas_props%get_ngpt()) :: lw_ds
193 real(kind_phys), dimension(lw_gas_props%get_nband(),rrtmgp_phys_blksz) :: sfc_emiss_byband
194
195 ! Local RRTMGP DDTs.
196 type(ty_gas_concs) :: gas_concs
197 type(ty_optical_props_1scl) :: lw_optical_props_clrsky, lw_optical_props_aerosol_local
198 type(ty_optical_props_2str) :: lw_optical_props_clouds, lw_optical_props_cloudsbyband, &
199 lw_optical_props_cnvcloudsbyband, lw_optical_props_pblcloudsbyband, &
200 lw_optical_props_precipbyband
201 type(ty_source_func_lw) :: sources
202
203 ! Initialize CCPP error handling variables
204 errmsg = ''
205 errflg = 0
206
207 if (.not. dolwrad) return
208
209 !
210 ! Initialize RRTMGP DDTs (local)
211 !
212
213 ! ty_gas_concs
214 call check_error_msg('rrtmgp_lw_main_gas_concs_run',gas_concs%init(active_gases_array))
215
216 ! ty_optical_props
217 call check_error_msg('rrtmgp_lw_main_gas_optics_run',&
218 lw_optical_props_clrsky%alloc_1scl(rrtmgp_phys_blksz, nlay, lw_gas_props))
219 call check_error_msg('rrtmgp_lw_main_sources_run',&
220 sources%alloc(rrtmgp_phys_blksz, nlay, lw_gas_props))
221 call check_error_msg('rrtmgp_lw_main_cloud_optics_run',&
222 lw_optical_props_cloudsbyband%alloc_2str(rrtmgp_phys_blksz, nlay, lw_gas_props%get_band_lims_wavenumber()))
223 call check_error_msg('rrtmgp_lw_main_precip_optics_run',&
224 lw_optical_props_precipbyband%alloc_2str(rrtmgp_phys_blksz, nlay, lw_gas_props%get_band_lims_wavenumber()))
225 call check_error_msg('rrtmgp_lw_mian_cloud_sampling_run', &
226 lw_optical_props_clouds%alloc_2str(rrtmgp_phys_blksz, nlay, lw_gas_props))
227 call check_error_msg('rrtmgp_lw_main_aerosol_optics_run',&
228 lw_optical_props_aerosol_local%alloc_1scl(rrtmgp_phys_blksz, nlay, lw_gas_props%get_band_lims_wavenumber()))
229 if (dogp_sgs_cnv) then
230 call check_error_msg('rrtmgp_lw_main_cnv_cloud_optics_run',&
231 lw_optical_props_cnvcloudsbyband%alloc_2str(rrtmgp_phys_blksz, nlay, lw_gas_props%get_band_lims_wavenumber()))
232 endif
233 if (dogp_sgs_pbl) then
234 call check_error_msg('rrtmgp_lw_main_pbl_cloud_optics_run',&
235 lw_optical_props_pblcloudsbyband%alloc_2str(rrtmgp_phys_blksz, nlay, lw_gas_props%get_band_lims_wavenumber()))
236 endif
237
238 ! ######################################################################################
239 !
240 ! Loop over all columns...
241 !
242 ! ######################################################################################
243 do icol=1,ncol,rrtmgp_phys_blksz
244 icol2 = icol + rrtmgp_phys_blksz - 1
245
246 ! Initialize/reset
247
248 ! ty_optical_props
249 lw_optical_props_clrsky%tau = 0._kind_phys
250 lw_optical_props_precipbyband%tau = 0._kind_phys
251 lw_optical_props_precipbyband%ssa = 0._kind_phys
252 lw_optical_props_precipbyband%g = 0._kind_phys
253 lw_optical_props_cloudsbyband%tau = 0._kind_phys
254 lw_optical_props_cloudsbyband%ssa = 0._kind_phys
255 lw_optical_props_cloudsbyband%g = 0._kind_phys
256 lw_optical_props_clouds%tau = 0._kind_phys
257 lw_optical_props_clouds%ssa = 0._kind_phys
258 lw_optical_props_clouds%g = 0._kind_phys
259 sources%sfc_source = 0._kind_phys
260 sources%lay_source = 0._kind_phys
261 sources%lev_source_inc = 0._kind_phys
262 sources%lev_source_dec = 0._kind_phys
263 sources%sfc_source_Jac = 0._kind_phys
264 fluxlw_up_allsky = 0._kind_phys
265 fluxlw_dn_allsky = 0._kind_phys
266 fluxlw_up_clrsky = 0._kind_phys
267 fluxlw_dn_clrsky = 0._kind_phys
268 if (dogp_sgs_cnv) lw_optical_props_cnvcloudsbyband%tau = 0._kind_phys
269 if (dogp_sgs_pbl) lw_optical_props_pblcloudsbyband%tau = 0._kind_phys
270
271 ! ty_fluxes_byband
272 fluxlw_up_allsky = 0._kind_phys
273 fluxlw_dn_allsky = 0._kind_phys
274 fluxlw_up_clrsky = 0._kind_phys
275 fluxlw_dn_clrsky = 0._kind_phys
276 flux_allsky%bnd_flux_up => fluxlw_up_allsky
277 flux_allsky%bnd_flux_dn => fluxlw_dn_allsky
278 flux_clrsky%bnd_flux_up => fluxlw_up_clrsky
279 flux_clrsky%bnd_flux_dn => fluxlw_dn_clrsky
280
281 ! ###################################################################################
282 !
283 ! Set gas-concentrations
284 !
285 ! ###################################################################################
286 call check_error_msg('rrtmgp_lw_main_set_vmr_o2', &
287 gas_concs%set_vmr(trim(active_gases_array(istr_o2)), vmr_o2(icol:icol2,:)))
288 call check_error_msg('rrtmgp_lw_main_set_vmr_co2', &
289 gas_concs%set_vmr(trim(active_gases_array(istr_co2)),vmr_co2(icol:icol2,:)))
290 call check_error_msg('rrtmgp_lw_main_set_vmr_ch4', &
291 gas_concs%set_vmr(trim(active_gases_array(istr_ch4)),vmr_ch4(icol:icol2,:)))
292 call check_error_msg('rrtmgp_lw_main_set_vmr_n2o', &
293 gas_concs%set_vmr(trim(active_gases_array(istr_n2o)),vmr_n2o(icol:icol2,:)))
294 call check_error_msg('rrtmgp_lw_main_set_vmr_h2o', &
295 gas_concs%set_vmr(trim(active_gases_array(istr_h2o)),vmr_h2o(icol:icol2,:)))
296 call check_error_msg('rrtmgp_lw_main_set_vmr_o3', &
297 gas_concs%set_vmr(trim(active_gases_array(istr_o3)), vmr_o3(icol:icol2,:)))
298
299 ! ###################################################################################
300 !
301 ! Surface emissity in each band
302 !
303 ! ###################################################################################
304 ! Assign same emissivity to all band
305 do iblck=1,rrtmgp_phys_blksz
306 if (semis(icol+iblck-1) > eps .and. semis(icol+iblck-1) <= 1._kind_phys) then
307 do iband=1,lw_gas_props%get_nband()
308 sfc_emiss_byband(iband,iblck) = semis(icol+iblck-1)
309 enddo
310 else
311 sfc_emiss_byband(1:lw_gas_props%get_nband(),iblck) = 1.0
312 endif
313 enddo
314
315 ! ###################################################################################
316 !
317 ! Compute gas-optics...
318 !
319 ! ###################################################################################
320 call check_error_msg('rrtmgp_lw_main_gas_optics',lw_gas_props%gas_optics(&
321 p_lay(icol:icol2,:), & ! IN - Pressure @ layer-centers (Pa)
322 p_lev(icol:icol2,:), & ! IN - Pressure @ layer-interfaces (Pa)
323 t_lay(icol:icol2,:), & ! IN - Temperature @ layer-centers (K)
324 tsfg(icol:icol2), & ! IN - Skin-temperature (K)
325 gas_concs, & ! IN - RRTMGP DDT: trace gas volumne mixing-ratios
326 lw_optical_props_clrsky, & ! OUT - RRTMGP DDT: longwave optical properties
327 sources, & ! OUT - RRTMGP DDT: source functions
328 tlev=t_lev(icol:icol2,:))) ! IN - Temperature @ layer-interfaces (K) (optional)
329
330 ! ###################################################################################
331 !
332 ! Compute cloud-optics...
333 !
334 ! ###################################################################################
335 ! Create clear/cloudy indicator
336 zcf0(:) = 1._kind_phys
337 zcf1(:) = 1._kind_phys
338 do iblck = 1, rrtmgp_phys_blksz
339 do ilay=1,nlay
340 zcf0(iblck) = min(zcf0(iblck), 1._kind_phys - cld_frac(icol+iblck-1,ilay))
341 enddo
342 if (zcf0(iblck) <= ftiny) zcf0(iblck) = 0._kind_phys
343 if (zcf0(iblck) > oneminus) zcf0(iblck) = 1._kind_phys
344 zcf1(iblck) = 1._kind_phys - zcf0(iblck)
345 enddo
346
347 if (any(zcf1 .gt. eps)) then
348 ! Microphysical (gridmean) cloud optics
349 call check_error_msg('rrtmgp_lw_main_cloud_optics',lw_cloud_props%cloud_optics(&
350 cld_lwp(icol:icol2,:), & ! IN - Cloud liquid water path (g/m2)
351 cld_iwp(icol:icol2,:), & ! IN - Cloud ice water path (g/m2)
352 cld_reliq(icol:icol2,:), & ! IN - Cloud liquid effective radius (microns)
353 cld_reice(icol:icol2,:), & ! IN - Cloud ice effective radius (microns)
354 lw_optical_props_cloudsbyband)) ! OUT - RRTMGP DDT containing cloud radiative properties
355 ! in each band
356 ! Include convective (subgrid scale) clouds?
357 if (dogp_sgs_cnv) then
358 ! Compute
359 call check_error_msg('rrtmgp_lw_main_cnv_cloud_optics',lw_cloud_props%cloud_optics(&
360 cld_cnv_lwp(icol:icol2,:), & ! IN - Convective cloud liquid water path (g/m2)
361 cld_cnv_iwp(icol:icol2,:), & ! IN - Convective cloud ice water path (g/m2)
362 cld_cnv_reliq(icol:icol2,:), & ! IN - Convective cloud liquid effective radius (microns)
363 cld_cnv_reice(icol:icol2,:), & ! IN - Convective cloud ice effective radius (microns)
364 lw_optical_props_cnvcloudsbyband)) ! OUT - RRTMGP DDT containing convective cloud radiative properties
365 ! in each band
366 ! Increment
367 call check_error_msg('rrtmgp_lw_main_increment_cnvclouds_to_clouds',&
368 lw_optical_props_cnvcloudsbyband%increment(lw_optical_props_cloudsbyband))
369 endif
370
371 ! Include PBL (subgrid scale) clouds?
372 if (dogp_sgs_pbl) then
373 ! Compute
374 call check_error_msg('rrtmgp_lw_main_pbl_cloud_optics',lw_cloud_props%cloud_optics(&
375 cld_pbl_lwp(icol:icol2,:), & ! IN - PBL cloud liquid water path (g/m2)
376 cld_pbl_iwp(icol:icol2,:), & ! IN - PBL cloud ice water path (g/m2)
377 cld_pbl_reliq(icol:icol2,:), & ! IN - PBL cloud liquid effective radius (microns)
378 cld_pbl_reice(icol:icol2,:), & ! IN - PBL cloud ice effective radius (microns)
379 lw_optical_props_pblcloudsbyband)) ! OUT - RRTMGP DDT containing PBL cloud radiative properties
380 ! in each band
381 ! Increment
382 call check_error_msg('rrtmgp_lw_main_increment_pblclouds_to_clouds',&
383 lw_optical_props_pblcloudsbyband%increment(lw_optical_props_cloudsbyband))
384 endif
385 endif
386
387 ! ###################################################################################
388 !
389 ! Cloud precipitation optics: rain and snow(+groupel)
390 !
391 ! ###################################################################################
392 tau_rain(:) = 0._kind_phys
393 tau_snow(:) = 0._kind_phys
394 do ix=1,rrtmgp_phys_blksz
395 do ilay=1,nlay
396 if (cld_frac(icol+ix-1,ilay) .gt. eps) then
397 ! Rain optical-depth (No band dependence)
398 tau_rain(ix) = absrain*cld_rwp(icol+ix-1,ilay)
399
400 ! Snow (+groupel) optical-depth (No band dependence)
401 if (cld_swp(icol+ix-1,ilay) .gt. 0. .and. cld_resnow(icol+ix-1,ilay) .gt. 10._kind_phys) then
402 tau_snow(ix) = abssnow0*1.05756*cld_swp(icol+ix-1,ilay)/cld_resnow(icol+ix-1,ilay)
403 else
404 tau_snow(ix) = 0.0
405 endif
406 do iband=1,lw_gas_props%get_nband()
407 lw_optical_props_precipbyband%tau(ix,ilay,iband) = tau_rain(ix) + tau_snow(ix)
408 enddo
409 endif
410 enddo
411 enddo
412 ! Increment
413 call check_error_msg('rrtmgp_lw_main_increment_precip_to_clouds',&
414 lw_optical_props_precipbyband%increment(lw_optical_props_cloudsbyband))
415
416 ! ###################################################################################
417 !
418 ! Cloud-sampling
419 ! *Note* All of the included cloud-types are sampled together, not independently.
420 !
421 ! ###################################################################################
422 if (any(zcf1 .gt. eps)) then
423 ! Change random number seed value for each radiation invocation (isubc_lw =1 or 2).
424 if(isubc_lw == 1) then ! advance prescribed permutation seed
425 do ix=1,rrtmgp_phys_blksz
426 ipseed_lw(ix) = lw_gas_props%get_ngpt() + icol + ix - 1
427 enddo
428 elseif (isubc_lw == 2) then ! use input array of permutaion seeds
429 do ix=1,rrtmgp_phys_blksz
430 ipseed_lw(ix) = icseed_lw(icol+ix-1)
431 enddo
432 endif
433
434 ! Call RNG
435 do ix=1,rrtmgp_phys_blksz
436 call random_setseed(ipseed_lw(ix),rng_stat)
437 ! Use same rng for each layer
438 if (iovr == iovr_max) then
439 call random_number(rng1d,rng_stat)
440 do ilay=1,nlay
441 rng3d(:,ilay,ix) = rng1d
442 enddo
443 else
444 do ilay=1,nlay
445 call random_number(rng1d,rng_stat)
446 rng3d(:,ilay,ix) = rng1d
447 enddo
448 endif
449 enddo
450
451 ! Cloud-overlap.
452 ! Maximum-random, random or maximum.
453 if (iovr == iovr_maxrand .or. iovr == iovr_rand .or. iovr == iovr_max) then
454 call sampled_mask(real(rng3d,kind=kind_phys), cld_frac(icol:icol2,:), maskmcica)
455 endif
456 ! Exponential decorrelation length overlap
457 if (iovr == iovr_dcorr) then
458 do ix=1,rrtmgp_phys_blksz
459 ! Generate second RNG
460 call random_setseed(ipseed_lw(ix),rng_stat)
461 call random_number(rng2d,rng_stat)
462 rng3d2(:,:,ix) = reshape(source = rng2d,shape=[lw_gas_props%get_ngpt(),nlay])
463 enddo
464 !
465 call sampled_mask(real(rng3d,kind=kind_phys), cld_frac(icol:icol2,:), maskmcica, &
466 overlap_param = cloud_overlap_param(icol:icol2,1:nlay-1), randoms2 = real(rng3d2, kind=kind_phys))
467 endif
468 ! Exponential or Exponential-random
469 if (iovr == iovr_exp .or. iovr == iovr_exprand) then
470 call sampled_mask(real(rng3d,kind=kind_phys), cld_frac(icol:icol2,:), maskmcica, &
471 overlap_param = cloud_overlap_param(icol:icol2,1:nlay-1))
472 endif
473 ! Sampling. Map band optical depth to each g-point using McICA
474 call check_error_msg('rrtmgp_lw_main_cloud_sampling',&
475 draw_samples(maskmcica, .true., &
476 lw_optical_props_cloudsbyband, lw_optical_props_clouds))
477 endif
478
479 ! ###################################################################################
480 !
481 ! Compute clear-sky fluxes (gaseous+aerosol) (optional)
482 !
483 ! ###################################################################################
484 ! Increment
485 lw_optical_props_aerosol_local%tau = aerlw_tau(icol:icol2,:,:)
486 call check_error_msg('rrtmgp_lw_main_increment_aerosol_to_clrsky',&
487 lw_optical_props_aerosol_local%increment(lw_optical_props_clrsky))
488
489 ! Call RTE solver
490 if (dolwclrsky) then
491 call check_error_msg('rrtmgp_lw_main_opt_angle',&
492 lw_gas_props%compute_optimal_angles(lw_optical_props_clrsky,lw_ds))
493 if (ngauss_angles .gt. 1) then
494 call check_error_msg('rrtmgp_lw_main_lw_rte_clrsky',rte_lw( &
495 lw_optical_props_clrsky, & ! IN - optical-properties
496 top_at_1, & ! IN - veritcal ordering flag
497 sources, & ! IN - source function
498 sfc_emiss_byband, & ! IN - surface emissivity in each LW band
499 flux_clrsky, & ! OUT - Fluxes
500 n_gauss_angles = ngauss_angles)) ! IN - Number of angles in Gaussian quadrature
501 else
502 call check_error_msg('rrtmgp_lw_main_lw_rte_clrsky',rte_lw( &
503 lw_optical_props_clrsky, & ! IN - optical-properties
504 top_at_1, & ! IN - veritcal ordering flag
505 sources, & ! IN - source function
506 sfc_emiss_byband, & ! IN - surface emissivity in each LW band
507 flux_clrsky, & ! OUT - Fluxes
508 lw_ds = lw_ds))
509 endif
510
511 ! Store fluxes
512 fluxlwup_clrsky(icol:icol2,:) = sum(flux_clrsky%bnd_flux_up, dim=3)
513 fluxlwdown_clrsky(icol:icol2,:) = sum(flux_clrsky%bnd_flux_dn, dim=3)
514 else
515 fluxlwup_clrsky(icol:icol2,:) = 0.0
516 fluxlwdown_clrsky(icol:icol2,:) = 0.0
517 endif
518
519 ! ###################################################################################
520 !
521 ! All-sky fluxes (clear-sky + clouds + precipitation)
522 ! *Note* CCPP does not allow for polymorphic types, they are ambiguous to the CCPP
523 ! framework. rte-rrtmgp uses polymorphic types extensively, for example, querying the
524 ! type to determine physics configuration/pathway/etc...
525 !
526 ! The logic in the code below is to satisfy the polymorphishm in the rte-rrtmgp code.
527 ! The rte-rrtmgp "increment" procedures are utilized to provide the correct type to the
528 ! rte solver (rte_lw). Rte_lw quieries the type determine if scattering is to be
529 ! included in the calculation. The increment procedures are called so that the correct
530 ! optical properties are inherited. ugh...
531 !
532 ! ###################################################################################
533
534 ! Include LW cloud-scattering?
535 if (dogp_lwscat) then
536 ! Increment
537 call check_error_msg('rrtmgp_lw_main_increment_clrsky_to_clouds',&
538 lw_optical_props_clrsky%increment(lw_optical_props_clouds))
539
540 if (use_lw_jacobian) then
541 ! Compute LW Jacobians
542 call check_error_msg('rrtmgp_lw_main_lw_rte_allsky',rte_lw( &
543 lw_optical_props_clouds, & ! IN - optical-properties
544 top_at_1, & ! IN - veritcal ordering flag
545 sources, & ! IN - source function
546 sfc_emiss_byband, & ! IN - surface emissivity in each LW band
547 flux_allsky, & ! OUT - Flxues
548 n_gauss_angles = ngauss_angles, & ! IN - Number of angles in Gaussian quadrature
549 flux_up_jac = fluxlwup_jac)) ! OUT - surface temperature flux (upward) Jacobian (W/m2/K)
550 else
551 call check_error_msg('rrtmgp_lw_main_lw_rte_allsky',rte_lw( &
552 lw_optical_props_clouds, & ! IN - optical-properties
553 top_at_1, & ! IN - veritcal ordering flag
554 sources, & ! IN - source function
555 sfc_emiss_byband, & ! IN - surface emissivity in each LW band
556 flux_allsky, & ! OUT - Flxues
557 n_gauss_angles = ngauss_angles)) ! IN - Number of angles in Gaussian quadrature
558 end if
559 ! No scattering in LW clouds.
560 else
561 ! Increment
562 call check_error_msg('rrtmgp_lw_main_increment_clouds_to_clrsky', &
563 lw_optical_props_clouds%increment(lw_optical_props_clrsky))
564
565 if (use_lw_jacobian) then
566 ! Compute LW Jacobians
567 call check_error_msg('rrtmgp_lw_rte_run',rte_lw( &
568 lw_optical_props_clrsky, & ! IN - optical-properties
569 top_at_1, & ! IN - veritcal ordering flag
570 sources, & ! IN - source function
571 sfc_emiss_byband, & ! IN - surface emissivity in each LW band
572 flux_allsky, & ! OUT - Flxues
573 n_gauss_angles = ngauss_angles, & ! IN - Number of angles in Gaussian quadrature
574 flux_up_jac = fluxlwup_jac)) ! OUT - surface temperature flux (upward) Jacobian (W/m2/K)
575 else
576 call check_error_msg('rrtmgp_lw_rte_run',rte_lw( &
577 lw_optical_props_clrsky, & ! IN - optical-properties
578 top_at_1, & ! IN - veritcal ordering flag
579 sources, & ! IN - source function
580 sfc_emiss_byband, & ! IN - surface emissivity in each LW band
581 flux_allsky, & ! OUT - Flxues
582 n_gauss_angles = ngauss_angles)) ! IN - Number of angles in Gaussian quadrature
583 end if
584 endif
585
586 ! Store fluxes
587 fluxlwup_allsky(icol:icol2,:) = sum(flux_allsky%bnd_flux_up, dim=3)
588 fluxlwdown_allsky(icol:icol2,:) = sum(flux_allsky%bnd_flux_dn, dim=3)
589
590 ! Save fluxes for coupling
591 fluxlwup_radtime(icol:icol2,:) = fluxlwup_allsky(icol:icol2,:)
592 fluxlwdown_radtime(icol:icol2,:) = fluxlwdown_allsky(icol:icol2,:)
593
594 enddo
595
596 end subroutine rrtmgp_lw_main_run
597end module rrtmgp_lw_main
This module calculates random numbers using the Mersenne twister.
This module contains tools for radiation.
This module contains two routines: The first initializes data and functions needed to compute the lon...
This module contains two routines: One to initialize the k-distribution data and functions needed to ...
This module contains the RRTMGP-LW radiation scheme.
This module provides a simple implementation of sampling for the Monte Carlo Independent Pixel Approx...