SCALE-RM
mod_atmos_phy_rd_driver.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
12 !-------------------------------------------------------------------------------
13 #include "inc_openmp.h"
15  !-----------------------------------------------------------------------------
16  !
17  !++ used modules
18  !
19  use scale_precision
20  use scale_stdio
21  use scale_prof
23  use scale_tracer
24  !-----------------------------------------------------------------------------
25  implicit none
26  private
27  !-----------------------------------------------------------------------------
28  !
29  !++ Public procedure
30  !
33  public :: atmos_phy_rd_driver
34 
35  !-----------------------------------------------------------------------------
36  !
37  !++ Public parameters & variables
38  !
39  !-----------------------------------------------------------------------------
40  !
41  !++ Private procedure
42  !
43  !-----------------------------------------------------------------------------
44  !
45  !++ Private parameters & variables
46  !
47  !-----------------------------------------------------------------------------
48 contains
49  !-----------------------------------------------------------------------------
51  subroutine atmos_phy_rd_driver_setup
52  use scale_atmos_phy_rd, only: &
54  use mod_atmos_admin, only: &
57  use mod_atmos_phy_rd_vars, only: &
58  sfcflx_lw_up => atmos_phy_rd_sflx_lw_up, &
59  sfcflx_lw_dn => atmos_phy_rd_sflx_lw_dn, &
60  sfcflx_sw_up => atmos_phy_rd_sflx_sw_up, &
61  sfcflx_sw_dn => atmos_phy_rd_sflx_sw_dn, &
62  toaflx_lw_up => atmos_phy_rd_toaflx_lw_up, &
63  toaflx_lw_dn => atmos_phy_rd_toaflx_lw_dn, &
64  toaflx_sw_up => atmos_phy_rd_toaflx_sw_up, &
65  toaflx_sw_dn => atmos_phy_rd_toaflx_sw_dn, &
66  sflx_rad_dn => atmos_phy_rd_sflx_downall, &
67  solins => atmos_phy_rd_solins, &
68  cossza => atmos_phy_rd_cossza
69  implicit none
70  !---------------------------------------------------------------------------
71 
72  if( io_l ) write(io_fid_log,*)
73  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[ATMOS PHY_RD] / Origin[SCALE-RM]'
74 
75  if ( atmos_sw_phy_rd ) then
76 
77  ! setup library component
79 
80  else
81 
82  if( io_l ) write(io_fid_log,*) '*** this component is never called.'
83  if( io_l ) write(io_fid_log,*) '*** radiation fluxes are set to zero.'
84  sfcflx_lw_up(:,:) = 0.0_rp
85  sfcflx_lw_dn(:,:) = 0.0_rp
86  sfcflx_sw_up(:,:) = 0.0_rp
87  sfcflx_sw_dn(:,:) = 0.0_rp
88  toaflx_lw_up(:,:) = 0.0_rp
89  toaflx_lw_dn(:,:) = 0.0_rp
90  toaflx_sw_up(:,:) = 0.0_rp
91  toaflx_sw_dn(:,:) = 0.0_rp
92  sflx_rad_dn(:,:,:,:) = 0.0_rp
93  solins(:,:) = 0.0_rp
94  cossza(:,:) = 0.0_rp
95 
96  endif
97 
98  return
99  end subroutine atmos_phy_rd_driver_setup
100 
101  !-----------------------------------------------------------------------------
103  subroutine atmos_phy_rd_driver_resume
104  use mod_atmos_admin, only: &
106  implicit none
107 
108  if ( atmos_sw_phy_rd ) then
109 
110  ! run once (only for the diagnostic value)
111  call prof_rapstart('ATM_Radiation', 1)
112  call atmos_phy_rd_driver( update_flag = .true. )
113  call prof_rapend ('ATM_Radiation', 1)
114 
115  end if
116 
117  return
118  end subroutine atmos_phy_rd_driver_resume
119 
120  !-----------------------------------------------------------------------------
122  subroutine atmos_phy_rd_driver( update_flag )
123  use scale_grid_real, only: &
124  real_cz, &
125  real_fz, &
126  real_lon, &
127  real_lat
128  use scale_const, only: &
129  pre00 => const_pre00, &
130  rdry => const_rdry, &
131  cpdry => const_cpdry
132  use scale_landuse, only: &
136  use scale_time, only: &
137  dt_rd => time_dtsec_atmos_phy_rd, &
138  time_nowdate, &
140  use scale_rm_statistics, only: &
142  stat_total
143  use scale_history, only: &
144  hist_in
145  use mod_atmos_admin, only: &
147  use scale_atmos_solarins, only: &
148  solarins_insolation => atmos_solarins_insolation
149  use scale_atmos_phy_rd, only: &
151  use scale_atmos_phy_rd_mm5sw, only: &
152  swrad
153  use scale_atmos_phy_rd_common, only: &
154  rd_heating => atmos_phy_rd_heating, &
155  i_sw, &
156  i_lw, &
157  i_dn, &
158  i_up, &
159  i_direct, &
160  i_diffuse
161  use mod_atmos_vars, only: &
162  temp, &
163  pres, &
164  dens, &
165  rhot, &
166  qtrc, &
167  rhot_t => rhot_tp
168  use mod_atmos_phy_sf_vars, only: &
169  sfc_temp => atmos_phy_sf_sfc_temp, &
170  sfc_albedo => atmos_phy_sf_sfc_albedo
171  use mod_atmos_phy_rd_vars, only: &
172  rhot_t_rd => atmos_phy_rd_rhot_t, &
173  sfcflx_lw_up => atmos_phy_rd_sflx_lw_up, &
174  sfcflx_lw_dn => atmos_phy_rd_sflx_lw_dn, &
175  sfcflx_sw_up => atmos_phy_rd_sflx_sw_up, &
176  sfcflx_sw_dn => atmos_phy_rd_sflx_sw_dn, &
177  toaflx_lw_up => atmos_phy_rd_toaflx_lw_up, &
178  toaflx_lw_dn => atmos_phy_rd_toaflx_lw_dn, &
179  toaflx_sw_up => atmos_phy_rd_toaflx_sw_up, &
180  toaflx_sw_dn => atmos_phy_rd_toaflx_sw_dn, &
181  sflx_rad_dn => atmos_phy_rd_sflx_downall, &
182  solins => atmos_phy_rd_solins, &
183  cossza => atmos_phy_rd_cossza
184  implicit none
185 
186  logical, intent(in) :: update_flag
187 
188  real(RP) :: TEMP_t (ka,ia,ja,3)
189  real(RP) :: flux_rad (ka,ia,ja,2,2,2)
190  real(RP) :: flux_rad_top( ia,ja,2,2,2)
191 
192  real(RP) :: flux_up (ka,ia,ja,2)
193  real(RP) :: flux_dn (ka,ia,ja,2)
194  real(RP) :: flux_net (ka,ia,ja,2)
195  real(RP) :: flux_net_toa( ia,ja,2)
196  real(RP) :: flux_net_sfc( ia,ja,2)
197 
198  real(RP) :: SFCFLX_LW_up_c(ia,ja)
199  real(RP) :: SFCFLX_LW_dn_c(ia,ja)
200  real(RP) :: SFCFLX_SW_up_c(ia,ja)
201  real(RP) :: SFCFLX_SW_dn_c(ia,ja)
202  real(RP) :: TOAFLX_LW_up_c(ia,ja)
203  real(RP) :: TOAFLX_LW_dn_c(ia,ja)
204  real(RP) :: TOAFLX_SW_up_c(ia,ja)
205  real(RP) :: TOAFLX_SW_dn_c(ia,ja)
206 
207  ! for WRF radiation scheme added by Adachi; array order is (i,k,j)
208  real(RP) :: RTHRATENSW(ia,ka,ja)
209  real(RP) :: SDOWN3D (ia,ka,ja) ! downward short wave flux (W/m2)
210  real(RP) :: GSW (ia,ja) ! net short wave flux at ground surface (W/m2)
211  real(RP) :: RHO3D (ia,ka,ja)
212  real(RP) :: T3D (ia,ka,ja)
213  real(RP) :: P3D (ia,ka,ja)
214  real(RP) :: PI3D (ia,ka,ja)
215  real(RP) :: DZ8W (ia,ka,ja)
216  real(RP) :: QV3D (ia,ka,ja)
217  real(RP) :: QC3D (ia,ka,ja)
218  real(RP) :: QR3D (ia,ka,ja)
219  real(RP) :: QI3D (ia,ka,ja)
220  real(RP) :: QS3D (ia,ka,ja)
221  real(RP) :: QG3D (ia,ka,ja)
222  real(RP) :: flux_rad_org(ka,ia,ja,2,2,2)
223 
224  real(RP) :: total ! dummy
225 
226  integer :: k, i, j
227  !---------------------------------------------------------------------------
228 
229  if ( update_flag ) then
230 
231  call solarins_insolation( solins(:,:), & ! [OUT]
232  cossza(:,:), & ! [OUT]
233  real_lon(:,:), & ! [IN]
234  real_lat(:,:), & ! [IN]
235  time_nowdate(:), & ! [IN]
236  time_offset_year ) ! [IN]
237 
238  call atmos_phy_rd( dens, rhot, qtrc, & ! [IN]
239  real_cz, real_fz, & ! [IN]
240  landuse_fact_ocean, & ! [IN]
241  landuse_fact_land, & ! [IN]
242  landuse_fact_urban, & ! [IN]
243  sfc_temp, & ! [IN]
244  sfc_albedo, & ! [IN]
245  solins, cossza, & ! [IN]
246  flux_rad, & ! [OUT]
247  flux_rad_top, & ! [OUT]
248  sflx_rad_dn ) ! [OUT]
249 
250  ! apply radiative flux convergence -> heating rate
251  call rd_heating( flux_rad(:,:,:,:,:,2), & ! [IN]
252  dens(:,:,:), & ! [IN]
253  rhot(:,:,:), & ! [IN]
254  qtrc(:,:,:,:), & ! [IN]
255  real_fz(:,:,:), & ! [IN]
256  dt_rd, & ! [IN]
257  temp_t(:,:,:,:), & ! [OUT]
258  rhot_t_rd(:,:,:) ) ! [OUT]
259 
260 
261 !OCL XFILL
262  do j = js, je
263  do i = is, ie
264  ! for clear-sky
265  sfcflx_lw_up_c(i,j) = flux_rad(ks-1,i,j,i_lw,i_up,1)
266  sfcflx_lw_dn_c(i,j) = flux_rad(ks-1,i,j,i_lw,i_dn,1)
267  sfcflx_sw_up_c(i,j) = flux_rad(ks-1,i,j,i_sw,i_up,1)
268  sfcflx_sw_dn_c(i,j) = flux_rad(ks-1,i,j,i_sw,i_dn,1)
269  ! for all-sky
270  sfcflx_lw_up(i,j) = flux_rad(ks-1,i,j,i_lw,i_up,2)
271  sfcflx_lw_dn(i,j) = flux_rad(ks-1,i,j,i_lw,i_dn,2)
272  sfcflx_sw_up(i,j) = flux_rad(ks-1,i,j,i_sw,i_up,2)
273  sfcflx_sw_dn(i,j) = flux_rad(ks-1,i,j,i_sw,i_dn,2)
274 
275  flux_net_sfc(i,j,i_lw) = flux_rad(ks-1,i,j,i_lw,i_up,2) - flux_rad(ks-1,i,j,i_lw,i_dn,2)
276  flux_net_sfc(i,j,i_sw) = flux_rad(ks-1,i,j,i_sw,i_up,2) - flux_rad(ks-1,i,j,i_sw,i_dn,2)
277  enddo
278  enddo
279 
280 !OCL XFILL
281  do j = js, je
282  do i = is, ie
283  ! for clear-sky
284  toaflx_lw_up_c(i,j) = flux_rad_top(i,j,i_lw,i_up,1)
285  toaflx_lw_dn_c(i,j) = flux_rad_top(i,j,i_lw,i_dn,1)
286  toaflx_sw_up_c(i,j) = flux_rad_top(i,j,i_sw,i_up,1)
287  toaflx_sw_dn_c(i,j) = flux_rad_top(i,j,i_sw,i_dn,1)
288  ! for all-sky
289  toaflx_lw_up(i,j) = flux_rad_top(i,j,i_lw,i_up,2)
290  toaflx_lw_dn(i,j) = flux_rad_top(i,j,i_lw,i_dn,2)
291  toaflx_sw_up(i,j) = flux_rad_top(i,j,i_sw,i_up,2)
292  toaflx_sw_dn(i,j) = flux_rad_top(i,j,i_sw,i_dn,2)
293 
294  flux_net_toa(i,j,i_lw) = flux_rad_top(i,j,i_lw,i_up,2) - flux_rad_top(i,j,i_lw,i_dn,2)
295  flux_net_toa(i,j,i_sw) = flux_rad_top(i,j,i_sw,i_up,2) - flux_rad_top(i,j,i_sw,i_dn,2)
296  enddo
297  enddo
298 
299 !OCL XFILL
300  do j = js, je
301  do i = is, ie
302  do k = ks, ke
303  flux_net(k,i,j,i_lw) = 0.5_rp * ( ( flux_rad(k-1,i,j,i_lw,i_up,2) - flux_rad(k-1,i,j,i_lw,i_dn,2) ) &
304  + ( flux_rad(k ,i,j,i_lw,i_up,2) - flux_rad(k ,i,j,i_lw,i_dn,2) ) )
305  flux_net(k,i,j,i_sw) = 0.5_rp * ( ( flux_rad(k-1,i,j,i_sw,i_up,2) - flux_rad(k-1,i,j,i_sw,i_dn,2) ) &
306  + ( flux_rad(k ,i,j,i_sw,i_up,2) - flux_rad(k ,i,j,i_sw,i_dn,2) ) )
307 
308  flux_up(k,i,j,i_lw) = 0.5_rp * ( flux_rad(k-1,i,j,i_lw,i_up,2) + flux_rad(k,i,j,i_lw,i_up,2) )
309  flux_up(k,i,j,i_sw) = 0.5_rp * ( flux_rad(k-1,i,j,i_sw,i_up,2) + flux_rad(k,i,j,i_sw,i_up,2) )
310  flux_dn(k,i,j,i_lw) = 0.5_rp * ( flux_rad(k-1,i,j,i_lw,i_dn,2) + flux_rad(k,i,j,i_lw,i_dn,2) )
311  flux_dn(k,i,j,i_sw) = 0.5_rp * ( flux_rad(k-1,i,j,i_sw,i_dn,2) + flux_rad(k,i,j,i_sw,i_dn,2) )
312  enddo
313  enddo
314  enddo
315 
316  if ( atmos_phy_rd_type == 'WRF' ) then
317 
318  flux_rad_org(:,:,:,:,:,:) = flux_rad(:,:,:,:,:,:)
319  rthratensw = 0.0_rp
320  sdown3d = 0.0_rp
321  gsw = 0.0_rp
322 
323  do j = 1, ja
324  do i = 1, ia
325  do k = 1, ka
326  qv3d(i,k,j) = qtrc(k,i,j,i_qv)
327  qc3d(i,k,j) = qtrc(k,i,j,i_qc)
328  qr3d(i,k,j) = qtrc(k,i,j,i_qr)
329  qi3d(i,k,j) = qtrc(k,i,j,i_qi)
330  qs3d(i,k,j) = qtrc(k,i,j,i_qs)
331  qg3d(i,k,j) = qtrc(k,i,j,i_qg)
332  t3d(i,k,j) = temp(k,i,j) ! temperature (K)
333  rho3d(i,k,j) = dens(k,i,j) ! density (kg/m^3)
334  p3d(i,k,j) = pres(k,i,j) ! pressure (Pa)
335  pi3d(i,k,j) = (pres(k,i,j)/pre00)**(rdry/cpdry) ! exner function (dimensionless)
336  dz8w(i,k,j) = real_fz(k,i,j)-real_fz(k-1,i,j) ! dz between full levels(m)
337  enddo
338  enddo
339  enddo
340 
341  call swrad( dt_rd, & ! [IN]
342  rthratensw, & ! [INOUT]
343  sdown3d, & ! [INOUT]
344  gsw, & ! [INOUT]
345  real_lat, & ! [IN]
346  real_lon, & ! [IN]
347  sfc_albedo(:,:,i_sw), & ! [IN]
348  rho3d, & ! [IN]
349  t3d, & ! [IN]
350  p3d, & ! [IN]
351  pi3d, & ! [IN]
352  dz8w, & ! [IN]
353  solins(:,:), & ! [IN]
354  cossza(:,:), & ! [IN]
355  qv3d, & ! [IN]
356  qc3d, & ! [IN]
357  qr3d, & ! [IN]
358  qi3d, & ! [IN]
359  qs3d, & ! [IN]
360  qg3d, & ! [IN]
361  f_qv = .true., & ! [IN]
362  f_qc = .true., & ! [IN]
363  f_qr = .true., & ! [IN]
364  f_qi = .true., & ! [IN]
365  f_qs = .true., & ! [IN]
366  f_qg = .true., & ! [IN]
367  icloud = 1, & ! [IN]
368  warm_rain = .true. ) ! [IN]
369 
370  do j = js, je
371  do i = is, ie
372  flux_net_sfc(i,j,i_sw) = gsw(i,j)
373  do k = ks-1, ke
374  flux_rad(k,i,j,i_sw,i_up,2) = 0.0_rp
375  flux_rad(k,i,j,i_sw,i_dn,2) = sdown3d(i,k,j)
376  enddo
377 
378  do k = 1, ks-2
379  flux_rad(k,i,j,i_sw,i_dn,2) = sdown3d(i,ks-1,j)
380  enddo
381 
382  do k = ke+1, ka
383  flux_rad(k,i,j,i_sw,i_dn,2) = sdown3d(i,ke,j)
384  enddo
385  enddo
386  enddo
387 
388  do j = js, je
389  do i = is, ie
390  sfcflx_sw_up(i,j) = flux_rad(ks-1,i,j,i_sw,i_dn,2) * sfc_albedo(i,j,i_sw)
391  sfcflx_sw_dn(i,j) = flux_rad(ks-1,i,j,i_sw,i_dn,2)
392 
393  toaflx_sw_up(i,j) = 0.0_rp
394  toaflx_sw_dn(i,j) = flux_rad(ke,i,j,i_sw,i_dn,2) ! sometimes TOA altitude is very low
395  enddo
396  enddo
397 
398  do j = js, je
399  do i = is, ie
400  flux_net_toa(i,j,i_sw) = 0.0_rp
401  do k = ks, ke
402  flux_net(k,i,j,i_sw) = 0.0_rp
403  flux_up(k,i,j,i_sw) = 0.0_rp
404  flux_dn(k,i,j,i_sw) = 0.5_rp * ( flux_rad(k-1,i,j,i_sw,i_dn,2) + flux_rad(k,i,j,i_sw,i_dn,2) )
405  enddo
406  enddo
407  enddo
408 
409  do j = js, je
410  do i = is, ie
411  flux_net_sfc(i,j,i_sw) = flux_rad(ks-1,i,j,i_sw,i_dn,2)*sfc_albedo(i,j,i_sw)-flux_rad(ks-1,i,j,i_sw,i_dn,2)
412  enddo
413  enddo
414 
415  endif
416 
417  call hist_in( solins(:,:), 'SOLINS', 'solar insolation', 'W/m2', nohalo=.true. )
418  call hist_in( cossza(:,:), 'COSZ', 'cos(solar zenith angle)', '0-1', nohalo=.true. )
419 
420  call hist_in( sfcflx_lw_up_c(:,:), 'SFLX_LW_up_c', 'SFC upward longwave radiation flux (clr)', 'W/m2', nohalo=.true. )
421  call hist_in( sfcflx_lw_dn_c(:,:), 'SFLX_LW_dn_c', 'SFC downward longwave radiation flux (clr)', 'W/m2', nohalo=.true. )
422  call hist_in( sfcflx_sw_up_c(:,:), 'SFLX_SW_up_c', 'SFC upward shortwave radiation flux (clr)', 'W/m2', nohalo=.true. )
423  call hist_in( sfcflx_sw_dn_c(:,:), 'SFLX_SW_dn_c', 'SFC downward shortwave radiation flux (clr)', 'W/m2', nohalo=.true. )
424 
425  call hist_in( toaflx_lw_up_c(:,:), 'TOAFLX_LW_up_c', 'TOA upward longwave radiation flux (clr)', 'W/m2', nohalo=.true. )
426  call hist_in( toaflx_lw_dn_c(:,:), 'TOAFLX_LW_dn_c', 'TOA downward longwave radiation flux (clr)', 'W/m2', nohalo=.true. )
427  call hist_in( toaflx_sw_up_c(:,:), 'TOAFLX_SW_up_c', 'TOA upward shortwave radiation flux (clr)', 'W/m2', nohalo=.true. )
428  call hist_in( toaflx_sw_dn_c(:,:), 'TOAFLX_SW_dn_c', 'TOA downward shortwave radiation flux (clr)', 'W/m2', nohalo=.true. )
429 
430  call hist_in( sfcflx_lw_up(:,:), 'SFLX_LW_up', 'SFC upward longwave radiation flux', 'W/m2', nohalo=.true. )
431  call hist_in( sfcflx_lw_dn(:,:), 'SFLX_LW_dn', 'SFC downward longwave radiation flux', 'W/m2', nohalo=.true. )
432  call hist_in( sfcflx_sw_up(:,:), 'SFLX_SW_up', 'SFC upward shortwave radiation flux', 'W/m2', nohalo=.true. )
433  call hist_in( sfcflx_sw_dn(:,:), 'SFLX_SW_dn', 'SFC downward shortwave radiation flux', 'W/m2', nohalo=.true. )
434 
435  call hist_in( sflx_rad_dn(:,:,i_sw,i_direct), 'SFLX_SW_dn_direct', 'SFC down. shortwave ratio direct', 'W/m2', nohalo=.true. )
436  call hist_in( sflx_rad_dn(:,:,i_sw,i_diffuse),'SFLX_SW_dn_diffuse', 'SFC down. shortwave ratio diffuse', 'W/m2', nohalo=.true. )
437 
438  call hist_in( toaflx_lw_up(:,:), 'TOAFLX_LW_up', 'TOA upward longwave radiation flux', 'W/m2', nohalo=.true. )
439  call hist_in( toaflx_lw_dn(:,:), 'TOAFLX_LW_dn', 'TOA downward longwave radiation flux', 'W/m2', nohalo=.true. )
440  call hist_in( toaflx_sw_up(:,:), 'TOAFLX_SW_up', 'TOA upward shortwave radiation flux', 'W/m2', nohalo=.true. )
441  call hist_in( toaflx_sw_dn(:,:), 'TOAFLX_SW_dn', 'TOA downward shortwave radiation flux', 'W/m2', nohalo=.true. )
442 
443  call hist_in( flux_net_sfc(:,:,i_lw), 'SLR', 'SFC net longwave radiation flux', 'W/m2', nohalo=.true. )
444  call hist_in( flux_net_sfc(:,:,i_sw), 'SSR', 'SFC net shortwave radiation flux', 'W/m2', nohalo=.true. )
445  call hist_in( flux_net_toa(:,:,i_lw), 'OLR', 'TOA net longwave radiation flux', 'W/m2', nohalo=.true. )
446  call hist_in( flux_net_toa(:,:,i_sw), 'OSR', 'TOA net shortwave radiation flux', 'W/m2', nohalo=.true. )
447 
448  call hist_in( flux_up(:,:,:,i_lw), 'RADFLUX_LWUP', 'upward longwave radiation flux', 'W/m2', nohalo=.true. )
449  call hist_in( flux_dn(:,:,:,i_lw), 'RADFLUX_LWDN', 'downward longwave radiation flux', 'W/m2', nohalo=.true. )
450  call hist_in( flux_net(:,:,:,i_lw), 'RADFLUX_LW', 'net longwave radiation flux', 'W/m2', nohalo=.true. )
451  call hist_in( flux_up(:,:,:,i_sw), 'RADFLUX_SWUP', 'upward shortwave radiation flux', 'W/m2', nohalo=.true. )
452  call hist_in( flux_dn(:,:,:,i_sw), 'RADFLUX_SWDN', 'downward shortwave radiation flux', 'W/m2', nohalo=.true. )
453  call hist_in( flux_net(:,:,:,i_sw), 'RADFLUX_SW', 'net shortwave radiation flux', 'W/m2', nohalo=.true. )
454 
455  call hist_in( temp_t(:,:,:,i_lw), 'TEMP_t_rd_LW', 'tendency of temp in rd(LW)', 'K/day', nohalo=.true. )
456  call hist_in( temp_t(:,:,:,i_sw), 'TEMP_t_rd_SW', 'tendency of temp in rd(SW)', 'K/day', nohalo=.true. )
457  call hist_in( temp_t(:,:,:,3 ), 'TEMP_t_rd', 'tendency of temp in rd', 'K/day', nohalo=.true. )
458  call hist_in( rhot_t_rd(:,:,:), 'RHOT_t_RD', 'tendency of RHOT in rd', 'K.kg/m3/s', nohalo=.true. )
459 
460  if ( atmos_phy_rd_type == 'WRF' ) then
461  ! revert all radiation flux from MM5 scheme to default
462  flux_rad(:,:,:,:,:,:) = flux_rad_org(:,:,:,:,:,:)
463 
464  do j = js, je
465  do i = is, ie
466  sfcflx_sw_up(i,j) = flux_rad(ks-1,i,j,i_sw,i_up,2)
467  sfcflx_sw_dn(i,j) = flux_rad(ks-1,i,j,i_sw,i_dn,2)
468 
469  toaflx_sw_up(i,j) = flux_rad_top(i,j,i_sw,i_up,2) ! mstrnx
470  toaflx_sw_dn(i,j) = flux_rad_top(i,j,i_sw,i_dn,2) ! mstrnx
471  enddo
472  enddo
473 
474  endif
475 
476  endif
477 
478  do j = js, je
479  do i = is, ie
480  do k = ks, ke
481  rhot_t(k,i,j) = rhot_t(k,i,j) + rhot_t_rd(k,i,j)
482  enddo
483  enddo
484  enddo
485 
486  if ( statistics_checktotal ) then
487  call stat_total( total, rhot_t_rd(:,:,:), 'RHOT_t_RD' )
488  endif
489 
490  return
491  end subroutine atmos_phy_rd_driver
492 
493 end module mod_atmos_phy_rd_driver
module ATMOS admin
integer, public is
start point of inner domain: x, local
logical, public statistics_checktotal
calc&report variable totals to logfile?
subroutine, public atmos_phy_rd_heating(flux_rad, DENS, RHOT, QTRC, FZ, dt, TEMP_t, RHOT_t)
Calc heating rate.
integer, public je
end point of inner domain: y, local
real(rp), public const_cpdry
specific heat (dry air,constant pressure) [J/kg/K]
Definition: scale_const.F90:58
integer, parameter, public i_direct
real(rp), dimension(:,:), allocatable, public landuse_fact_urban
urban factor
real(dp), public time_dtsec_atmos_phy_rd
time interval of physics(radiation ) [sec]
Definition: scale_time.F90:42
logical, public atmos_sw_phy_rd
real(rp), dimension(:,:,:), allocatable, target, public rhot
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
procedure(rd), pointer, public atmos_phy_rd
real(rp), dimension(:,:,:), allocatable, public pres
module ATMOSPHERE / Physics Radiation
module ATMOSPHERIC Variables
module STDIO
Definition: scale_stdio.F90:12
integer, public ke
end point of inner domain: z, local
real(rp), dimension(:,:,:), allocatable, public rhot_tp
real(rp), dimension(:,:,:), allocatable, public atmos_phy_rd_rhot_t
real(rp), dimension(:,:,:), allocatable, public real_fz
geopotential height [m] (cell face )
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sfc_temp
real(rp), dimension(:,:,:), allocatable, public real_cz
geopotential height [m] (cell center)
real(rp), dimension(:,:,:), allocatable, target, public dens
integer, parameter, public i_diffuse
character(len=h_short), public atmos_phy_rd_type
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_lw_up
subroutine, public atmos_phy_rd_driver_setup
Setup.
integer, parameter, public i_lw
real(rp), public const_rdry
specific gas constant (dry air) [J/kg/K]
Definition: scale_const.F90:57
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_sw_up
module Statistics
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_lw_dn
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_cossza
module Atmosphere / Physics Radiation
module grid index
module ATMOSPHERIC Surface Variables
integer, parameter, public i_sw
module TRACER
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_sw_up
integer, public ia
of x whole cells (local, with HALO)
real(rp), dimension(:,:,:), allocatable, public temp
module GRID (real space)
module LANDUSE
integer, parameter, public i_dn
integer, public ka
of z whole cells (local, with HALO)
integer, public i_qv
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_sw_dn
real(rp), public const_pre00
pressure reference [Pa]
Definition: scale_const.F90:93
integer, public time_offset_year
time offset [year]
Definition: scale_time.F90:73
real(rp), dimension(:,:,:), allocatable, public atmos_phy_sf_sfc_albedo
real(rp), dimension(:,:), allocatable, public landuse_fact_ocean
ocean factor
integer, public js
start point of inner domain: y, local
module TIME
Definition: scale_time.F90:15
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_lw_dn
module ATMOSPHERE / Physics Radiation
module CONSTANT
Definition: scale_const.F90:14
integer, public ks
start point of inner domain: z, local
integer, public i_qs
subroutine, public prof_rapstart(rapname_base, level)
Start raptime.
Definition: scale_prof.F90:132
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_rd_sflx_downall
subroutine, public swrad(dt, RTHRATEN, SDOWN3D, GSW, XLAT, XLONG, ALBEDO, rho_phy, T3D, P3D, pi3D, dz8w, solins, cosSZA, QV3D, QC3D, QR3D, QI3D, QS3D, QG3D, F_QV, F_QC, F_QR, F_QI, F_QS, F_QG, icloud, warm_rain)
subroutine, public atmos_phy_rd_driver(update_flag)
Driver.
module profiler
Definition: scale_prof.F90:10
integer, public i_qi
integer, public ie
end point of inner domain: x, local
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_sw_dn
real(rp), dimension(:,:), allocatable, public real_lon
longitude [rad,0-2pi]
integer, public i_qg
module PRECISION
subroutine, public atmos_phy_rd_driver_resume
Resume.
subroutine, public atmos_phy_rd_setup(RD_TYPE)
Setup.
module HISTORY
module ATMOSPHERE / Physics Radiation
integer, dimension(6), public time_nowdate
current time [YYYY MM DD HH MM SS]
Definition: scale_time.F90:65
real(rp), dimension(:,:), allocatable, public real_lat
latitude [rad,-pi,pi]
real(rp), dimension(:,:), allocatable, public landuse_fact_land
land factor
module ATMOSPHERE / Physics Radiation
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_solins
subroutine, public prof_rapend(rapname_base, level)
Save raptime.
Definition: scale_prof.F90:178
integer, parameter, public i_up
integer, public i_qr
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_lw_up
integer, public i_qc
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
integer, public ja
of y whole cells (local, with HALO)