SCALE-RM
Functions/Subroutines
scale_atmos_phy_rd_offline Module Reference

module atmosphere / physics / radiation / offline More...

Functions/Subroutines

subroutine, public atmos_phy_rd_offline_setup
 Setup. More...
 
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. More...
 

Detailed Description

module atmosphere / physics / radiation / offline

Description
Atmospheric radiation transfer process for offline usage (input radiation flux from the file)
Author
Team SCALE
NAMELIST
  • PARAM_ATMOS_PHY_RD_OFFLINE
    nametypedefault valuecomment
    ATMOS_PHY_RD_OFFLINE_BASENAME character(len=H_LONG), dimension(FILE_EXTERNAL_INPUT_FILE_LIMIT) ''
    ATMOS_PHY_RD_OFFLINE_AXISTYPE character(len=H_SHORT) 'XYZ'
    ATMOS_PHY_RD_OFFLINE_ENABLE_PERIODIC_YEAR logical .false.
    ATMOS_PHY_RD_OFFLINE_ENABLE_PERIODIC_MONTH logical .false.
    ATMOS_PHY_RD_OFFLINE_ENABLE_PERIODIC_DAY logical .false.
    ATMOS_PHY_RD_OFFLINE_STEP_FIXED integer 0
    ATMOS_PHY_RD_OFFLINE_OFFSET real(RP) 0.0_RP
    ATMOS_PHY_RD_OFFLINE_DEFVAL real(RP) = UNDEF
    ATMOS_PHY_RD_OFFLINE_CHECK_COORDINATES logical .true.
    ATMOS_PHY_RD_OFFLINE_STEP_LIMIT integer 0
    ATMOS_PHY_RD_OFFLINE_DIFFUSE_RATE real(RP) 0.5_RP
    ATMOS_PHY_RD_OFFLINE_NIR_RATE real(RP) 0.5_RP

History Output
No history output

Function/Subroutine Documentation

◆ atmos_phy_rd_offline_setup()

subroutine, public scale_atmos_phy_rd_offline::atmos_phy_rd_offline_setup ( )

Setup.

Definition at line 58 of file scale_atmos_phy_rd_offline.F90.

References scale_const::const_undef, scale_file_external_input::file_external_input_file_limit, scale_file_external_input::file_external_input_regist(), scale_io::io_fid_conf, and scale_prc::prc_abort().

Referenced by mod_atmos_phy_rd_driver::atmos_phy_rd_driver_setup().

58  use scale_prc, only: &
59  prc_abort
60  use scale_file_external_input, only: &
63  use scale_const, only: &
64  undef => const_undef
65  implicit none
66 
67  character(len=H_SHORT) :: vars_3d (num_vars_3d)
68  character(len=H_SHORT) :: vars_2d (num_vars_2d)
69  character(len=H_SHORT) :: vars_2d_op(num_vars_2d_op)
70 
71  data vars_3d / 'RFLX_LW_up', 'RFLX_LW_dn', 'RFLX_SW_up', 'RFLX_SW_dn' /
72  data vars_2d / 'SFLX_LW_up', 'SFLX_LW_dn', 'SFLX_SW_up', 'SFLX_SW_dn' /
73  data vars_2d_op / 'SFLX_NIR_dn_dir', 'SFLX_NIR_dn_dif', 'SFLX_VIS_dn_dir', 'SFLX_VIS_dn_dif' /
74 
75  character(len=H_LONG) :: atmos_phy_rd_offline_basename(file_external_input_file_limit) = ''
76  character(len=H_SHORT) :: atmos_phy_rd_offline_axistype = 'XYZ'
77  logical :: atmos_phy_rd_offline_enable_periodic_year = .false.
78  logical :: atmos_phy_rd_offline_enable_periodic_month = .false.
79  logical :: atmos_phy_rd_offline_enable_periodic_day = .false.
80  integer :: atmos_phy_rd_offline_step_fixed = 0
81  real(RP) :: atmos_phy_rd_offline_offset = 0.0_rp
82  real(RP) :: atmos_phy_rd_offline_defval ! = UNDEF
83  logical :: atmos_phy_rd_offline_check_coordinates = .true.
84  integer :: atmos_phy_rd_offline_step_limit = 0
85 
86  namelist / param_atmos_phy_rd_offline / &
87  atmos_phy_rd_offline_basename, &
88  atmos_phy_rd_offline_axistype, &
89  atmos_phy_rd_offline_enable_periodic_year, &
90  atmos_phy_rd_offline_enable_periodic_month, &
91  atmos_phy_rd_offline_enable_periodic_day, &
92  atmos_phy_rd_offline_step_fixed, &
93  atmos_phy_rd_offline_offset, &
94  atmos_phy_rd_offline_defval, &
95  atmos_phy_rd_offline_check_coordinates, &
96  atmos_phy_rd_offline_step_limit, &
97  atmos_phy_rd_offline_diffuse_rate, &
98  atmos_phy_rd_offline_nir_rate
99 
100  integer :: n, ierr
101  !---------------------------------------------------------------------------
102 
103  log_newline
104  log_info("ATMOS_PHY_RD_offline_setup",*) 'Setup'
105  log_info("ATMOS_PHY_RD_offline_setup",*) 'Offline radiation process'
106 
107  atmos_phy_rd_offline_defval = undef
108 
109  !--- read namelist
110  rewind(io_fid_conf)
111  read(io_fid_conf,nml=param_atmos_phy_rd_offline,iostat=ierr)
112  if( ierr < 0 ) then !--- missing
113  log_info("ATMOS_PHY_RD_offline_setup",*) 'Not found namelist. Default used.'
114  elseif( ierr > 0 ) then !--- fatal error
115  log_error("ATMOS_PHY_RD_offline_setup",*) 'Not appropriate names in namelist PARAM_ATMOS_PHY_RD_OFFLINE. Check!'
116  call prc_abort
117  endif
118  log_nml(param_atmos_phy_rd_offline)
119 
120  if ( atmos_phy_rd_offline_basename(1) == '' ) then
121  log_error("ATMOS_PHY_RD_offline_setup",*) 'ATMOS_PHY_RD_offline_basename is necessary'
122  call prc_abort
123  end if
124 
125  do n = 1, num_vars_3d
126  call file_external_input_regist( atmos_phy_rd_offline_basename(:), & ! [IN]
127  vars_3d(n), & ! [IN]
128  atmos_phy_rd_offline_axistype, & ! [IN]
129  atmos_phy_rd_offline_enable_periodic_year, & ! [IN]
130  atmos_phy_rd_offline_enable_periodic_month, & ! [IN]
131  atmos_phy_rd_offline_enable_periodic_day, & ! [IN]
132  atmos_phy_rd_offline_step_fixed, & ! [IN]
133  atmos_phy_rd_offline_offset, & ! [IN]
134  atmos_phy_rd_offline_defval, & ! [IN]
135  atmos_phy_rd_offline_check_coordinates, & ! [IN]
136  atmos_phy_rd_offline_step_limit ) ! [IN]
137  end do
138 
139  do n = 1, num_vars_2d
140  call file_external_input_regist( atmos_phy_rd_offline_basename(:), & ! [IN]
141  vars_2d(n), & ! [IN]
142  'XY', & ! [IN]
143  atmos_phy_rd_offline_enable_periodic_year, & ! [IN]
144  atmos_phy_rd_offline_enable_periodic_month, & ! [IN]
145  atmos_phy_rd_offline_enable_periodic_day, & ! [IN]
146  atmos_phy_rd_offline_step_fixed, & ! [IN]
147  atmos_phy_rd_offline_offset, & ! [IN]
148  atmos_phy_rd_offline_defval, & ! [IN]
149  atmos_phy_rd_offline_check_coordinates, & ! [IN]
150  atmos_phy_rd_offline_step_limit ) ! [IN]
151  end do
152 
153  do n = 1, num_vars_2d_op
154  call file_external_input_regist( atmos_phy_rd_offline_basename(:), & ! [IN]
155  vars_2d_op(n), & ! [IN]
156  'XY', & ! [IN]
157  atmos_phy_rd_offline_enable_periodic_year, & ! [IN]
158  atmos_phy_rd_offline_enable_periodic_month, & ! [IN]
159  atmos_phy_rd_offline_enable_periodic_day, & ! [IN]
160  atmos_phy_rd_offline_step_fixed, & ! [IN]
161  atmos_phy_rd_offline_offset, & ! [IN]
162  atmos_phy_rd_offline_defval, & ! [IN]
163  atmos_phy_rd_offline_check_coordinates, & ! [IN]
164  atmos_phy_rd_offline_step_limit, & ! [IN]
165  exist = vars_2d_exist(n) ) ! [OUT]
166  if ( vars_2d_exist(n) ) then
167  log_info("ATMOS_PHY_RD_offline_setup",*) '', trim(vars_2d_op(n)), ' found.'
168  else
169  log_info("ATMOS_PHY_RD_offline_setup",*) '', trim(vars_2d_op(n)), ' not found.'
170  end if
171  end do
172 
173  return
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:55
module file / external_input
subroutine, public file_external_input_regist(basename, varname, axistype, enable_periodic_year, enable_periodic_month, enable_periodic_day, step_fixed, offset, defval, check_coordinates, step_limit, exist)
Regist data.
real(rp), public const_undef
Definition: scale_const.F90:41
integer, parameter, public file_external_input_file_limit
limit of file (for one item)
module PROCESS
Definition: scale_prc.F90:11
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
module CONSTANT
Definition: scale_const.F90:11
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_rd_offline_flux()

subroutine, public scale_atmos_phy_rd_offline::atmos_phy_rd_offline_flux ( integer, intent(in)  KA,
integer, intent(in)  KS,
integer, intent(in)  KE,
integer, intent(in)  IA,
integer, intent(in)  IS,
integer, intent(in)  IE,
integer, intent(in)  JA,
integer, intent(in)  JS,
integer, intent(in)  JE,
real(dp), intent(in)  time_now,
real(rp), dimension (ka,ia,ja,2,2), intent(out)  flux_rad,
real(rp), dimension(ia,ja,n_rad_dir,n_rad_rgn), intent(out)  SFLX_rad_dn 
)

Radiation main.

Definition at line 183 of file scale_atmos_phy_rd_offline.F90.

References scale_atmos_phy_rd_common::i_dn, scale_atmos_phy_rd_common::i_lw, scale_cpl_sfc_index::i_r_diffuse, scale_cpl_sfc_index::i_r_direct, scale_cpl_sfc_index::i_r_ir, scale_cpl_sfc_index::i_r_nir, scale_cpl_sfc_index::i_r_vis, scale_atmos_phy_rd_common::i_sw, scale_atmos_phy_rd_common::i_up, and scale_prc::prc_abort().

Referenced by mod_atmos_phy_rd_driver::atmos_phy_rd_driver_calc_tendency().

183  use scale_prc, only: &
184  prc_abort
185  use scale_file_external_input, only: &
186  file_external_input_update
187  use scale_atmos_phy_rd_common, only: &
188  i_sw, &
189  i_lw, &
190  i_dn, &
191  i_up
192  implicit none
193 
194  integer, intent(in) :: ka, ks, ke
195  integer, intent(in) :: ia, is, ie
196  integer, intent(in) :: ja, js, je
197  real(DP), intent(in) :: time_now
198  real(RP), intent(out) :: flux_rad (ka,ia,ja,2,2)
199  real(RP), intent(out) :: sflx_rad_dn(ia,ja,n_rad_dir,n_rad_rgn)
200 
201  real(RP) :: buffer(ia,ja)
202  logical :: error, error_sum, error_sflx
203 
204  integer :: i, j
205  !---------------------------------------------------------------------------
206 
207  log_progress(*) 'atmosphere / physics / radiation / offline'
208 
209  ! [note] external data input is now support only SCALE-RM
210 
211  error_sum = .false.
212 
213  ! 3D
214  call file_external_input_update( 'RFLX_LW_up', time_now, flux_rad(:,:,:,i_lw,i_up), error )
215  error_sum = ( error .OR. error_sum )
216 
217  call file_external_input_update( 'RFLX_LW_dn', time_now, flux_rad(:,:,:,i_lw,i_dn), error )
218  error_sum = ( error .OR. error_sum )
219 
220  call file_external_input_update( 'RFLX_SW_up', time_now, flux_rad(:,:,:,i_sw,i_up), error )
221  error_sum = ( error .OR. error_sum )
222 
223  call file_external_input_update( 'RFLX_SW_dn', time_now, flux_rad(:,:,:,i_sw,i_dn), error )
224  error_sum = ( error .OR. error_sum )
225 
226 
227  ! 2D
228  call file_external_input_update( 'SFLX_LW_up', time_now, buffer(:,:), error )
229  if ( error ) then
230  error_sum = .true.
231  else
232  !$omp parallel do default(none) OMP_SCHEDULE_ &
233  !$omp private(i,j) &
234  !$omp shared(KS,IS,IE,JS,JE) &
235  !$omp shared(flux_rad,buffer)
236  do j = js, je
237  do i = is, ie
238  flux_rad(ks-1,i,j,i_lw,i_up) = buffer(i,j)
239  end do
240  end do
241  end if
242 
243  call file_external_input_update( 'SFLX_LW_dn', time_now, buffer(:,:), error )
244  if ( error ) then
245  error_sum = .true.
246  else
247  !$omp parallel do default(none) OMP_SCHEDULE_ &
248  !$omp private(i,j) &
249  !$omp shared(KS,IS,IE,JS,JE) &
250  !$omp shared(flux_rad,buffer)
251  do j = js, je
252  do i = is, ie
253  flux_rad(ks-1,i,j,i_lw,i_dn) = buffer(i,j)
254  end do
255  end do
256  end if
257 
258  call file_external_input_update( 'SFLX_SW_up', time_now, buffer(:,:), error )
259  if ( error ) then
260  error_sum = .true.
261  else
262  !$omp parallel do default(none) OMP_SCHEDULE_ &
263  !$omp private(i,j) &
264  !$omp shared(KS,IS,IE,JS,JE) &
265  !$omp shared(flux_rad,buffer)
266  do j = js, je
267  do i = is, ie
268  flux_rad(ks-1,i,j,i_sw,i_up) = buffer(i,j)
269  end do
270  end do
271  end if
272 
273  call file_external_input_update( 'SFLX_SW_dn', time_now, buffer(:,:), error )
274  if ( error ) then
275  error_sum = .true.
276  else
277  !$omp parallel do default(none) OMP_SCHEDULE_ &
278  !$omp private(i,j) &
279  !$omp shared(KS,IS,IE,JS,JE) &
280  !$omp shared(flux_rad,buffer)
281  do j = js, je
282  do i = is, ie
283  flux_rad(ks-1,i,j,i_sw,i_dn) = buffer(i,j)
284  end do
285  end do
286  end if
287 
288  !$omp parallel do default(none) OMP_SCHEDULE_ &
289  !$omp private(i,j) &
290  !$omp shared(KS,IS,IE,JS,JE,ATMOS_PHY_RD_offline_diffuse_rate) &
291  !$omp shared(SFLX_rad_dn,flux_rad)
292  do j = js, je
293  do i = is, ie
294  sflx_rad_dn(i,j,i_r_direct ,i_r_ir) = 0.0_rp
295  sflx_rad_dn(i,j,i_r_diffuse,i_r_ir) = flux_rad(ks-1,i,j,i_lw,i_dn)
296  end do
297  end do
298 
299  ! 2D optional
300 
301  error_sflx = .false.
302 
303  if ( vars_2d_exist(1) ) then
304  call file_external_input_update( 'SFLX_NIR_dn_dir', time_now, sflx_rad_dn(:,:,i_r_direct,i_r_vis), error )
305  error_sum = ( error .OR. error_sum )
306  else
307  error_sflx = .true.
308  endif
309 
310  if ( vars_2d_exist(2) ) then
311  call file_external_input_update( 'SFLX_NIR_dn_dif', time_now, sflx_rad_dn(:,:,i_r_direct,i_r_vis), error )
312  error_sum = ( error .OR. error_sum )
313  else
314  error_sflx = .true.
315  endif
316 
317  if ( vars_2d_exist(3) ) then
318  call file_external_input_update( 'SFLX_VIS_dn_dir', time_now, sflx_rad_dn(:,:,i_r_direct,i_r_vis), error )
319  error_sum = ( error .OR. error_sum )
320  else
321  error_sflx = .true.
322  endif
323 
324  if ( vars_2d_exist(4) ) then
325  call file_external_input_update( 'SFLX_VIS_dn_dif', time_now, sflx_rad_dn(:,:,i_r_direct,i_r_vis), error )
326  error_sum = ( error .OR. error_sum )
327  else
328  error_sflx = .true.
329  endif
330 
331  if ( error_sflx ) then ! reconstruct from lowermost SW flux
332  !$omp parallel do default(none) OMP_SCHEDULE_ &
333  !$omp private(i,j) &
334  !$omp shared(KS,IS,IE,JS,JE,ATMOS_PHY_RD_offline_diffuse_rate,ATMOS_PHY_RD_offline_NIR_rate) &
335  !$omp shared(SFLX_rad_dn,flux_rad)
336  do j = js, je
337  do i = is, ie
338  sflx_rad_dn(i,j,i_r_direct ,i_r_nir) = ( 1.0_rp-atmos_phy_rd_offline_diffuse_rate ) &
339  * ( atmos_phy_rd_offline_nir_rate ) * flux_rad(ks-1,i,j,i_sw,i_dn)
340  sflx_rad_dn(i,j,i_r_diffuse,i_r_nir) = ( atmos_phy_rd_offline_diffuse_rate ) &
341  * ( atmos_phy_rd_offline_nir_rate ) * flux_rad(ks-1,i,j,i_sw,i_dn)
342  sflx_rad_dn(i,j,i_r_direct ,i_r_vis) = ( 1.0_rp-atmos_phy_rd_offline_diffuse_rate ) &
343  * ( 1.0_rp-atmos_phy_rd_offline_nir_rate ) * flux_rad(ks-1,i,j,i_sw,i_dn)
344  sflx_rad_dn(i,j,i_r_diffuse,i_r_vis) = ( atmos_phy_rd_offline_diffuse_rate ) &
345  * ( 1.0_rp-atmos_phy_rd_offline_nir_rate ) * flux_rad(ks-1,i,j,i_sw,i_dn)
346  enddo
347  enddo
348  endif
349 
350  if ( error_sum ) then
351  log_error("ATMOS_PHY_RD_offline_flux",*) 'Requested data is not found!'
352  call prc_abort
353  endif
354 
355  return
integer, public ia
of whole cells: x, local, with HALO
integer, public ja
of whole cells: y, local, with HALO
module file / external_input
integer, parameter, public i_lw
integer, public is
start point of inner domain: x, local
integer, parameter, public i_sw
integer, public ie
end point of inner domain: x, local
integer, parameter, public i_dn
integer, public ke
end point of inner domain: z, local
module PROCESS
Definition: scale_prc.F90:11
integer, public je
end point of inner domain: y, local
integer, public ks
start point of inner domain: z, local
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
integer, public js
start point of inner domain: y, local
integer, public ka
of whole cells: z, local, with HALO
module atmosphere / physics / radiation / common
integer, parameter, public i_up
Here is the call graph for this function:
Here is the caller graph for this function: