SCALE-RM
Functions/Subroutines
scale_atmos_phy_rd_offline Module Reference

module ATMOSPHERE / Physics Radiation More...

Functions/Subroutines

subroutine, public atmos_phy_rd_offline_setup (RD_TYPE)
 Setup. More...
 
subroutine, public atmos_phy_rd_offline (DENS, RHOT, QTRC, CZ, FZ, fact_ocean, fact_land, fact_urban, temp_sfc, albedo_land, solins, cosSZA, flux_rad, flux_rad_top, SFLX_rad_dn)
 Radiation main. More...
 

Detailed Description

module ATMOSPHERE / Physics Radiation

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) ''
    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 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 ( character(len=*), intent(in)  RD_TYPE)

Setup.

Definition at line 58 of file scale_atmos_phy_rd_offline.F90.

References scale_const::const_undef, scale_external_input::extin_regist(), scale_stdio::io_fid_conf, scale_stdio::io_fid_log, scale_stdio::io_fid_nml, scale_stdio::io_l, scale_stdio::io_nml, and scale_process::prc_mpistop().

Referenced by scale_atmos_phy_rd::atmos_phy_rd_setup().

58  use scale_process, only: &
60  use scale_external_input, only: &
62  use scale_const, only: &
63  undef => const_undef
64  implicit none
65 
66  character(len=*), intent(in) :: RD_TYPE
67 
68  character(len=H_SHORT) :: vars_3d (num_vars_3d)
69  character(len=H_SHORT) :: vars_2d (num_vars_2d)
70  character(len=H_SHORT) :: vars_2d_op(num_vars_2d_op)
71 
72  data vars_3d / 'RFLX_LW_up', 'RFLX_LW_dn', 'RFLX_SW_up', 'RFLX_SW_dn' /
73  data vars_2d / 'SFLX_LW_up', 'SFLX_LW_dn', 'SFLX_SW_up', 'SFLX_SW_dn' /
74  data vars_2d_op / 'SFLX_SW_dn_dir' /
75 
76  character(len=H_LONG) :: ATMOS_PHY_RD_offline_basename = ''
77  character(len=H_SHORT) :: ATMOS_PHY_RD_offline_axistype = 'XYZ'
78  logical :: ATMOS_PHY_RD_offline_enable_periodic_year = .false.
79  logical :: ATMOS_PHY_RD_offline_enable_periodic_month = .false.
80  logical :: ATMOS_PHY_RD_offline_enable_periodic_day = .false.
81  integer :: ATMOS_PHY_RD_offline_step_fixed = 0
82  real(RP) :: ATMOS_PHY_RD_offline_offset = 0.0_rp
83  real(RP) :: ATMOS_PHY_RD_offline_defval
84  logical :: ATMOS_PHY_RD_offline_check_coordinates = .true.
85  integer :: ATMOS_PHY_RD_offline_step_limit = 0
86 
87  namelist / param_atmos_phy_rd_offline / &
88  atmos_phy_rd_offline_basename, &
89  atmos_phy_rd_offline_axistype, &
90  atmos_phy_rd_offline_enable_periodic_year, &
91  atmos_phy_rd_offline_enable_periodic_month, &
92  atmos_phy_rd_offline_enable_periodic_day, &
93  atmos_phy_rd_offline_step_fixed, &
94  atmos_phy_rd_offline_offset, &
95  atmos_phy_rd_offline_defval, &
96  atmos_phy_rd_offline_check_coordinates, &
97  atmos_phy_rd_offline_step_limit, &
98  atmos_phy_rd_offline_diffuse_rate
99 
100  integer :: n, ierr
101  !---------------------------------------------------------------------------
102 
103  if( io_l ) write(io_fid_log,*)
104  if( io_l ) write(io_fid_log,*) '++++++ Module[RADIATION] / Categ[ATMOS PHYSICS] / Origin[SCALElib]'
105  if( io_l ) write(io_fid_log,*) '*** Offline radiation process'
106 
107  if ( rd_type /= 'OFFLINE' ) then
108  write(*,*) 'xxx RD_TYPE is not OFFLINE. Check!'
109  call prc_mpistop
110  endif
111 
112 
113  atmos_phy_rd_offline_defval = undef
114 
115  !--- read namelist
116  rewind(io_fid_conf)
117  read(io_fid_conf,nml=param_atmos_phy_rd_offline,iostat=ierr)
118  if( ierr < 0 ) then !--- missing
119  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
120  elseif( ierr > 0 ) then !--- fatal error
121  write(*,*) 'xxx Not appropriate names in namelist PARAM_ATMOS_PHY_RD_OFFLINE. Check!'
122  call prc_mpistop
123  endif
124  if( io_nml ) write(io_fid_nml,nml=param_atmos_phy_rd_offline)
125 
126  if ( atmos_phy_rd_offline_basename == '' ) then
127  write(*,*) 'xxx ATMOS_PHY_RD_offline_basename is necessary'
128  call prc_mpistop
129  end if
130 
131  do n = 1, num_vars_3d
132  call extin_regist( atmos_phy_rd_offline_basename, & ! [IN]
133  vars_3d(n), & ! [IN]
134  atmos_phy_rd_offline_axistype, & ! [IN]
135  atmos_phy_rd_offline_enable_periodic_year, & ! [IN]
136  atmos_phy_rd_offline_enable_periodic_month, & ! [IN]
137  atmos_phy_rd_offline_enable_periodic_day, & ! [IN]
138  atmos_phy_rd_offline_step_fixed, & ! [IN]
139  atmos_phy_rd_offline_offset, & ! [IN]
140  atmos_phy_rd_offline_defval, & ! [IN]
141  atmos_phy_rd_offline_check_coordinates, & ! [IN]
142  atmos_phy_rd_offline_step_limit ) ! [IN]
143  end do
144 
145  do n = 1, num_vars_2d
146  call extin_regist( atmos_phy_rd_offline_basename, & ! [IN]
147  vars_2d(n), & ! [IN]
148  'XY', & ! [IN]
149  atmos_phy_rd_offline_enable_periodic_year, & ! [IN]
150  atmos_phy_rd_offline_enable_periodic_month, & ! [IN]
151  atmos_phy_rd_offline_enable_periodic_day, & ! [IN]
152  atmos_phy_rd_offline_step_fixed, & ! [IN]
153  atmos_phy_rd_offline_offset, & ! [IN]
154  atmos_phy_rd_offline_defval, & ! [IN]
155  atmos_phy_rd_offline_check_coordinates, & ! [IN]
156  atmos_phy_rd_offline_step_limit ) ! [IN]
157  end do
158 
159  do n = 1, num_vars_2d_op
160  call extin_regist( atmos_phy_rd_offline_basename, & ! [IN]
161  vars_2d_op(n), & ! [IN]
162  'XY', & ! [IN]
163  atmos_phy_rd_offline_enable_periodic_year, & ! [IN]
164  atmos_phy_rd_offline_enable_periodic_month, & ! [IN]
165  atmos_phy_rd_offline_enable_periodic_day, & ! [IN]
166  atmos_phy_rd_offline_step_fixed, & ! [IN]
167  atmos_phy_rd_offline_offset, & ! [IN]
168  atmos_phy_rd_offline_defval, & ! [IN]
169  atmos_phy_rd_offline_check_coordinates, & ! [IN]
170  atmos_phy_rd_offline_step_limit, & ! [IN]
171  exist = vars_2d_exist(n) ) ! [OUT]
172  if ( vars_2d_exist(n) ) then
173  if( io_l ) write(io_fid_log,*) '*** ', trim(vars_2d_op(n)), ' found.'
174  else
175  if( io_l ) write(io_fid_log,*) '*** ', trim(vars_2d_op(n)), ' not found.'
176  end if
177  end do
178 
179  return
subroutine, public prc_mpistop
Abort MPI.
real(rp), public const_undef
Definition: scale_const.F90:43
module PROCESS
subroutine, public extin_regist(basename, varname, axistype, enable_periodic_year, enable_periodic_month, enable_periodic_day, step_fixed, offset, defval, check_coordinates, step_limit, exist)
Regist data.
module CONSTANT
Definition: scale_const.F90:14
module EXTERNAL INPUT
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_rd_offline()

subroutine, public scale_atmos_phy_rd_offline::atmos_phy_rd_offline ( real(rp), dimension (ka,ia,ja), intent(in)  DENS,
real(rp), dimension (ka,ia,ja), intent(in)  RHOT,
real(rp), dimension (ka,ia,ja,qa), intent(in)  QTRC,
real(rp), dimension ( ka,ia,ja), intent(in)  CZ,
real(rp), dimension (0:ka,ia,ja), intent(in)  FZ,
real(rp), dimension (ia,ja), intent(in)  fact_ocean,
real(rp), dimension (ia,ja), intent(in)  fact_land,
real(rp), dimension (ia,ja), intent(in)  fact_urban,
real(rp), dimension (ia,ja), intent(in)  temp_sfc,
real(rp), dimension (ia,ja,2), intent(in)  albedo_land,
real(rp), dimension (ia,ja), intent(in)  solins,
real(rp), dimension (ia,ja), intent(in)  cosSZA,
real(rp), dimension (ka,ia,ja,2,2,2), intent(out)  flux_rad,
real(rp), dimension(ia,ja,2,2,2), intent(out)  flux_rad_top,
real(rp), dimension (ia,ja,2,2), intent(out)  SFLX_rad_dn 
)

Radiation main.

Definition at line 195 of file scale_atmos_phy_rd_offline.F90.

References scale_atmos_phy_rd_common::i_diffuse, scale_atmos_phy_rd_common::i_direct, scale_atmos_phy_rd_common::i_dn, scale_atmos_phy_rd_common::i_lw, scale_atmos_phy_rd_common::i_sw, scale_atmos_phy_rd_common::i_up, scale_grid_index::ie, scale_stdio::io_fid_log, scale_stdio::io_l, scale_grid_index::is, scale_grid_index::je, scale_grid_index::js, scale_grid_index::ks, scale_process::prc_mpistop(), and scale_time::time_nowdaysec.

Referenced by scale_atmos_phy_rd::atmos_phy_rd_setup().

195 ! Jval )
196  use scale_grid_index
197  use scale_tracer
198  use scale_process, only: &
200  use scale_external_input, only: &
201  extin_update
202  use scale_time, only: &
204  use scale_atmos_phy_rd_common, only: &
205  i_sw, &
206  i_lw, &
207  i_dn, &
208  i_up, &
209  i_direct, &
210  i_diffuse
211  implicit none
212  real(RP), intent(in) :: DENS (KA,IA,JA)
213  real(RP), intent(in) :: RHOT (KA,IA,JA)
214  real(RP), intent(in) :: QTRC (KA,IA,JA,QA)
215  real(RP), intent(in) :: CZ ( KA,IA,JA) ! UNUSED
216  real(RP), intent(in) :: FZ (0:KA,IA,JA)
217  real(RP), intent(in) :: fact_ocean (IA,JA)
218  real(RP), intent(in) :: fact_land (IA,JA)
219  real(RP), intent(in) :: fact_urban (IA,JA)
220  real(RP), intent(in) :: temp_sfc (IA,JA)
221  real(RP), intent(in) :: albedo_land (IA,JA,2)
222  real(RP), intent(in) :: solins (IA,JA)
223  real(RP), intent(in) :: cosSZA (IA,JA)
224  real(RP), intent(out) :: flux_rad (KA,IA,JA,2,2,2)
225  real(RP), intent(out) :: flux_rad_top(IA,JA,2,2,2)
226  real(RP), intent(out) :: SFLX_rad_dn (IA,JA,2,2)
227 ! real(RP), intent(out) :: Jval (KA,IA,JA,CH_QA_photo)
228 
229  real(RP) :: buffer(IA,JA)
230  logical :: error, error_sum
231 
232  integer :: i, j
233  !---------------------------------------------------------------------------
234 
235  if( io_l ) write(io_fid_log,*) '*** Atmos physics step: Radiation(offline)'
236 
237  ! [note] external data input is now support only SCALE-RM
238 
239  error_sum = .false.
240 
241  ! 3D
242  call extin_update( flux_rad(:,:,:,i_lw,i_up,2), 'RFLX_LW_up', time_nowdaysec, error )
243  error_sum = ( error .OR. error_sum )
244 
245  call extin_update( flux_rad(:,:,:,i_lw,i_dn,2), 'RFLX_LW_dn', time_nowdaysec, error )
246  error_sum = ( error .OR. error_sum )
247 
248  call extin_update( flux_rad(:,:,:,i_sw,i_up,2), 'RFLX_SW_up', time_nowdaysec, error )
249  error_sum = ( error .OR. error_sum )
250 
251  call extin_update( flux_rad(:,:,:,i_sw,i_dn,2), 'RFLX_SW_dn', time_nowdaysec, error )
252  error_sum = ( error .OR. error_sum )
253 
254 
255  ! 2D
256  call extin_update( buffer(:,:), 'SFLX_LW_up', time_nowdaysec, error )
257  if ( error ) then
258  error_sum = .true.
259  else
260  !$omp parallel do default(none) OMP_SCHEDULE_ &
261  !$omp private(i,j) &
262  !$omp shared(KS,IS,IE,JS,JE) &
263  !$omp shared(flux_rad,buffer)
264  do j = js, je
265  do i = is, ie
266  flux_rad(ks-1,i,j,i_lw,i_up,2) = buffer(i,j)
267  end do
268  end do
269  end if
270 
271  call extin_update( buffer(:,:), 'SFLX_LW_dn', time_nowdaysec, error )
272  if ( error ) then
273  error_sum = .true.
274  else
275  !$omp parallel do default(none) OMP_SCHEDULE_ &
276  !$omp private(i,j) &
277  !$omp shared(KS,IS,IE,JS,JE) &
278  !$omp shared(flux_rad,buffer)
279  do j = js, je
280  do i = is, ie
281  flux_rad(ks-1,i,j,i_lw,i_dn,2) = buffer(i,j)
282  end do
283  end do
284  end if
285 
286  call extin_update( buffer(:,:), 'SFLX_SW_up', time_nowdaysec, error )
287  if ( error ) then
288  error_sum = .true.
289  else
290  !$omp parallel do default(none) OMP_SCHEDULE_ &
291  !$omp private(i,j) &
292  !$omp shared(KS,IS,IE,JS,JE) &
293  !$omp shared(flux_rad,buffer)
294  do j = js, je
295  do i = is, ie
296  flux_rad(ks-1,i,j,i_sw,i_up,2) = buffer(i,j)
297  end do
298  end do
299  end if
300 
301  call extin_update( buffer(:,:), 'SFLX_SW_dn', time_nowdaysec, error )
302  if ( error ) then
303  error_sum = .true.
304  else
305  !$omp parallel do default(none) OMP_SCHEDULE_ &
306  !$omp private(i,j) &
307  !$omp shared(KS,IS,IE,JS,JE) &
308  !$omp shared(flux_rad,buffer)
309  do j = js, je
310  do i = is, ie
311  flux_rad(ks-1,i,j,i_sw,i_dn,2) = buffer(i,j)
312  end do
313  end do
314  end if
315 
316  !$omp parallel do default(none) OMP_SCHEDULE_ &
317  !$omp private(i,j) &
318  !$omp shared(KS,IS,IE,JS,JE,ATMOS_PHY_RD_offline_diffuse_rate) &
319  !$omp shared(SFLX_rad_dn,flux_rad)
320  do j = js, je
321  do i = is, ie
322  sflx_rad_dn(i,j,i_lw,i_diffuse) = flux_rad(ks-1,i,j,i_lw,i_dn,2)
323  sflx_rad_dn(i,j,i_lw,i_direct ) = 0.0_rp
324  end do
325  end do
326 
327  ! 2D optional
328  if ( vars_2d_exist(1) ) then
329  call extin_update( sflx_rad_dn(:,:,i_sw,i_direct), 'SFLX_SW_dn_dir', time_nowdaysec, error )
330  if ( error ) then
331  error_sum = .true.
332  else
333  !$omp parallel do default(none) OMP_SCHEDULE_ &
334  !$omp private(i,j) &
335  !$omp shared(KS,IS,IE,JS,JE) &
336  !$omp shared(SFLX_rad_dn,flux_rad)
337  do j = js, je
338  do i = is, ie
339  sflx_rad_dn(i,j,i_sw,i_diffuse) = flux_rad(ks-1,i,j,i_sw,i_dn,2) - sflx_rad_dn(i,j,i_sw,i_direct)
340  end do
341  end do
342  end if
343  else
344  !$omp parallel do default(none) OMP_SCHEDULE_ &
345  !$omp private(i,j) &
346  !$omp shared(KS,IS,IE,JS,JE,ATMOS_PHY_RD_offline_diffuse_rate) &
347  !$omp shared(SFLX_rad_dn,flux_rad)
348  do j = js, je
349  do i = is, ie
350  sflx_rad_dn(i,j,i_sw,i_diffuse) = ( atmos_phy_rd_offline_diffuse_rate ) * flux_rad(ks-1,i,j,i_sw,i_dn,2)
351  sflx_rad_dn(i,j,i_sw,i_direct ) = ( 1.0_rp - atmos_phy_rd_offline_diffuse_rate ) * flux_rad(ks-1,i,j,i_sw,i_dn,2)
352  end do
353  end do
354  end if
355 
356  if ( error_sum ) then
357  write(*,*) 'xxx Requested data is not found!'
358  call prc_mpistop
359  endif
360 
361  ! clearsky and TOA value are not defined
362  flux_rad(:,:,:,:,:,1) = 0.0_rp
363  flux_rad_top(:,:,:,:,:) = 0.0_rp
364 
365  return
integer, public is
start point of inner domain: x, local
integer, public je
end point of inner domain: y, local
subroutine, public prc_mpistop
Abort MPI.
real(dp), public time_nowdaysec
second of current time [sec]
Definition: scale_time.F90:69
module grid index
module TRACER
integer, public js
start point of inner domain: y, local
module TIME
Definition: scale_time.F90:15
module PROCESS
module EXTERNAL INPUT
integer, public ie
end point of inner domain: x, local
module ATMOSPHERE / Physics Radiation
Here is the call graph for this function:
Here is the caller graph for this function: