SCALE-RM
mod_atmos_phy_rd_driver.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
10 !-------------------------------------------------------------------------------
11 #include "scalelib.h"
13  !-----------------------------------------------------------------------------
14  !
15  !++ used modules
16  !
17  use scale_precision
18  use scale_io
19  use scale_prof
21  use scale_tracer
23  !-----------------------------------------------------------------------------
24  implicit none
25  private
26  !-----------------------------------------------------------------------------
27  !
28  !++ Public procedure
29  !
33 
34  !-----------------------------------------------------------------------------
35  !
36  !++ Public parameters & variables
37  !
38  !-----------------------------------------------------------------------------
39  !
40  !++ Private procedure
41  !
42  !-----------------------------------------------------------------------------
43  !
44  !++ Private parameters & variables
45  !
46  logical, private :: RD_use_PBL_cloud = .false.
47 
48  !-----------------------------------------------------------------------------
49 contains
50  !-----------------------------------------------------------------------------
52  subroutine atmos_phy_rd_driver_setup
53  use scale_prc, only: &
54  prc_abort
55  use scale_atmos_phy_rd_mstrnx, only: &
57  use scale_atmos_phy_rd_offline, only: &
59  use scale_atmos_grid_cartesc, only: &
60  cz => atmos_grid_cartesc_cz, &
62  use mod_atmos_admin, only: &
65  use mod_atmos_phy_rd_vars, only: &
66  sfcflx_lw_up => atmos_phy_rd_sflx_lw_up, &
67  sfcflx_lw_dn => atmos_phy_rd_sflx_lw_dn, &
68  sfcflx_sw_up => atmos_phy_rd_sflx_sw_up, &
69  sfcflx_sw_dn => atmos_phy_rd_sflx_sw_dn, &
70  tomflx_lw_up => atmos_phy_rd_tomflx_lw_up, &
71  tomflx_lw_dn => atmos_phy_rd_tomflx_lw_dn, &
72  tomflx_sw_up => atmos_phy_rd_tomflx_sw_up, &
73  tomflx_sw_dn => atmos_phy_rd_tomflx_sw_dn, &
74  sflx_rad_dn => atmos_phy_rd_sflx_down, &
75  solins => atmos_phy_rd_solins, &
76  cossza => atmos_phy_rd_cossza
77  implicit none
78 
79  namelist / param_atmos_phy_rd / &
80  rd_use_pbl_cloud
81 
82  integer :: ierr
83  !---------------------------------------------------------------------------
84 
85  log_newline
86  log_info("ATMOS_PHY_RD_driver_setup",*) 'Setup'
87 
88  if ( atmos_sw_phy_rd ) then
89 
90  !--- read namelist
91  rewind(io_fid_conf)
92  read(io_fid_conf,nml=param_atmos_phy_rd,iostat=ierr)
93  if( ierr < 0 ) then !--- missing
94  log_info("ATMOS_PHY_RD_driver_setup",*) 'Not found namelist. Default used.'
95  elseif( ierr > 0 ) then !--- fatal error
96  log_error("ATMOS_PHY_RD_driver_setup",*) 'Not appropriate names in namelist PARAM_ATMOS_PHY_RD. Check!'
97  call prc_abort
98  endif
99  log_nml(param_atmos_phy_rd)
100 
101  select case ( atmos_phy_rd_type )
102  case ( "MSTRNX" )
103  call atmos_phy_rd_mstrnx_setup( ka, ks, ke, cz(:), fz(:) )
104  case ( "OFFLINE" )
106  case default
107  log_error("ATMOS_PHY_RD_driver_setup",*) 'invalid Radiation type(', trim(atmos_phy_rd_type), '). CHECK!'
108  call prc_abort
109  end select
110 
111  else
112 
113  log_info("ATMOS_PHY_RD_driver_setup",*) 'this component is never called.'
114  log_info("ATMOS_PHY_RD_driver_setup",*) 'radiation fluxes are set to zero.'
115  !$acc kernels
116  sfcflx_lw_up(:,:) = 0.0_rp
117  sfcflx_lw_dn(:,:) = 0.0_rp
118  sfcflx_sw_up(:,:) = 0.0_rp
119  sfcflx_sw_dn(:,:) = 0.0_rp
120  tomflx_lw_up(:,:) = 0.0_rp
121  tomflx_lw_dn(:,:) = 0.0_rp
122  tomflx_sw_up(:,:) = 0.0_rp
123  tomflx_sw_dn(:,:) = 0.0_rp
124  sflx_rad_dn(:,:,:,:) = 0.0_rp
125  solins(:,:) = 0.0_rp
126  cossza(:,:) = 0.0_rp
127  !$acc end kernels
128 
129  endif
130 
131  return
132  end subroutine atmos_phy_rd_driver_setup
133 
134  !-----------------------------------------------------------------------------
139  use scale_atmos_phy_rd_profile, only: &
141  use mod_atmos_admin, only: &
144  implicit none
145  !---------------------------------------------------------------------------
146 
147  log_newline
148  log_info("ATMOS_PHY_RD_driver_finalize",*) 'Finalize'
149 
150  if ( atmos_sw_phy_rd ) then
151  select case ( atmos_phy_rd_type )
152  case ( "MSTRNX" )
154  case ( "OFFLINE" )
155  end select
156  end if
157 
159 
160  return
161  end subroutine atmos_phy_rd_driver_finalize
162 
163  !-----------------------------------------------------------------------------
165  subroutine atmos_phy_rd_driver_calc_tendency( update_flag )
166  use scale_const, only: &
167  eps => const_eps
168  use scale_atmos_grid_cartesc_real, only: &
169  real_cz => atmos_grid_cartesc_real_cz, &
170  real_fz => atmos_grid_cartesc_real_fz, &
171  real_lon => atmos_grid_cartesc_real_lon, &
172  real_lat => atmos_grid_cartesc_real_lat, &
175  use scale_landuse, only: &
176  fact_ocean => landuse_fact_ocean, &
177  fact_land => landuse_fact_land, &
178  fact_urban => landuse_fact_urban
179  use scale_time, only: &
180  time_nowdate, &
181  time_nowdaysec, &
183  use scale_statistics, only: &
185  statistics_total
186  use scale_file_history, only: &
187  file_history_in
188  use scale_atmos_hydrometeor, only: &
189  n_hyd, &
190  i_hc, &
191  i_hi
192  use scale_atmos_aerosol, only: &
193  n_ae
194  use mod_atmos_admin, only: &
196  use scale_atmos_solarins, only: &
197  solarins_insolation => atmos_solarins_insolation
198  use scale_atmos_phy_rd_mstrnx, only: &
200  use scale_atmos_phy_rd_offline, only: &
202  use scale_atmos_phy_rd_common, only: &
204  i_sw, &
205  i_lw, &
206  i_dn, &
207  i_up
208  use mod_atmos_vars, only: &
209  temp, &
210  pres, &
211  qv, &
212  cvtot, &
213  dens => dens_av, &
214  qtrc => qtrc_av, &
215  rhoh => rhoh_p
216  use mod_atmos_phy_sf_vars, only: &
217  sfc_temp => atmos_phy_sf_sfc_temp, &
218  sfc_albedo => atmos_phy_sf_sfc_albedo
219  use mod_atmos_phy_rd_vars, only: &
220  rhoh_rd => atmos_phy_rd_rhoh, &
221  sfcflx_lw_up => atmos_phy_rd_sflx_lw_up, &
222  sfcflx_lw_dn => atmos_phy_rd_sflx_lw_dn, &
223  sfcflx_sw_up => atmos_phy_rd_sflx_sw_up, &
224  sfcflx_sw_dn => atmos_phy_rd_sflx_sw_dn, &
225  tomflx_lw_up => atmos_phy_rd_tomflx_lw_up, &
226  tomflx_lw_dn => atmos_phy_rd_tomflx_lw_dn, &
227  tomflx_sw_up => atmos_phy_rd_tomflx_sw_up, &
228  tomflx_sw_dn => atmos_phy_rd_tomflx_sw_dn, &
229  sflx_rad_dn => atmos_phy_rd_sflx_down, &
230  solins => atmos_phy_rd_solins, &
231  cossza => atmos_phy_rd_cossza
232  use mod_atmos_phy_bl_vars, only: &
233  atmos_phy_bl_zi, &
234  atmos_phy_bl_ql, &
236  use mod_atmos_vars, only: &
237  atmos_vars_get_diagnostic
238  use mod_atmos_phy_mp_vars, only: &
240  use mod_atmos_phy_ae_vars, only: &
242  implicit none
243 
244  logical, intent(in) :: update_flag
245 
246  real(rp) :: temp_t (ka,ia,ja,3)
247  real(rp) :: flux_rad (ka,ia,ja,2,2,2)
248  real(rp) :: flux_rad_top( ia,ja,2,2,2)
249 
250  real(rp) :: dtau_s (ka,ia,ja) ! 0.67 micron cloud optical depth
251  real(rp) :: dem_s (ka,ia,ja) ! 10.5 micron cloud emissivity
252 
253  real(rp) :: flux_up (ka,ia,ja,2)
254  real(rp) :: flux_dn (ka,ia,ja,2)
255  real(rp) :: flux_net (ka,ia,ja,2)
256  real(rp) :: flux_net_sfc( ia,ja,2)
257  real(rp) :: flux_net_toa( ia,ja,2)
258  real(rp) :: flux_net_tom( ia,ja,2)
259 
260  real(rp) :: toaflx_lw_up(ia,ja)
261  real(rp) :: toaflx_lw_dn(ia,ja)
262  real(rp) :: toaflx_sw_up(ia,ja)
263  real(rp) :: toaflx_sw_dn(ia,ja)
264 
265  real(rp) :: sfcflx_lw_up_c(ia,ja)
266  real(rp) :: sfcflx_lw_dn_c(ia,ja)
267  real(rp) :: sfcflx_sw_up_c(ia,ja)
268  real(rp) :: sfcflx_sw_dn_c(ia,ja)
269  real(rp) :: toaflx_lw_up_c(ia,ja)
270  real(rp) :: toaflx_lw_dn_c(ia,ja)
271  real(rp) :: toaflx_sw_up_c(ia,ja)
272  real(rp) :: toaflx_sw_dn_c(ia,ja)
273  real(rp) :: tomflx_lw_up_c(ia,ja)
274  real(rp) :: tomflx_lw_dn_c(ia,ja)
275  real(rp) :: tomflx_sw_up_c(ia,ja)
276  real(rp) :: tomflx_sw_dn_c(ia,ja)
277 
278  real(rp) :: cldfrac(ka,ia,ja)
279  real(rp) :: mp_re (ka,ia,ja,n_hyd)
280  real(rp) :: mp_qe (ka,ia,ja,n_hyd)
281  real(rp) :: ae_re (ka,ia,ja,n_ae)
282  real(rp) :: ae_qe (ka,ia,ja,n_ae)
283 
284  real(rp) :: rh(ka,ia,ja)
285 
286  integer :: k, i, j
287  !---------------------------------------------------------------------------
288 
289  if ( update_flag ) then
290 
291  !$acc data create(TEMP_t,flux_rad,flux_rad_top,dtau_s,dem_s,flux_up,flux_dn,flux_net,flux_net_sfc,flux_net_toa,flux_net_tom,TOAFLX_LW_up,TOAFLX_LW_dn,TOAFLX_SW_up,TOAFLX_SW_dn,SFCFLX_LW_up_c,SFCFLX_LW_dn_c,SFCFLX_SW_up_c,SFCFLX_SW_dn_c,TOAFLX_LW_up_c,TOAFLX_LW_dn_c,TOAFLX_SW_up_c,TOAFLX_SW_dn_c,TOMFLX_LW_up_c,TOMFLX_LW_dn_c,TOMFLX_SW_up_c,TOMFLX_SW_dn_c,CLDFRAC,MP_Re,MP_Qe,AE_Re,AE_Qe,RH)
292 
293  call solarins_insolation( ia, is, ie, ja, js, je, &
294  real_lon(:,:), real_lat(:,:), & ! [IN]
295  time_nowdate(:), time_offset_year, & ! [IN]
296  solins(:,:), cossza(:,:) ) ! [OUT]
297 
299  dens(:,:,:), temp(:,:,:), qtrc(:,:,:,:), & ! [IN]
300  cldfrac=cldfrac, re=mp_re, qe=mp_qe ) ! [OUT]
301 
302  if ( rd_use_pbl_cloud ) then
303  !$omp parallel do
304  !$acc kernels
305  do j = js, je
306  do i = is, ie
307  do k = ks, ke
308  if ( real_cz(k,i,j) < atmos_phy_bl_zi(i,j) + real_fz(ks-1,i,j) ) then
309  cldfrac(k,i,j) = atmos_phy_bl_cldfrac(k,i,j)
310  if ( atmos_phy_bl_cldfrac(k,i,j) > eps ) then
311  mp_qe(k,i,j,i_hc) = atmos_phy_bl_ql(k,i,j) / atmos_phy_bl_cldfrac(k,i,j)
312  else
313  mp_qe(k,i,j,i_hc) = 0.0_rp
314  end if
315  mp_qe(k,i,j,i_hi) = 0.0_rp
316  mp_re(k,i,j,i_hc) = 8.0e-4
317  end if
318  end do
319  end do
320  end do
321  !$acc end kernels
322 
323  end if
324 
325  call atmos_vars_get_diagnostic( "RH", rh )
327  qtrc(:,:,:,:), rh(:,:,:), & ! [IN]
328  re=ae_re, qe=ae_qe ) ! [IN]
329 
330 
331  select case ( atmos_phy_rd_type )
332  case ( "MSTRNX" )
333 
335  ka, ks, ke, ia, is, ie, ja, js, je, &
336  dens(:,:,:), temp(:,:,:), pres(:,:,:), qv(:,:,:), & ! [IN]
337  real_cz(:,:,:), real_fz(:,:,:), & ! [IN]
338  fact_ocean(:,:), fact_land(:,:), fact_urban(:,:), & ! [IN]
339  sfc_temp(:,:), sfc_albedo(:,:,:,:), & ! [IN]
340  solins(:,:), cossza(:,:), & ! [IN]
341  cldfrac(:,:,:), mp_re(:,:,:,:), mp_qe(:,:,:,:), & ! [IN]
342  ae_re(:,:,:,:), ae_qe(:,:,:,:), & ! [IN]
343  flux_rad(:,:,:,:,:,:), & ! [OUT]
344  flux_rad_top(:,:,:,:,:), sflx_rad_dn(:,:,:,:), & ! [OUT]
345  dtau_s = dtau_s(:,:,:), dem_s = dem_s(:,:,:) ) ! [OUT]
346 
347  case ( "OFFLINE" )
348 
350  ka, ks, ke, ia, is, ie, ja, js, je, &
351  time_nowdaysec, & ! [IN]
352  flux_rad(:,:,:,:,:,2), & ! [OUT]
353  sflx_rad_dn(:,:,:,:) ) ! [OUT]
354  !$acc kernels
355  flux_rad(:,:,:,:,:,1) = 0.0_rp ! clear sky
356  flux_rad_top(:,:,:,:,:) = 0.0_rp
357  dtau_s(:,:,:) = 0.0_rp
358  dem_s(:,:,:) = 0.0_rp
359  !$acc end kernels
360 
361  end select
362 
363 
364  ! surface
365 !OCL XFILL
366  !$omp parallel do
367  !$acc kernels
368  do j = js, je
369  do i = is, ie
370  ! for clear-sky
371  sfcflx_lw_up_c(i,j) = flux_rad(ks-1,i,j,i_lw,i_up,1)
372  sfcflx_lw_dn_c(i,j) = flux_rad(ks-1,i,j,i_lw,i_dn,1)
373  sfcflx_sw_up_c(i,j) = flux_rad(ks-1,i,j,i_sw,i_up,1)
374  sfcflx_sw_dn_c(i,j) = flux_rad(ks-1,i,j,i_sw,i_dn,1)
375  ! for all-sky
376  sfcflx_lw_up(i,j) = flux_rad(ks-1,i,j,i_lw,i_up,2)
377  sfcflx_lw_dn(i,j) = flux_rad(ks-1,i,j,i_lw,i_dn,2)
378  sfcflx_sw_up(i,j) = flux_rad(ks-1,i,j,i_sw,i_up,2)
379  sfcflx_sw_dn(i,j) = flux_rad(ks-1,i,j,i_sw,i_dn,2)
380 
381  flux_net_sfc(i,j,i_lw) = sfcflx_lw_up(i,j) - sfcflx_lw_dn(i,j)
382  flux_net_sfc(i,j,i_sw) = sfcflx_sw_up(i,j) - sfcflx_sw_dn(i,j)
383  enddo
384  enddo
385  !$acc end kernels
386 
387  ! top of the atmosphere
388 !OCL XFILL
389  !$omp parallel do
390  !$acc kernels
391  do j = js, je
392  do i = is, ie
393  ! for clear-sky
394  toaflx_lw_up_c(i,j) = flux_rad_top(i,j,i_lw,i_up,1)
395  toaflx_lw_dn_c(i,j) = flux_rad_top(i,j,i_lw,i_dn,1)
396  toaflx_sw_up_c(i,j) = flux_rad_top(i,j,i_sw,i_up,1)
397  toaflx_sw_dn_c(i,j) = flux_rad_top(i,j,i_sw,i_dn,1)
398  ! for all-sky
399  toaflx_lw_up(i,j) = flux_rad_top(i,j,i_lw,i_up,2)
400  toaflx_lw_dn(i,j) = flux_rad_top(i,j,i_lw,i_dn,2)
401  toaflx_sw_up(i,j) = flux_rad_top(i,j,i_sw,i_up,2)
402  toaflx_sw_dn(i,j) = flux_rad_top(i,j,i_sw,i_dn,2)
403 
404  flux_net_toa(i,j,i_lw) = toaflx_lw_up(i,j) - toaflx_lw_dn(i,j)
405  flux_net_toa(i,j,i_sw) = toaflx_sw_up(i,j) - toaflx_sw_dn(i,j)
406  enddo
407  enddo
408  !$acc end kernels
409 
410  ! top of the model
411 !OCL XFILL
412  !$omp parallel do
413  !$acc kernels
414  do j = js, je
415  do i = is, ie
416  ! for clear-sky
417  tomflx_lw_up_c(i,j) = flux_rad(ke,i,j,i_lw,i_up,1)
418  tomflx_lw_dn_c(i,j) = flux_rad(ke,i,j,i_lw,i_dn,1)
419  tomflx_sw_up_c(i,j) = flux_rad(ke,i,j,i_sw,i_up,1)
420  tomflx_sw_dn_c(i,j) = flux_rad(ke,i,j,i_sw,i_dn,1)
421  ! for all-sky
422  tomflx_lw_up(i,j) = flux_rad(ke,i,j,i_lw,i_up,2)
423  tomflx_lw_dn(i,j) = flux_rad(ke,i,j,i_lw,i_dn,2)
424  tomflx_sw_up(i,j) = flux_rad(ke,i,j,i_sw,i_up,2)
425  tomflx_sw_dn(i,j) = flux_rad(ke,i,j,i_sw,i_dn,2)
426 
427  flux_net_tom(i,j,i_lw) = tomflx_lw_up(i,j) - tomflx_lw_dn(i,j)
428  flux_net_tom(i,j,i_sw) = tomflx_sw_up(i,j) - tomflx_sw_dn(i,j)
429  enddo
430  enddo
431  !$acc end kernels
432 
433 !OCL XFILL
434  !$omp parallel do collapse(2)
435  !$acc kernels
436  do j = js, je
437  do i = is, ie
438  do k = ks, ke
439  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) )
440  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) )
441  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) )
442  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) )
443 
444  flux_net(k,i,j,i_lw) = flux_up(k,i,j,i_lw) - flux_dn(k,i,j,i_lw)
445  flux_net(k,i,j,i_sw) = flux_up(k,i,j,i_sw) - flux_dn(k,i,j,i_sw)
446  enddo
447  enddo
448  enddo
449  !$acc end kernels
450 
451  ! apply radiative flux convergence -> heating rate
453  ka, ks, ke, ia, is, ie, ja, js, je, &
454  flux_rad(:,:,:,:,:,2), & ! [IN]
455  dens(:,:,:), temp(:,:,:), & ! [IN]
456  cvtot(:,:,:), & ! [IN]
457  real_fz(:,:,:), & ! [IN]
458  rhoh_rd(:,:,:), & ! [OUT]
459  temp_t = temp_t(:,:,:,:) ) ! [OUT]
460 
461 
462 
463  call file_history_in( solins(:,:), 'SOLINS', 'solar insolation', 'W/m2', fill_halo=.true. )
464  call file_history_in( cossza(:,:), 'COSZ', 'cos(solar zenith angle)', '1', fill_halo=.true. )
465 
466  call file_history_in( sfcflx_lw_up_c(:,:), 'SFLX_LW_up_c', 'SFC upward longwave radiation flux (clr)', 'W/m2', fill_halo=.true. )
467  call file_history_in( sfcflx_lw_dn_c(:,:), 'SFLX_LW_dn_c', 'SFC downward longwave radiation flux (clr)', 'W/m2', fill_halo=.true. )
468  call file_history_in( sfcflx_sw_up_c(:,:), 'SFLX_SW_up_c', 'SFC upward shortwave radiation flux (clr)', 'W/m2', fill_halo=.true. )
469  call file_history_in( sfcflx_sw_dn_c(:,:), 'SFLX_SW_dn_c', 'SFC downward shortwave radiation flux (clr)', 'W/m2', fill_halo=.true. )
470 
471  call file_history_in( sfcflx_lw_up(:,:), 'SFLX_LW_up', 'SFC upward longwave radiation flux', 'W/m2', fill_halo=.true. )
472  call file_history_in( sfcflx_lw_dn(:,:), 'SFLX_LW_dn', 'SFC downward longwave radiation flux', 'W/m2', fill_halo=.true. )
473  call file_history_in( sfcflx_sw_up(:,:), 'SFLX_SW_up', 'SFC upward shortwave radiation flux', 'W/m2', fill_halo=.true. )
474  call file_history_in( sfcflx_sw_dn(:,:), 'SFLX_SW_dn', 'SFC downward shortwave radiation flux', 'W/m2', fill_halo=.true. )
475 
476  call file_history_in( flux_net_sfc(:,:,i_lw), 'SFLX_LW_net', 'SFC net longwave radiation flux', 'W/m2', fill_halo=.true. )
477  call file_history_in( flux_net_sfc(:,:,i_sw), 'SFLX_SW_net', 'SFC net shortwave radiation flux', 'W/m2', fill_halo=.true. )
478 
479  call file_history_in( toaflx_lw_up_c(:,:), 'TOAFLX_LW_up_c', 'TOA upward longwave radiation flux (clr)', 'W/m2', fill_halo=.true. )
480  call file_history_in( toaflx_lw_dn_c(:,:), 'TOAFLX_LW_dn_c', 'TOA downward longwave radiation flux (clr)', 'W/m2', fill_halo=.true. )
481  call file_history_in( toaflx_sw_up_c(:,:), 'TOAFLX_SW_up_c', 'TOA upward shortwave radiation flux (clr)', 'W/m2', fill_halo=.true. )
482  call file_history_in( toaflx_sw_dn_c(:,:), 'TOAFLX_SW_dn_c', 'TOA downward shortwave radiation flux (clr)', 'W/m2', fill_halo=.true. )
483 
484  call file_history_in( toaflx_lw_up(:,:), 'TOAFLX_LW_up', 'TOA upward longwave radiation flux', 'W/m2', fill_halo=.true. )
485  call file_history_in( toaflx_lw_dn(:,:), 'TOAFLX_LW_dn', 'TOA downward longwave radiation flux', 'W/m2', fill_halo=.true. )
486  call file_history_in( toaflx_sw_up(:,:), 'TOAFLX_SW_up', 'TOA upward shortwave radiation flux', 'W/m2', fill_halo=.true. )
487  call file_history_in( toaflx_sw_dn(:,:), 'TOAFLX_SW_dn', 'TOA downward shortwave radiation flux', 'W/m2', fill_halo=.true. )
488 
489  call file_history_in( flux_net_toa(:,:,i_lw), 'TOAFLX_LW_net', 'TOA net longwave radiation flux', 'W/m2', fill_halo=.true. )
490  call file_history_in( flux_net_toa(:,:,i_sw), 'TOAFLX_SW_net', 'TOA net shortwave radiation flux', 'W/m2', fill_halo=.true. )
491 
492  call file_history_in( tomflx_lw_up_c(:,:), 'TOMFLX_LW_up_c', 'TOM upward longwave radiation flux (clr)', 'W/m2', fill_halo=.true. )
493  call file_history_in( tomflx_lw_dn_c(:,:), 'TOMFLX_LW_dn_c', 'TOM downward longwave radiation flux (clr)', 'W/m2', fill_halo=.true. )
494  call file_history_in( tomflx_sw_up_c(:,:), 'TOMFLX_SW_up_c', 'TOM upward shortwave radiation flux (clr)', 'W/m2', fill_halo=.true. )
495  call file_history_in( tomflx_sw_dn_c(:,:), 'TOMFLX_SW_dn_c', 'TOM downward shortwave radiation flux (clr)', 'W/m2', fill_halo=.true. )
496 
497  call file_history_in( tomflx_lw_up(:,:), 'TOMFLX_LW_up', 'TOM upward longwave radiation flux', 'W/m2', fill_halo=.true. )
498  call file_history_in( tomflx_lw_dn(:,:), 'TOMFLX_LW_dn', 'TOM downward longwave radiation flux', 'W/m2', fill_halo=.true. )
499  call file_history_in( tomflx_sw_up(:,:), 'TOMFLX_SW_up', 'TOM upward shortwave radiation flux', 'W/m2', fill_halo=.true. )
500  call file_history_in( tomflx_sw_dn(:,:), 'TOMFLX_SW_dn', 'TOM downward shortwave radiation flux', 'W/m2', fill_halo=.true. )
501 
502  call file_history_in( flux_net_tom(:,:,i_lw), 'TOMFLX_LW_net', 'TOM net longwave radiation flux', 'W/m2', fill_halo=.true. )
503  call file_history_in( flux_net_tom(:,:,i_sw), 'TOMFLX_SW_net', 'TOM net shortwave radiation flux', 'W/m2', fill_halo=.true. )
504 
505  call file_history_in( flux_net_sfc(:,:,i_lw), 'SLR', 'SFC net longwave radiation flux', 'W/m2', fill_halo=.true. )
506  call file_history_in( flux_net_sfc(:,:,i_sw), 'SSR', 'SFC net shortwave radiation flux', 'W/m2', fill_halo=.true. )
507  call file_history_in( toaflx_lw_up(:,:), 'OLR', 'outgoing longwave radiation flux', 'W/m2', fill_halo=.true. )
508  call file_history_in( toaflx_sw_up(:,:), 'OSR', 'outgoing shortwave radiation flux', 'W/m2', fill_halo=.true. )
509 
510  call file_history_in( flux_up(:,:,:,i_lw), 'RADFLUX_LWUP', 'upward longwave radiation flux', 'W/m2', fill_halo=.true. )
511  call file_history_in( flux_dn(:,:,:,i_lw), 'RADFLUX_LWDN', 'downward longwave radiation flux', 'W/m2', fill_halo=.true. )
512  call file_history_in( flux_net(:,:,:,i_lw), 'RADFLUX_LW', 'net longwave radiation flux', 'W/m2', fill_halo=.true. )
513  call file_history_in( flux_up(:,:,:,i_sw), 'RADFLUX_SWUP', 'upward shortwave radiation flux', 'W/m2', fill_halo=.true. )
514  call file_history_in( flux_dn(:,:,:,i_sw), 'RADFLUX_SWDN', 'downward shortwave radiation flux', 'W/m2', fill_halo=.true. )
515  call file_history_in( flux_net(:,:,:,i_sw), 'RADFLUX_SW', 'net shortwave radiation flux', 'W/m2', fill_halo=.true. )
516 
517  call file_history_in( sflx_rad_dn(:,:,i_r_direct ,i_r_ir ), 'SFLX_IR_dn_dir', 'SFC downward radiation flux (direct; IR)', 'W/m2', fill_halo=.true. )
518  call file_history_in( sflx_rad_dn(:,:,i_r_diffuse,i_r_ir ), 'SFLX_IR_dn_dif', 'SFC downward radiation flux (diffuse; IR)', 'W/m2', fill_halo=.true. )
519  call file_history_in( sflx_rad_dn(:,:,i_r_direct ,i_r_nir), 'SFLX_NIR_dn_dir', 'SFC downward radiation flux (direct; NIR)', 'W/m2', fill_halo=.true. )
520  call file_history_in( sflx_rad_dn(:,:,i_r_diffuse,i_r_nir), 'SFLX_NIR_dn_dif', 'SFC downward radiation flux (diffuse; NIR)', 'W/m2', fill_halo=.true. )
521  call file_history_in( sflx_rad_dn(:,:,i_r_direct ,i_r_vis), 'SFLX_VIS_dn_dir', 'SFC downward radiation flux (direct; VIS)', 'W/m2', fill_halo=.true. )
522  call file_history_in( sflx_rad_dn(:,:,i_r_diffuse,i_r_vis), 'SFLX_VIS_dn_dif', 'SFC downward radiation flux (diffuse; VIS)', 'W/m2', fill_halo=.true. )
523 
524  call file_history_in( temp_t(:,:,:,i_lw), 'TEMP_t_rd_LW', 'tendency of temp in rd(LW)', 'K/day', fill_halo=.true. )
525  call file_history_in( temp_t(:,:,:,i_sw), 'TEMP_t_rd_SW', 'tendency of temp in rd(SW)', 'K/day', fill_halo=.true. )
526  call file_history_in( temp_t(:,:,:,3 ), 'TEMP_t_rd', 'tendency of temp in rd', 'K/day', fill_halo=.true. )
527  call file_history_in( rhoh_rd(:,:,:), 'RHOH_RD', 'diabatic heating rate in rd', 'J/m3/s', fill_halo=.true. )
528 
529  ! output of raw data, for offline output
530  call file_history_in( flux_rad(:,:,:,i_lw,i_up,2), 'RFLX_LW_up', 'upward longwave radiation flux (cell face)', 'W/m2', fill_halo=.true. )
531  call file_history_in( flux_rad(:,:,:,i_lw,i_dn,2), 'RFLX_LW_dn', 'downward longwave radiation flux (cell face)', 'W/m2', fill_halo=.true. )
532  call file_history_in( flux_rad(:,:,:,i_sw,i_up,2), 'RFLX_SW_up', 'upward shortwave radiation flux (cell face)', 'W/m2', fill_halo=.true. )
533  call file_history_in( flux_rad(:,:,:,i_sw,i_dn,2), 'RFLX_SW_dn', 'downward shortwave radiation flux (cell face)', 'W/m2', fill_halo=.true. )
534 
535  call file_history_in( dtau_s(:,:,:), 'dtau_s', '0.67 micron cloud optical depth', '1', fill_halo=.true. )
536  call file_history_in( dem_s(:,:,:), 'dem_s', '10.5 micron cloud emissivity', '1', fill_halo=.true. )
537 
538  !$acc end data
539 
540  endif
541 
542  !$acc kernels
543  do j = js, je
544  do i = is, ie
545  do k = ks, ke
546  rhoh(k,i,j) = rhoh(k,i,j) + rhoh_rd(k,i,j)
547  enddo
548  enddo
549  enddo
550  !$acc end kernels
551 
552  if ( statistics_checktotal ) then
553  call statistics_total( ka, ks, ke, ia, is, ie, ja, js, je, &
554  rhoh_rd(:,:,:), 'RHOH_RD', &
557  endif
558 
559  return
560  end subroutine atmos_phy_rd_driver_calc_tendency
561 
562 end module mod_atmos_phy_rd_driver
mod_atmos_phy_rd_vars::atmos_phy_rd_sflx_down
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_rd_sflx_down
Definition: mod_atmos_phy_rd_vars.F90:72
scale_statistics
module Statistics
Definition: scale_statistics.F90:11
mod_atmos_phy_mp_vars
module Atmosphere / Physics Cloud Microphysics
Definition: mod_atmos_phy_mp_vars.F90:12
scale_landuse::landuse_fact_ocean
real(rp), dimension(:,:), allocatable, public landuse_fact_ocean
ocean factor
Definition: scale_landuse.F90:45
scale_atmos_grid_cartesc_index::ke
integer, public ke
end point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:52
scale_time::time_nowdaysec
real(dp), public time_nowdaysec
second of current time [sec]
Definition: scale_time.F90:72
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:350
mod_atmos_phy_rd_vars::atmos_phy_rd_rhoh
real(rp), dimension(:,:,:), allocatable, public atmos_phy_rd_rhoh
Definition: mod_atmos_phy_rd_vars.F90:58
scale_cpl_sfc_index::i_r_direct
integer, parameter, public i_r_direct
Definition: scale_cpl_sfc_index.F90:37
mod_atmos_phy_mp_vars::atmos_phy_mp_vars_get_diagnostic
subroutine, public atmos_phy_mp_vars_get_diagnostic(DENS, TEMP, QTRC, CLDFRAC, Re, Qe, Ne)
Definition: mod_atmos_phy_mp_vars.F90:629
scale_atmos_phy_rd_offline::atmos_phy_rd_offline_flux
subroutine, public atmos_phy_rd_offline_flux(KA, KS, KE, IA, IS, IE, JA, JS, JE, time_now, flux_rad, SFLX_rad_dn)
Radiation main.
Definition: scale_atmos_phy_rd_offline.F90:187
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_cz
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_cz
geopotential height [m] (zxy)
Definition: scale_atmos_grid_cartesC_real.F90:39
mod_atmos_vars::qtrc_av
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
Definition: mod_atmos_vars.F90:95
scale_cpl_sfc_index::i_r_diffuse
integer, parameter, public i_r_diffuse
Definition: scale_cpl_sfc_index.F90:38
scale_atmos_phy_rd_offline::atmos_phy_rd_offline_setup
subroutine, public atmos_phy_rd_offline_setup
Setup.
Definition: scale_atmos_phy_rd_offline.F90:58
mod_atmos_admin::atmos_phy_rd_type
character(len=h_short), public atmos_phy_rd_type
Definition: mod_atmos_admin.F90:39
scale_atmos_phy_rd_common::atmos_phy_rd_calc_heating
subroutine, public atmos_phy_rd_calc_heating(KA, KS, KE, IA, IS, IE, JA, JS, JE, flux_rad, DENS, TEMP, CVtot, FZ, RHOH, TEMP_t)
Calc heating rate.
Definition: scale_atmos_phy_rd_common.F90:60
scale_precision
module PRECISION
Definition: scale_precision.F90:14
scale_atmos_grid_cartesc_index::ka
integer, public ka
Definition: scale_atmos_grid_cartesC_index.F90:47
mod_atmos_phy_bl_vars::atmos_phy_bl_zi
real(rp), dimension(:,:), allocatable, public atmos_phy_bl_zi
Definition: mod_atmos_phy_bl_vars.F90:67
mod_atmos_admin
module ATMOS admin
Definition: mod_atmos_admin.F90:11
mod_atmos_phy_ae_vars::atmos_phy_ae_vars_get_diagnostic
subroutine, public atmos_phy_ae_vars_get_diagnostic(QTRC, RH, Re, Qe)
Definition: mod_atmos_phy_ae_vars.F90:515
scale_atmos_aerosol::n_ae
integer, parameter, public n_ae
Definition: scale_atmos_aerosol.F90:33
mod_atmos_phy_rd_vars::atmos_phy_rd_tomflx_lw_dn
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_tomflx_lw_dn
Definition: mod_atmos_phy_rd_vars.F90:68
scale_atmos_phy_rd_common::i_dn
integer, parameter, public i_dn
Definition: scale_atmos_phy_rd_common.F90:35
scale_atmos_phy_rd_common::i_lw
integer, parameter, public i_lw
Definition: scale_atmos_phy_rd_common.F90:37
scale_atmos_phy_rd_offline
module atmosphere / physics / radiation / offline
Definition: scale_atmos_phy_rd_offline.F90:13
scale_cpl_sfc_index::i_r_ir
integer, parameter, public i_r_ir
Definition: scale_cpl_sfc_index.F90:29
mod_atmos_phy_rd_vars::atmos_phy_rd_cossza
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_cossza
Definition: mod_atmos_phy_rd_vars.F90:75
scale_const::const_eps
real(rp), public const_eps
small number
Definition: scale_const.F90:35
scale_atmos_phy_rd_common::i_up
integer, parameter, public i_up
Definition: scale_atmos_phy_rd_common.F90:34
scale_atmos_hydrometeor
module atmosphere / hydrometeor
Definition: scale_atmos_hydrometeor.F90:12
mod_atmos_phy_rd_vars
module Atmosphere / Physics Radiation
Definition: mod_atmos_phy_rd_vars.F90:12
scale_atmos_phy_rd_mstrnx::atmos_phy_rd_mstrnx_finalize
subroutine, public atmos_phy_rd_mstrnx_finalize
finalize
Definition: scale_atmos_phy_rd_mstrnx.F90:441
mod_atmos_phy_sf_vars
module ATMOSPHERIC Surface Variables
Definition: mod_atmos_phy_sf_vars.F90:12
mod_atmos_phy_rd_vars::atmos_phy_rd_tomflx_sw_up
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_tomflx_sw_up
Definition: mod_atmos_phy_rd_vars.F90:69
scale_atmos_solarins
module atmosphere / SOLARINS
Definition: scale_atmos_solarins.F90:14
scale_atmos_grid_cartesc_real
module Atmosphere GRID CartesC Real(real space)
Definition: scale_atmos_grid_cartesC_real.F90:11
mod_atmos_phy_sf_vars::atmos_phy_sf_sfc_temp
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sfc_temp
Definition: mod_atmos_phy_sf_vars.F90:65
mod_atmos_vars::qtrc
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
Definition: mod_atmos_vars.F90:81
scale_file_history
module file_history
Definition: scale_file_history.F90:15
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lon
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lon
longitude [rad,0-2pi]
Definition: scale_atmos_grid_cartesC_real.F90:49
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_precision::rp
integer, parameter, public rp
Definition: scale_precision.F90:41
scale_atmos_hydrometeor::i_hi
integer, parameter, public i_hi
ice water cloud
Definition: scale_atmos_hydrometeor.F90:99
scale_atmos_grid_cartesc_index::ie
integer, public ie
end point of inner domain: x, local
Definition: scale_atmos_grid_cartesC_index.F90:54
scale_io
module STDIO
Definition: scale_io.F90:10
mod_atmos_phy_rd_vars::atmos_phy_rd_sflx_lw_dn
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_lw_dn
Definition: mod_atmos_phy_rd_vars.F90:62
mod_atmos_phy_bl_vars
module atmosphere / physics / PBL
Definition: mod_atmos_phy_bl_vars.F90:12
mod_atmos_phy_rd_vars::atmos_phy_rd_sflx_sw_dn
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_sw_dn
Definition: mod_atmos_phy_rd_vars.F90:64
mod_atmos_vars::dens
real(rp), dimension(:,:,:), allocatable, target, public dens
Definition: mod_atmos_vars.F90:76
scale_cpl_sfc_index::i_r_nir
integer, parameter, public i_r_nir
Definition: scale_cpl_sfc_index.F90:30
scale_tracer::k
real(rp), public k
Definition: scale_tracer.F90:45
scale_atmos_grid_cartesc_index
module atmosphere / grid / cartesC index
Definition: scale_atmos_grid_cartesC_index.F90:12
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_atmos_grid_cartesc_index::ia
integer, public ia
Definition: scale_atmos_grid_cartesC_index.F90:48
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_vol
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_vol
control volume (zxy) [m3]
Definition: scale_atmos_grid_cartesC_real.F90:84
mod_atmos_phy_rd_vars::atmos_phy_rd_sflx_sw_up
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_sw_up
Definition: mod_atmos_phy_rd_vars.F90:63
mod_atmos_phy_rd_vars::atmos_phy_rd_sflx_lw_up
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_lw_up
Definition: mod_atmos_phy_rd_vars.F90:61
mod_atmos_phy_sf_vars::atmos_phy_sf_sfc_albedo
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_sf_sfc_albedo
Definition: mod_atmos_phy_sf_vars.F90:66
scale_atmos_phy_rd_mstrnx::atmos_phy_rd_mstrnx_setup
subroutine, public atmos_phy_rd_mstrnx_setup(KA, KS, KE, CZ, FZ)
Setup.
Definition: scale_atmos_phy_rd_mstrnx.F90:222
scale_prof
module profiler
Definition: scale_prof.F90:11
mod_atmos_phy_rd_vars::atmos_phy_rd_tomflx_sw_dn
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_tomflx_sw_dn
Definition: mod_atmos_phy_rd_vars.F90:70
scale_atmos_grid_cartesc_index::is
integer, public is
start point of inner domain: x, local
Definition: scale_atmos_grid_cartesC_index.F90:53
mod_atmos_vars::temp
real(rp), dimension(:,:,:), allocatable, target, public temp
Definition: mod_atmos_vars.F90:134
scale_atmos_grid_cartesc_index::ja
integer, public ja
Definition: scale_atmos_grid_cartesC_index.F90:49
scale_time
module TIME
Definition: scale_time.F90:11
mod_atmos_vars::qv
real(rp), dimension(:,:,:), allocatable, pointer, target, public qv
Definition: mod_atmos_vars.F90:97
scale_atmos_hydrometeor::i_hc
integer, parameter, public i_hc
liquid water cloud
Definition: scale_atmos_hydrometeor.F90:97
scale_tracer
module TRACER
Definition: scale_tracer.F90:12
scale_atmos_aerosol
module atmosphere / aerosol
Definition: scale_atmos_aerosol.F90:12
mod_atmos_phy_rd_driver
module ATMOSPHERE / Physics Radiation
Definition: mod_atmos_phy_rd_driver.F90:12
mod_atmos_vars::pres
real(rp), dimension(:,:,:), allocatable, target, public pres
Definition: mod_atmos_vars.F90:135
mod_atmos_admin::atmos_sw_phy_rd
logical, public atmos_sw_phy_rd
Definition: mod_atmos_admin.F90:55
mod_atmos_vars::dens_av
real(rp), dimension(:,:,:), pointer, public dens_av
Definition: mod_atmos_vars.F90:90
scale_atmos_phy_rd_common::i_sw
integer, parameter, public i_sw
Definition: scale_atmos_phy_rd_common.F90:38
scale_landuse::landuse_fact_land
real(rp), dimension(:,:), allocatable, public landuse_fact_land
land factor
Definition: scale_landuse.F90:46
mod_atmos_phy_rd_vars::atmos_phy_rd_tomflx_lw_up
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_tomflx_lw_up
Definition: mod_atmos_phy_rd_vars.F90:67
scale_atmos_grid_cartesc_index::ks
integer, public ks
start point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:51
scale_atmos_phy_rd_profile::atmos_phy_rd_profile_finalize
subroutine, public atmos_phy_rd_profile_finalize
finalize
Definition: scale_atmos_phy_rd_profile.F90:201
mod_atmos_vars::rhoh_p
real(rp), dimension(:,:,:), allocatable, public rhoh_p
Definition: mod_atmos_vars.F90:120
scale_atmos_grid_cartesc::atmos_grid_cartesc_fz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fz
face coordinate [m]: z, local
Definition: scale_atmos_grid_cartesC.F90:42
scale_statistics::statistics_checktotal
logical, public statistics_checktotal
calc&report variable totals to logfile?
Definition: scale_statistics.F90:109
mod_atmos_vars
module ATMOSPHERIC Variables
Definition: mod_atmos_vars.F90:12
scale_cpl_sfc_index
module coupler / surface-atmospehre
Definition: scale_cpl_sfc_index.F90:11
scale_time::time_nowdate
integer, dimension(6), public time_nowdate
current time [YYYY MM DD HH MM SS]
Definition: scale_time.F90:68
scale_atmos_grid_cartesc_index::js
integer, public js
start point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:55
scale_cpl_sfc_index::i_r_vis
integer, parameter, public i_r_vis
Definition: scale_cpl_sfc_index.F90:31
mod_atmos_phy_ae_vars
module ATMOSPHERE / Physics Aerosol Microphysics
Definition: mod_atmos_phy_ae_vars.F90:12
mod_atmos_phy_rd_driver::atmos_phy_rd_driver_finalize
subroutine, public atmos_phy_rd_driver_finalize
finalize
Definition: mod_atmos_phy_rd_driver.F90:137
scale_atmos_phy_rd_common
module atmosphere / physics / radiation / common
Definition: scale_atmos_phy_rd_common.F90:12
scale_landuse::landuse_fact_urban
real(rp), dimension(:,:), allocatable, public landuse_fact_urban
urban factor
Definition: scale_landuse.F90:47
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lat
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lat
latitude [rad,-pi,pi]
Definition: scale_atmos_grid_cartesC_real.F90:53
mod_atmos_phy_rd_driver::atmos_phy_rd_driver_setup
subroutine, public atmos_phy_rd_driver_setup
Setup.
Definition: mod_atmos_phy_rd_driver.F90:53
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_fz
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fz
geopotential height [m] (wxy)
Definition: scale_atmos_grid_cartesC_real.F90:43
mod_atmos_phy_rd_vars::atmos_phy_rd_solins
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_solins
Definition: mod_atmos_phy_rd_vars.F90:74
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totvol
real(rp), public atmos_grid_cartesc_real_totvol
total volume (zxy, local) [m3]
Definition: scale_atmos_grid_cartesC_real.F90:88
mod_atmos_phy_bl_vars::atmos_phy_bl_cldfrac
real(rp), dimension(:,:,:), allocatable, public atmos_phy_bl_cldfrac
Definition: mod_atmos_phy_bl_vars.F90:71
scale_atmos_grid_cartesc
module atmosphere / grid / cartesC
Definition: scale_atmos_grid_cartesC.F90:12
scale_landuse
module LANDUSE
Definition: scale_landuse.F90:19
scale_atmos_grid_cartesc::atmos_grid_cartesc_cz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cz
center coordinate [m]: z, local
Definition: scale_atmos_grid_cartesC.F90:41
scale_atmos_phy_rd_mstrnx::atmos_phy_rd_mstrnx_flux
subroutine, public atmos_phy_rd_mstrnx_flux(KA, KS, KE, IA, IS, IE, JA, JS, JE, DENS, TEMP, PRES, QV, CZ, FZ, fact_ocean, fact_land, fact_urban, temp_sfc, albedo_sfc, solins, cosSZA, CLDFRAC, MP_Re, MP_Qe, AE_Re, AE_Qe, flux_rad, flux_rad_top, flux_rad_sfc_dn, dtau_s, dem_s)
Radiation main.
Definition: scale_atmos_phy_rd_mstrnx.F90:514
mod_atmos_phy_bl_vars::atmos_phy_bl_ql
real(rp), dimension(:,:,:), allocatable, public atmos_phy_bl_ql
Definition: mod_atmos_phy_bl_vars.F90:70
scale_io::io_fid_conf
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:57
scale_atmos_grid_cartesc_index::je
integer, public je
end point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:56
scale_atmos_hydrometeor::n_hyd
integer, parameter, public n_hyd
Definition: scale_atmos_hydrometeor.F90:95
mod_atmos_phy_rd_driver::atmos_phy_rd_driver_calc_tendency
subroutine, public atmos_phy_rd_driver_calc_tendency(update_flag)
Driver.
Definition: mod_atmos_phy_rd_driver.F90:166
mod_atmos_vars::cvtot
real(rp), dimension(:,:,:), allocatable, target, public cvtot
Definition: mod_atmos_vars.F90:142
scale_time::time_offset_year
integer, public time_offset_year
time offset [year]
Definition: scale_time.F90:76
scale_atmos_phy_rd_mstrnx
module atmosphere / physics / radiation / mstrnX
Definition: scale_atmos_phy_rd_mstrnx.F90:15
scale_atmos_phy_rd_profile
module atmosphere / physics/ radiation / profile
Definition: scale_atmos_phy_rd_profile.F90:15