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_process, only: &
130  use scale_const, only: &
131  pre00 => const_pre00, &
132  rdry => const_rdry, &
133  cpdry => const_cpdry
134  use scale_landuse, only: &
138  use scale_time, only: &
139  dt_rd => time_dtsec_atmos_phy_rd, &
140  time_nowdate, &
142  use scale_rm_statistics, only: &
144  stat_total
145  use scale_history, only: &
146  hist_in
147  use mod_atmos_admin, only: &
149  use scale_atmos_solarins, only: &
150  solarins_insolation => atmos_solarins_insolation
151  use scale_atmos_phy_rd, only: &
153  use scale_atmos_phy_rd_mm5sw, only: &
154  swrad
155  use scale_atmos_phy_rd_common, only: &
156  rd_heating => atmos_phy_rd_heating, &
157  i_sw, &
158  i_lw, &
159  i_dn, &
160  i_up, &
161  i_direct, &
162  i_diffuse
163  use scale_atmos_hydrometeor, only: &
164  i_qv, &
165  i_qc, &
166  i_qr, &
167  i_qi, &
168  i_qs, &
169  i_qg
170  use mod_atmos_vars, only: &
171  temp, &
172  pres, &
173  dens => dens_av, &
174  rhot => rhot_av, &
175  qtrc => qtrc_av, &
176  rhot_t => rhot_tp
177  use mod_atmos_phy_sf_vars, only: &
178  sfc_temp => atmos_phy_sf_sfc_temp, &
179  sfc_albedo => atmos_phy_sf_sfc_albedo
180  use mod_atmos_phy_rd_vars, only: &
181  rhot_t_rd => atmos_phy_rd_rhot_t, &
182  sfcflx_lw_up => atmos_phy_rd_sflx_lw_up, &
183  sfcflx_lw_dn => atmos_phy_rd_sflx_lw_dn, &
184  sfcflx_sw_up => atmos_phy_rd_sflx_sw_up, &
185  sfcflx_sw_dn => atmos_phy_rd_sflx_sw_dn, &
186  toaflx_lw_up => atmos_phy_rd_toaflx_lw_up, &
187  toaflx_lw_dn => atmos_phy_rd_toaflx_lw_dn, &
188  toaflx_sw_up => atmos_phy_rd_toaflx_sw_up, &
189  toaflx_sw_dn => atmos_phy_rd_toaflx_sw_dn, &
190  sflx_rad_dn => atmos_phy_rd_sflx_downall, &
191  solins => atmos_phy_rd_solins, &
192  cossza => atmos_phy_rd_cossza
193  implicit none
194 
195  logical, intent(in) :: update_flag
196 
197  real(RP) :: temp_t (ka,ia,ja,3)
198  real(RP) :: flux_rad (ka,ia,ja,2,2,2)
199  real(RP) :: flux_rad_top( ia,ja,2,2,2)
200 
201  real(RP) :: flux_up (ka,ia,ja,2)
202  real(RP) :: flux_dn (ka,ia,ja,2)
203  real(RP) :: flux_net (ka,ia,ja,2)
204  real(RP) :: flux_net_toa( ia,ja,2)
205  real(RP) :: flux_net_sfc( ia,ja,2)
206 
207  real(RP) :: sfcflx_lw_up_c(ia,ja)
208  real(RP) :: sfcflx_lw_dn_c(ia,ja)
209  real(RP) :: sfcflx_sw_up_c(ia,ja)
210  real(RP) :: sfcflx_sw_dn_c(ia,ja)
211  real(RP) :: toaflx_lw_up_c(ia,ja)
212  real(RP) :: toaflx_lw_dn_c(ia,ja)
213  real(RP) :: toaflx_sw_up_c(ia,ja)
214  real(RP) :: toaflx_sw_dn_c(ia,ja)
215 
216  ! for WRF radiation scheme added by Adachi; array order is (i,k,j)
217  real(RP) :: rthratensw(ia,ka,ja)
218  real(RP) :: sdown3d (ia,ka,ja) ! downward short wave flux (W/m2)
219  real(RP) :: gsw (ia,ja) ! net short wave flux at ground surface (W/m2)
220  real(RP) :: rho3d (ia,ka,ja)
221  real(RP) :: t3d (ia,ka,ja)
222  real(RP) :: p3d (ia,ka,ja)
223  real(RP) :: pi3d (ia,ka,ja)
224  real(RP) :: dz8w (ia,ka,ja)
225  real(RP) :: qv3d (ia,ka,ja)
226  real(RP) :: qc3d (ia,ka,ja)
227  real(RP) :: qr3d (ia,ka,ja)
228  real(RP) :: qi3d (ia,ka,ja)
229  real(RP) :: qs3d (ia,ka,ja)
230  real(RP) :: qg3d (ia,ka,ja)
231  real(RP) :: flux_rad_org(ka,ia,ja,2,2,2)
232 
233  real(RP) :: total ! dummy
234 
235  integer :: k, i, j
236  !---------------------------------------------------------------------------
237 
238  if ( update_flag ) then
239 
240  call solarins_insolation( solins(:,:), & ! [OUT]
241  cossza(:,:), & ! [OUT]
242  real_lon(:,:), & ! [IN]
243  real_lat(:,:), & ! [IN]
244  time_nowdate(:), & ! [IN]
245  time_offset_year ) ! [IN]
246 
247 
248  call atmos_phy_rd( dens, rhot, qtrc, & ! [IN]
249  real_cz, real_fz, & ! [IN]
250  landuse_fact_ocean, & ! [IN]
251  landuse_fact_land, & ! [IN]
252  landuse_fact_urban, & ! [IN]
253  sfc_temp, & ! [IN]
254  sfc_albedo, & ! [IN]
255  solins, cossza, & ! [IN]
256  flux_rad, & ! [OUT]
257  flux_rad_top, & ! [OUT]
258  sflx_rad_dn ) ! [OUT]
259 
260 
261  ! apply radiative flux convergence -> heating rate
262  call rd_heating( flux_rad(:,:,:,:,:,2), & ! [IN]
263  dens(:,:,:), & ! [IN]
264  rhot(:,:,:), & ! [IN]
265  qtrc(:,:,:,:), & ! [IN]
266  real_fz(:,:,:), & ! [IN]
267  dt_rd, & ! [IN]
268  temp_t(:,:,:,:), & ! [OUT]
269  rhot_t_rd(:,:,:) ) ! [OUT]
270 
271 
272 !OCL XFILL
273  do j = js, je
274  do i = is, ie
275  ! for clear-sky
276  sfcflx_lw_up_c(i,j) = flux_rad(ks-1,i,j,i_lw,i_up,1)
277  sfcflx_lw_dn_c(i,j) = flux_rad(ks-1,i,j,i_lw,i_dn,1)
278  sfcflx_sw_up_c(i,j) = flux_rad(ks-1,i,j,i_sw,i_up,1)
279  sfcflx_sw_dn_c(i,j) = flux_rad(ks-1,i,j,i_sw,i_dn,1)
280  ! for all-sky
281  sfcflx_lw_up(i,j) = flux_rad(ks-1,i,j,i_lw,i_up,2)
282  sfcflx_lw_dn(i,j) = flux_rad(ks-1,i,j,i_lw,i_dn,2)
283  sfcflx_sw_up(i,j) = flux_rad(ks-1,i,j,i_sw,i_up,2)
284  sfcflx_sw_dn(i,j) = flux_rad(ks-1,i,j,i_sw,i_dn,2)
285 
286  flux_net_sfc(i,j,i_lw) = sfcflx_lw_up(i,j) - sfcflx_lw_dn(i,j)
287  flux_net_sfc(i,j,i_sw) = sfcflx_sw_up(i,j) - sfcflx_sw_dn(i,j)
288  enddo
289  enddo
290 
291 !OCL XFILL
292  do j = js, je
293  do i = is, ie
294  ! for clear-sky
295  toaflx_lw_up_c(i,j) = flux_rad_top(i,j,i_lw,i_up,1)
296  toaflx_lw_dn_c(i,j) = flux_rad_top(i,j,i_lw,i_dn,1)
297  toaflx_sw_up_c(i,j) = flux_rad_top(i,j,i_sw,i_up,1)
298  toaflx_sw_dn_c(i,j) = flux_rad_top(i,j,i_sw,i_dn,1)
299  ! for all-sky
300  toaflx_lw_up(i,j) = flux_rad_top(i,j,i_lw,i_up,2)
301  toaflx_lw_dn(i,j) = flux_rad_top(i,j,i_lw,i_dn,2)
302  toaflx_sw_up(i,j) = flux_rad_top(i,j,i_sw,i_up,2)
303  toaflx_sw_dn(i,j) = flux_rad_top(i,j,i_sw,i_dn,2)
304 
305  flux_net_toa(i,j,i_lw) = toaflx_lw_up(i,j) - toaflx_lw_dn(i,j)
306  flux_net_toa(i,j,i_sw) = toaflx_sw_up(i,j) - toaflx_sw_dn(i,j)
307  enddo
308  enddo
309 
310 !OCL XFILL
311  do j = js, je
312  do i = is, ie
313  do k = ks, ke
314  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) )
315  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) )
316  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) )
317  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) )
318 
319  flux_net(k,i,j,i_lw) = flux_up(k,i,j,i_lw) - flux_dn(k,i,j,i_lw)
320  flux_net(k,i,j,i_sw) = flux_up(k,i,j,i_sw) - flux_dn(k,i,j,i_sw)
321  enddo
322  enddo
323  enddo
324 
325  if ( atmos_phy_rd_type == 'WRF' ) then
326 
327  flux_rad_org(:,:,:,:,:,:) = flux_rad(:,:,:,:,:,:)
328  rthratensw = 0.0_rp
329  sdown3d = 0.0_rp
330  gsw = 0.0_rp
331 
332  if ( i_qv > 0 ) then
333  qv3d(:,:,:) = qtrc(:,:,:,i_qv)
334  else
335  qv3d = 0.0_rp
336  end if
337  if ( i_qc > 0 ) then
338  qc3d(:,:,:) = qtrc(:,:,:,i_qc)
339  else
340  qc3d = 0.0_rp
341  end if
342  if ( i_qr > 0 ) then
343  qr3d(:,:,:) = qtrc(:,:,:,i_qr)
344  else
345  qr3d = 0.0_rp
346  end if
347  if ( i_qi > 0 ) then
348  qi3d(:,:,:) = qtrc(:,:,:,i_qi)
349  else
350  qi3d = 0.0_rp
351  end if
352  if ( i_qs > 0 ) then
353  qs3d(:,:,:) = qtrc(:,:,:,i_qs)
354  else
355  qs3d = 0.0_rp
356  end if
357  if ( i_qg > 0 ) then
358  qg3d(:,:,:) = qtrc(:,:,:,i_qg)
359  else
360  qg3d = 0.0_rp
361  end if
362 
363  do j = 1, ja
364  do i = 1, ia
365  do k = 1, ka
366  t3d(i,k,j) = temp(k,i,j) ! temperature (K)
367  rho3d(i,k,j) = dens(k,i,j) ! density (kg/m^3)
368  p3d(i,k,j) = pres(k,i,j) ! pressure (Pa)
369  pi3d(i,k,j) = (pres(k,i,j)/pre00)**(rdry/cpdry) ! exner function (dimensionless)
370  dz8w(i,k,j) = real_fz(k,i,j)-real_fz(k-1,i,j) ! dz between full levels(m)
371  enddo
372  enddo
373  enddo
374 
375  call swrad( dt_rd, & ! [IN]
376  rthratensw, & ! [INOUT]
377  sdown3d, & ! [INOUT]
378  gsw, & ! [INOUT]
379  real_lat, & ! [IN]
380  real_lon, & ! [IN]
381  sfc_albedo(:,:,i_sw), & ! [IN]
382  rho3d, & ! [IN]
383  t3d, & ! [IN]
384  p3d, & ! [IN]
385  pi3d, & ! [IN]
386  dz8w, & ! [IN]
387  solins(:,:), & ! [IN]
388  cossza(:,:), & ! [IN]
389  qv3d, & ! [IN]
390  qc3d, & ! [IN]
391  qr3d, & ! [IN]
392  qi3d, & ! [IN]
393  qs3d, & ! [IN]
394  qg3d, & ! [IN]
395  f_qv = .true., & ! [IN]
396  f_qc = .true., & ! [IN]
397  f_qr = .true., & ! [IN]
398  f_qi = .true., & ! [IN]
399  f_qs = .true., & ! [IN]
400  f_qg = .true., & ! [IN]
401  icloud = 1, & ! [IN]
402  warm_rain = .true. ) ! [IN]
403 
404  do j = js, je
405  do i = is, ie
406  flux_net_sfc(i,j,i_sw) = gsw(i,j)
407  do k = ks-1, ke
408  flux_rad(k,i,j,i_sw,i_up,2) = 0.0_rp
409  flux_rad(k,i,j,i_sw,i_dn,2) = sdown3d(i,k,j)
410  enddo
411 
412  do k = 1, ks-2
413  flux_rad(k,i,j,i_sw,i_dn,2) = sdown3d(i,ks-1,j)
414  enddo
415 
416  do k = ke+1, ka
417  flux_rad(k,i,j,i_sw,i_dn,2) = sdown3d(i,ke,j)
418  enddo
419  enddo
420  enddo
421 
422  do j = js, je
423  do i = is, ie
424  sfcflx_sw_up(i,j) = flux_rad(ks-1,i,j,i_sw,i_dn,2) * sfc_albedo(i,j,i_sw)
425  sfcflx_sw_dn(i,j) = flux_rad(ks-1,i,j,i_sw,i_dn,2)
426 
427  toaflx_sw_up(i,j) = 0.0_rp
428  toaflx_sw_dn(i,j) = flux_rad(ke,i,j,i_sw,i_dn,2) ! sometimes TOA altitude is very low
429  enddo
430  enddo
431 
432  do j = js, je
433  do i = is, ie
434  flux_net_toa(i,j,i_sw) = 0.0_rp
435  do k = ks, ke
436  flux_net(k,i,j,i_sw) = 0.0_rp
437  flux_up(k,i,j,i_sw) = 0.0_rp
438  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) )
439  enddo
440  enddo
441  enddo
442 
443  do j = js, je
444  do i = is, ie
445  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)
446  enddo
447  enddo
448 
449  endif
450 
451  call hist_in( solins(:,:), 'SOLINS', 'solar insolation', 'W/m2', nohalo=.true. )
452  call hist_in( cossza(:,:), 'COSZ', 'cos(solar zenith angle)', '1', nohalo=.true. )
453 
454  call hist_in( sfcflx_lw_up_c(:,:), 'SFLX_LW_up_c', 'SFC upward longwave radiation flux (clr)', 'W/m2', nohalo=.true. )
455  call hist_in( sfcflx_lw_dn_c(:,:), 'SFLX_LW_dn_c', 'SFC downward longwave radiation flux (clr)', 'W/m2', nohalo=.true. )
456  call hist_in( sfcflx_sw_up_c(:,:), 'SFLX_SW_up_c', 'SFC upward shortwave radiation flux (clr)', 'W/m2', nohalo=.true. )
457  call hist_in( sfcflx_sw_dn_c(:,:), 'SFLX_SW_dn_c', 'SFC downward shortwave radiation flux (clr)', 'W/m2', nohalo=.true. )
458 
459  call hist_in( sfcflx_lw_up(:,:), 'SFLX_LW_up', 'SFC upward longwave radiation flux', 'W/m2', nohalo=.true. )
460  call hist_in( sfcflx_lw_dn(:,:), 'SFLX_LW_dn', 'SFC downward longwave radiation flux', 'W/m2', nohalo=.true. )
461  call hist_in( sfcflx_sw_up(:,:), 'SFLX_SW_up', 'SFC upward shortwave radiation flux', 'W/m2', nohalo=.true. )
462  call hist_in( sfcflx_sw_dn(:,:), 'SFLX_SW_dn', 'SFC downward shortwave radiation flux', 'W/m2', nohalo=.true. )
463 
464  call hist_in( toaflx_lw_up_c(:,:), 'TOAFLX_LW_up_c', 'TOA upward longwave radiation flux (clr)', 'W/m2', nohalo=.true. )
465  call hist_in( toaflx_lw_dn_c(:,:), 'TOAFLX_LW_dn_c', 'TOA downward longwave radiation flux (clr)', 'W/m2', nohalo=.true. )
466  call hist_in( toaflx_sw_up_c(:,:), 'TOAFLX_SW_up_c', 'TOA upward shortwave radiation flux (clr)', 'W/m2', nohalo=.true. )
467  call hist_in( toaflx_sw_dn_c(:,:), 'TOAFLX_SW_dn_c', 'TOA downward shortwave radiation flux (clr)', 'W/m2', nohalo=.true. )
468 
469  call hist_in( toaflx_lw_up(:,:), 'TOAFLX_LW_up', 'TOA upward longwave radiation flux', 'W/m2', nohalo=.true. )
470  call hist_in( toaflx_lw_dn(:,:), 'TOAFLX_LW_dn', 'TOA downward longwave radiation flux', 'W/m2', nohalo=.true. )
471  call hist_in( toaflx_sw_up(:,:), 'TOAFLX_SW_up', 'TOA upward shortwave radiation flux', 'W/m2', nohalo=.true. )
472  call hist_in( toaflx_sw_dn(:,:), 'TOAFLX_SW_dn', 'TOA downward shortwave radiation flux', 'W/m2', nohalo=.true. )
473 
474  call hist_in( flux_net_sfc(:,:,i_lw), 'SLR', 'SFC net longwave radiation flux', 'W/m2', nohalo=.true. )
475  call hist_in( flux_net_sfc(:,:,i_sw), 'SSR', 'SFC net shortwave radiation flux', 'W/m2', nohalo=.true. )
476  call hist_in( flux_net_toa(:,:,i_lw), 'OLR', 'TOA net longwave radiation flux', 'W/m2', nohalo=.true. )
477  call hist_in( flux_net_toa(:,:,i_sw), 'OSR', 'TOA net shortwave radiation flux', 'W/m2', nohalo=.true. )
478 
479  call hist_in( flux_up(:,:,:,i_lw), 'RADFLUX_LWUP', 'upward longwave radiation flux', 'W/m2', nohalo=.true. )
480  call hist_in( flux_dn(:,:,:,i_lw), 'RADFLUX_LWDN', 'downward longwave radiation flux', 'W/m2', nohalo=.true. )
481  call hist_in( flux_net(:,:,:,i_lw), 'RADFLUX_LW', 'net longwave radiation flux', 'W/m2', nohalo=.true. )
482  call hist_in( flux_up(:,:,:,i_sw), 'RADFLUX_SWUP', 'upward shortwave radiation flux', 'W/m2', nohalo=.true. )
483  call hist_in( flux_dn(:,:,:,i_sw), 'RADFLUX_SWDN', 'downward shortwave radiation flux', 'W/m2', nohalo=.true. )
484  call hist_in( flux_net(:,:,:,i_sw), 'RADFLUX_SW', 'net shortwave radiation flux', 'W/m2', nohalo=.true. )
485 
486  call hist_in( sflx_rad_dn(:,:,i_lw,i_direct ), 'SFLX_LW_dn_dir', 'SFC downward longwave flux (direct )', 'W/m2', nohalo=.true. )
487  call hist_in( sflx_rad_dn(:,:,i_lw,i_diffuse), 'SFLX_LW_dn_dif', 'SFC downward longwave flux (diffuse)', 'W/m2', nohalo=.true. )
488  call hist_in( sflx_rad_dn(:,:,i_sw,i_direct ), 'SFLX_SW_dn_dir', 'SFC downward shortwave flux (direct )', 'W/m2', nohalo=.true. )
489  call hist_in( sflx_rad_dn(:,:,i_sw,i_diffuse), 'SFLX_SW_dn_dif', 'SFC downward shortwave flux (diffuse)', 'W/m2', nohalo=.true. )
490 
491  call hist_in( temp_t(:,:,:,i_lw), 'TEMP_t_rd_LW', 'tendency of temp in rd(LW)', 'K/day', nohalo=.true. )
492  call hist_in( temp_t(:,:,:,i_sw), 'TEMP_t_rd_SW', 'tendency of temp in rd(SW)', 'K/day', nohalo=.true. )
493  call hist_in( temp_t(:,:,:,3 ), 'TEMP_t_rd', 'tendency of temp in rd', 'K/day', nohalo=.true. )
494  call hist_in( rhot_t_rd(:,:,:), 'RHOT_t_RD', 'tendency of RHOT in rd', 'K.kg/m3/s', nohalo=.true. )
495 
496  ! output of raw data, for offline output
497  call hist_in( flux_rad(:,:,:,i_lw,i_up,2), 'RFLX_LW_up', 'upward longwave radiation flux (cell face)', 'W/m2', nohalo=.true. )
498  call hist_in( flux_rad(:,:,:,i_lw,i_dn,2), 'RFLX_LW_dn', 'downward longwave radiation flux (cell face)', 'W/m2', nohalo=.true. )
499  call hist_in( flux_rad(:,:,:,i_sw,i_up,2), 'RFLX_SW_up', 'upward shortwave radiation flux (cell face)', 'W/m2', nohalo=.true. )
500  call hist_in( flux_rad(:,:,:,i_sw,i_dn,2), 'RFLX_SW_dn', 'downward shortwave radiation flux (cell face)', 'W/m2', nohalo=.true. )
501 
502  if ( atmos_phy_rd_type == 'WRF' ) then
503  ! revert all radiation flux from MM5 scheme to default
504  flux_rad(:,:,:,:,:,:) = flux_rad_org(:,:,:,:,:,:)
505 
506  do j = js, je
507  do i = is, ie
508  sfcflx_sw_up(i,j) = flux_rad(ks-1,i,j,i_sw,i_up,2)
509  sfcflx_sw_dn(i,j) = flux_rad(ks-1,i,j,i_sw,i_dn,2)
510 
511  toaflx_sw_up(i,j) = flux_rad_top(i,j,i_sw,i_up,2) ! mstrnx
512  toaflx_sw_dn(i,j) = flux_rad_top(i,j,i_sw,i_dn,2) ! mstrnx
513  enddo
514  enddo
515 
516  endif
517 
518  endif
519 
520  do j = js, je
521  do i = is, ie
522  do k = ks, ke
523  rhot_t(k,i,j) = rhot_t(k,i,j) + rhot_t_rd(k,i,j)
524  enddo
525  enddo
526  enddo
527 
528  if ( statistics_checktotal ) then
529  call stat_total( total, rhot_t_rd(:,:,:), 'RHOT_t_RD' )
530  endif
531 
532  return
533  end subroutine atmos_phy_rd_driver
534 
535 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
subroutine, public prc_mpistop
Abort MPI.
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:61
procedure(rd), pointer, public atmos_phy_rd
real(rp), dimension(:,:,:), allocatable, public pres
module ATMOSPHERE / Physics Radiation
module ATMOSPHERIC Variables
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
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 whole cells: x, local, with HALO
real(rp), dimension(:,:,:), allocatable, public temp
module GRID (real space)
module LANDUSE
integer, parameter, public i_dn
integer, public ka
of whole cells: z, local, with HALO
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_sw_dn
real(rp), public const_pre00
pressure reference [Pa]
Definition: scale_const.F90:90
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 PROCESS
real(rp), dimension(:,:,:), pointer, public dens_av
module CONSTANT
Definition: scale_const.F90:14
integer, public ks
start point of inner domain: z, local
subroutine, public prof_rapstart(rapname_base, level)
Start raptime.
Definition: scale_prof.F90:156
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 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]
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(:,:,:), pointer, public rhot_av
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:204
integer, parameter, public i_up
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_lw_up
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
integer, public ja
of whole cells: y, local, with HALO