SCALE-RM
Functions/Subroutines | Variables
mod_atmos_bnd_driver Module Reference

module ATMOSPHERE / Boundary treatment More...

Functions/Subroutines

subroutine, public atmos_boundary_driver_setup
 Setup. More...
 
subroutine, public atmos_boundary_driver_set (time)
 set More...
 
subroutine atmos_boundary_set_file (time)
 Set boundary value for real case experiment. More...
 
subroutine atmos_boundary_set_online (time)
 Set boundary value for real case experiment [online daughter]. More...
 
subroutine, public atmos_boundary_driver_finalize
 Finalize boundary value. More...
 
subroutine, public atmos_boundary_driver_update (time)
 Update boundary value with a constant time boundary. More...
 
subroutine, public atmos_boundary_driver_send
 Send data to child domain. More...
 
subroutine set_boundary
 
subroutine history_bnd (ATMOS_BOUNDARY_DENS, ATMOS_BOUNDARY_VELZ, ATMOS_BOUNDARY_VELX, ATMOS_BOUNDARY_VELY, ATMOS_BOUNDARY_POTT, ATMOS_BOUNDARY_QTRC)
 
subroutine calc_mass
 
subroutine set_offset
 

Variables

integer, public bnd_qa
 
integer, allocatable, public of
 
integer, allocatable, public tracer
 
integer, public at
 
integer, public boundary
 
integer, dimension(:), allocatable, public bnd_iq
 
integer, allocatable, public index
 
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_dens
 
real(rp), allocatable, public reference
 
real(rp), dimension(0-1), allocatable, public dens
 
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_velz
 
real(rp), dimension(0-1), allocatable, public velz
 
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_velx
 
real(rp), dimension(0-1), allocatable, public velx
 
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_vely
 
real(rp), dimension(0-1), allocatable, public vely
 
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_pott
 
real(rp), dimension(0-1), allocatable, public pott
 
real(rp), dimension(:,:,:,:), allocatable, public atmos_boundary_qtrc
 
real(rp), dimension(0-1), allocatable, public qtrc
 
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_alpha_dens
 
real(rp), allocatable, public damping
 
real(rp), allocatable, public coefficient
 
real(rp), allocatable, public for
 
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_alpha_velz
 
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_alpha_velx
 
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_alpha_vely
 
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_alpha_pott
 
real(rp), dimension(:,:,:,:), allocatable, public atmos_boundary_alpha_qtrc
 
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_mflux_offset_x
 
real(rp), allocatable, public mass
 
real(rp), allocatable, public flux
 
real(rp), dimension(south, north), allocatable, public offset
 
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_mflux_offset_y
 
real(rp), public atmos_boundary_smoother_fact = 0.2_RP
 
real(rp), public fact
 
real(rp), public smoother
 
real(rp), public to
 
logical, public atmos_boundary_update_flag = .false.
 
logical, public switch
 
logical, public real
 
logical, public case
 

Detailed Description

module ATMOSPHERE / Boundary treatment

Description
Boundary treatment of model domain Additional forcing, Sponge layer, rayleigh dumping
Author
Team SCALE
NAMELIST
  • PARAM_ATMOS_BOUNDARY
    nametypedefault valuecomment
    ATMOS_BOUNDARY_TYPE character(len=H_SHORT) 'NONE'
    ATMOS_BOUNDARY_IN_BASENAME character(len=H_LONG) ''
    ATMOS_BOUNDARY_IN_BASENAME_ADD_NUM logical .false.
    ATMOS_BOUNDARY_IN_NUMBER_OF_FILES integer 1
    ATMOS_BOUNDARY_IN_CHECK_COORDINATES logical .true.
    ATMOS_BOUNDARY_IN_STEP_LIMIT integer 1000
    ATMOS_BOUNDARY_IN_AGGREGATE logical
    ATMOS_BOUNDARY_OUT_BASENAME character(len=H_LONG) ''
    ATMOS_BOUNDARY_OUT_TITLE character(len=H_MID) 'SCALE-RM BOUNDARY CONDITION' title of the output file
    ATMOS_BOUNDARY_OUT_DTYPE character(len=H_SHORT) 'DEFAULT' REAL4 or REAL8
    ATMOS_BOUNDARY_OUT_AGGREGATE logical
    ATMOS_BOUNDARY_USE_VELZ logical .false. read from file?
    ATMOS_BOUNDARY_USE_VELX logical .false. read from file?
    ATMOS_BOUNDARY_USE_VELY logical .false. read from file?
    ATMOS_BOUNDARY_USE_PT logical .false. read from file?
    ATMOS_BOUNDARY_USE_DENS logical .false. read from file?
    ATMOS_BOUNDARY_USE_QV logical .false. read from file?
    ATMOS_BOUNDARY_USE_QHYD logical .false. read from file?
    ATMOS_BOUNDARY_USE_CHEM logical .false. read from file?
    ATMOS_BOUNDARY_DENS_ADJUST logical .false.
    ATMOS_BOUNDARY_DENS_ADJUST_TAU real(RP)
    ATMOS_BOUNDARY_VALUE_VELZ real(RP) 0.0_RP velocity w at boundary, 0 [m/s]
    ATMOS_BOUNDARY_VALUE_VELX real(RP) 0.0_RP velocity u at boundary, 0 [m/s]
    ATMOS_BOUNDARY_VALUE_VELY real(RP) 0.0_RP velocity v at boundary, 0 [m/s]
    ATMOS_BOUNDARY_VALUE_PT real(RP) 300.0_RP potential temp. at boundary, 300 [K]
    ATMOS_BOUNDARY_VALUE_QTRC real(RP) 0.0_RP tracer at boundary, 0 [kg/kg]
    ATMOS_BOUNDARY_ALPHAFACT_DENS real(RP) 1.0_RP alpha factor again default
    ATMOS_BOUNDARY_ALPHAFACT_VELZ real(RP) 1.0_RP alpha factor again default
    ATMOS_BOUNDARY_ALPHAFACT_VELX real(RP) 1.0_RP alpha factor again default
    ATMOS_BOUNDARY_ALPHAFACT_VELY real(RP) 1.0_RP alpha factor again default
    ATMOS_BOUNDARY_ALPHAFACT_PT real(RP) 1.0_RP alpha factor again default
    ATMOS_BOUNDARY_ALPHAFACT_QTRC real(RP) 1.0_RP alpha factor again default
    ATMOS_BOUNDARY_SMOOTHER_FACT real(RP) 0.2_RP > fact for smoother to damping
    ATMOS_BOUNDARY_FRACZ real(RP) 1.0_RP fraction of boundary region for dumping (z) (0-1)
    ATMOS_BOUNDARY_FRACX real(RP) 1.0_RP fraction of boundary region for dumping (x) (0-1)
    ATMOS_BOUNDARY_FRACY real(RP) 1.0_RP fraction of boundary region for dumping (y) (0-1)
    ATMOS_BOUNDARY_TAUZ real(RP) maximum value for damping tau (z) [s]
    ATMOS_BOUNDARY_TAUX real(RP) maximum value for damping tau (x) [s]
    ATMOS_BOUNDARY_TAUY real(RP) maximum value for damping tau (y) [s]
    ATMOS_BOUNDARY_LINEAR_V logical .false. linear or non-linear profile of relax region
    ATMOS_BOUNDARY_LINEAR_H logical .true. linear or non-linear profile of relax region
    ATMOS_BOUNDARY_EXP_H real(RP) 2.0_RP factor of non-linear profile of relax region
    ATMOS_GRID_NUDGING_UV logical .false. grid nudging
    ATMOS_GRID_NUDGING_PT logical .false. grid nudging
    ATMOS_GRID_NUDGING_QV logical .false. grid nudging
    ATMOS_GRID_NUDGING_TAU real(RP) Damping tau for grid nudging [s]

History Output
namedescriptionunitvariable
DENS_BND Boundary Density kg/m3 ATMOS_BOUNDARY_DENS
PT_BND Boundary potential temperature K ATMOS_BOUNDARY_POTT
VELX_BND Boundary velocity x-direction m/s ATMOS_BOUNDARY_VELX
VELY_BND Boundary velocity y-direction m/s ATMOS_BOUNDARY_VELY
VELZ_BND Boundary velocity z-direction m/s ATMOS_BOUNDARY_VELZ
{TRACER_NAME}_BND {TRACER_NAME} in boundary;
{TRACER_NAME} depends on the physics schemes, e.g., QV, QC, QR.
kg/kg ATMOS_BOUNDARY_QTRC

Function/Subroutine Documentation

◆ atmos_boundary_driver_setup()

subroutine, public mod_atmos_bnd_driver::atmos_boundary_driver_setup

Setup.

Definition at line 179 of file mod_atmos_bnd_driver.F90.

179  use scale_prc, only: &
180  prc_abort
181  use scale_const, only: &
182  undef => const_undef
183  use scale_time, only: &
184  dt => time_dtsec
185  use scale_file, only: &
187  use scale_comm_cartesc_nest, only: &
188  online_use_velz, &
190  use_nesting, &
195  online_send_qa, &
197  use scale_atmos_hydrometeor, only: &
199  i_qv
200  use mod_atmos_phy_mp_vars, only: &
201  qs_mp, &
202  qe_mp
203  use mod_atmos_phy_ch_vars, only: &
204  qs_ch, &
205  qe_ch
206  use scale_atmos_grid_cartesc_real, only: &
208  implicit none
209 
210  namelist / param_atmos_boundary / &
211  atmos_boundary_type, &
212  atmos_boundary_in_basename, &
213  atmos_boundary_in_basename_add_num, &
214  atmos_boundary_in_number_of_files, &
215  atmos_boundary_in_check_coordinates, &
216  atmos_boundary_in_step_limit, &
217  atmos_boundary_in_aggregate, &
218  atmos_boundary_out_basename, &
219  atmos_boundary_out_title, &
220  atmos_boundary_out_dtype, &
221  atmos_boundary_out_aggregate, &
222  atmos_boundary_use_velz, &
223  atmos_boundary_use_velx, &
224  atmos_boundary_use_vely, &
225  atmos_boundary_use_pt, &
226  atmos_boundary_use_dens, &
227  atmos_boundary_use_qv, &
228  atmos_boundary_use_qhyd, &
229  atmos_boundary_use_chem, &
230  atmos_boundary_dens_adjust, &
231  atmos_boundary_dens_adjust_tau, &
232  atmos_boundary_value_velz, &
233  atmos_boundary_value_velx, &
234  atmos_boundary_value_vely, &
235  atmos_boundary_value_pt, &
236  atmos_boundary_value_qtrc, &
237  atmos_boundary_alphafact_dens, &
238  atmos_boundary_alphafact_velz, &
239  atmos_boundary_alphafact_velx, &
240  atmos_boundary_alphafact_vely, &
241  atmos_boundary_alphafact_pt, &
242  atmos_boundary_alphafact_qtrc, &
243  atmos_boundary_smoother_fact, &
244  atmos_boundary_fracz, &
245  atmos_boundary_fracx, &
246  atmos_boundary_fracy, &
247  atmos_boundary_tauz, &
248  atmos_boundary_taux, &
249  atmos_boundary_tauy, &
250  atmos_boundary_linear_v, &
251  atmos_boundary_linear_h, &
252  atmos_boundary_exp_h, &
253  atmos_grid_nudging_uv, &
254  atmos_grid_nudging_pt, &
255  atmos_grid_nudging_qv, &
256  atmos_grid_nudging_tau
257 
258  integer :: k, i, j, iq
259  integer :: ierr
260  !---------------------------------------------------------------------------
261 
262  log_newline
263  log_info("ATMOS_BOUNDARY_setup",*) 'Setup'
264 
265 
266  atmos_boundary_tauz = dt * 10.0_rp
267  atmos_boundary_taux = dt * 10.0_rp
268  atmos_boundary_tauy = dt * 10.0_rp
269 
270  atmos_boundary_in_aggregate = file_aggregate
271  atmos_boundary_out_aggregate = file_aggregate
272 
273  atmos_boundary_dens_adjust = .false.
274  atmos_boundary_dens_adjust_tau = -1.0_rp
275 
276  atmos_grid_nudging_tau = 10.0_rp * 24.0_rp * 3600.0_rp ! 10days [s]
277 
278 
279  !--- read namelist
280  rewind(io_fid_conf)
281  read(io_fid_conf,nml=param_atmos_boundary,iostat=ierr)
282  if( ierr < 0 ) then !--- missing
283  log_info("ATMOS_BOUNDARY_setup",*) 'Not found namelist. Default used.'
284  elseif( ierr > 0 ) then !--- fatal error
285  log_error("ATMOS_BOUNDARY_setup",*) 'Not appropriate names in namelist PARAM_ATMOS_BOUNDARY. Check!'
286  call prc_abort
287  endif
288  log_nml(param_atmos_boundary)
289 
290  ! setting switches
291  if( .NOT. use_nesting ) then
292  atmos_boundary_online = .false.
293  else
294  atmos_boundary_online = .true.
295  endif
296  do_parent_process = .false.
297  do_daughter_process = .false.
298  if ( atmos_boundary_online ) then
299  if ( online_iam_parent ) then
300  do_parent_process = .true.
301  endif
302  if ( online_iam_daughter ) then
303  do_daughter_process = .true.
304  atmos_boundary_use_velz = online_use_velz
305  atmos_boundary_use_qhyd = online_boundary_use_qhyd
306  endif
307  endif
308 
309  allocate( bnd_iq(qa) )
310  bnd_iq(:) = -1
311  bnd_qa = 0
312  if ( .not. atmos_hydrometeor_dry ) then
313  bnd_qa = bnd_qa + 1
314  bnd_iq(i_qv) = bnd_qa
315  if( atmos_boundary_use_qhyd ) then
316  do iq = qs_mp+1, qe_mp
317  bnd_qa = bnd_qa + 1
318  bnd_iq(iq) = bnd_qa
319  end do
320  end if
321  end if
322  if( atmos_boundary_use_chem ) then
323  do iq = qs_ch, qe_ch
324  bnd_qa = bnd_qa + 1
325  bnd_iq(iq) = bnd_qa
326  end do
327  endif
328  !$acc enter data copyin(BND_IQ)
329 
330  allocate( atmos_boundary_dens(ka,ia,ja) )
331  allocate( atmos_boundary_velz(ka,ia,ja) )
332  allocate( atmos_boundary_velx(ka,ia,ja) )
333  allocate( atmos_boundary_vely(ka,ia,ja) )
334  allocate( atmos_boundary_pott(ka,ia,ja) )
335  allocate( atmos_boundary_qtrc(ka,ia,ja,max(bnd_qa,1)) )
336  atmos_boundary_dens(:,:,:) = undef
337  atmos_boundary_velz(:,:,:) = undef
338  atmos_boundary_velx(:,:,:) = undef
339  atmos_boundary_vely(:,:,:) = undef
340  atmos_boundary_pott(:,:,:) = undef
341  atmos_boundary_qtrc(:,:,:,:) = undef
342  !$acc enter data create(ATMOS_BOUNDARY_DENS, ATMOS_BOUNDARY_VELZ, ATMOS_BOUNDARY_VELX, ATMOS_BOUNDARY_VELY, ATMOS_BOUNDARY_POTT, ATMOS_BOUNDARY_QTRC)
343 
344  allocate( atmos_boundary_alpha_dens(ka,ia,ja) )
345  allocate( atmos_boundary_alpha_velz(ka,ia,ja) )
346  allocate( atmos_boundary_alpha_velx(ka,ia,ja) )
347  allocate( atmos_boundary_alpha_vely(ka,ia,ja) )
348  allocate( atmos_boundary_alpha_pott(ka,ia,ja) )
349  allocate( atmos_boundary_alpha_qtrc(ka,ia,ja,max(bnd_qa,1)) )
350  atmos_boundary_alpha_dens(:,:,:) = 0.0_rp
351  atmos_boundary_alpha_velz(:,:,:) = 0.0_rp
352  atmos_boundary_alpha_velx(:,:,:) = 0.0_rp
353  atmos_boundary_alpha_vely(:,:,:) = 0.0_rp
354  atmos_boundary_alpha_pott(:,:,:) = 0.0_rp
355  atmos_boundary_alpha_qtrc(:,:,:,:) = 0.0_rp
356  !$acc enter data copyin(ATMOS_BOUNDARY_alpha_DENS, ATMOS_BOUNDARY_alpha_VELZ, ATMOS_BOUNDARY_alpha_VELX, ATMOS_BOUNDARY_alpha_VELY, ATMOS_BOUNDARY_alpha_POTT, ATMOS_BOUNDARY_alpha_QTRC)
357 
358  allocate( atmos_boundary_mflux_offset_x(ka,ja,2) )
359  allocate( atmos_boundary_mflux_offset_y(ka,ia,2) )
360  atmos_boundary_mflux_offset_x(:,:,:) = 0.0_rp
361  atmos_boundary_mflux_offset_y(:,:,:) = 0.0_rp
362  !$acc enter data copyin(ATMOS_BOUNDARY_MFLUX_OFFSET_X, ATMOS_BOUNDARY_MFLUX_OFFSET_Y)
363 
364  if ( atmos_boundary_type == 'REAL' .OR. do_daughter_process ) then
365  l_bnd = .true.
366  else
367  l_bnd = .false.
368  end if
369 
370  if ( l_bnd ) then
371 
372  allocate( dens_ref(ka,ia,ja) )
373  allocate( velx_ref(ka,ia,ja) )
374  allocate( vely_ref(ka,ia,ja) )
375  allocate( pott_ref(ka,ia,ja) )
376  allocate( qtrc_ref(ka,ia,ja,max(bnd_qa,1)) )
377  dens_ref(:,:,:) = 0.0_rp
378  velx_ref(:,:,:) = 0.0_rp
379  vely_ref(:,:,:) = 0.0_rp
380  pott_ref(:,:,:) = 0.0_rp
381  qtrc_ref(:,:,:,:) = 0.0_rp
382  !$acc enter data copyin(DENS_ref, VELX_ref, VELY_ref, POTT_ref, QTRC_ref)
383  if ( atmos_boundary_use_velz ) then
384  allocate( velz_ref(ka,ia,ja) )
385  velz_ref(:,:,:) = 0.0_rp
386  !$acc enter data copyin(VELZ_ref)
387  end if
388 
389  ! initialize boundary value (reading file or waiting parent domain)
390  if ( do_daughter_process ) then
391  call atmos_boundary_initialize_online
392  else
393  if ( atmos_boundary_in_basename /= '' ) then
394  call atmos_boundary_initialize_file
395  else
396  log_error("ATMOS_BOUNDARY_setup",*) 'You need specify ATMOS_BOUNDARY_IN_BASENAME'
397  call prc_abort
398  endif
399  endif
400 
401  if ( atmos_boundary_dens_adjust_tau <= 0.0_rp ) then
402  atmos_boundary_dens_adjust_tau = max( real(update_dt,kind=rp) / 6.0_rp, &
403  atmos_boundary_taux, atmos_boundary_tauy )
404  end if
405 
406  call atmos_boundary_setalpha
407 
408  atmos_boundary_update_flag = .true.
409 
410  ! for mass flux offset
411  if ( atmos_boundary_dens_adjust ) then
412  allocate( areazuy_w(ka,ja), areazuy_e(ka,ja) )
413  allocate( mflux_offset_x(ka,ja,2,2), mflux_offset_y(ka,ia,2,2) )
414  allocate( zero_x(ka,ja), zero_y(ka,ia) )
415 
416  !$omp parallel do
417  do j = js, je
418  do k = ks, ke
419  areazuy_w(k,j) = atmos_grid_cartesc_real_areazuy_x(k,is-1,j)
420  areazuy_e(k,j) = atmos_grid_cartesc_real_areazuy_x(k,ie ,j)
421  end do
422  end do
423  !$omp parallel do
424  do j = js, je
425  do k = ks, ke
426  mflux_offset_x(k,j,:,:) = 0.0_rp
427  end do
428  end do
429  !$omp parallel do
430  do i = is, ie
431  do k = ks, ke
432  mflux_offset_y(k,i,:,:) = 0.0_rp
433  end do
434  end do
435 
436  !$omp parallel do
437  do j = js, je
438  do k = ks, ke
439  zero_x(k,j) = 0.0_rp
440  end do
441  end do
442  !$omp parallel do
443  do i = is, ie
444  do k = ks, ke
445  zero_y(k,i) = 0.0_rp
446  end do
447  end do
448 
449  !$acc enter data copyin(AREAZUY_W, AREAZUY_E, MFLUX_OFFSET_X, MFLUX_OFFSET_Y, zero_x, zero_y)
450  end if
451 
452  elseif ( atmos_boundary_type == 'NONE' ) then
453 
454  atmos_boundary_update_flag = .false.
455 
456  elseif ( atmos_boundary_type == 'CONST' ) then
457 
458  call atmos_boundary_setalpha
459 
460  atmos_boundary_update_flag = .false.
461 
462  elseif ( atmos_boundary_type == 'INIT' ) then
463 
464  call atmos_boundary_setalpha
465 
466  atmos_boundary_update_flag = .false.
467 
468  elseif ( atmos_boundary_type == 'OFFLINE' ) then
469 
470  if ( atmos_boundary_in_basename /= '' ) then
471  call atmos_boundary_read
472  else
473  log_error("ATMOS_BOUNDARY_setup",*) 'You need specify ATMOS_BOUNDARY_IN_BASENAME'
474  call prc_abort
475  endif
476 
477  atmos_boundary_update_flag = .false.
478 
479  else
480  log_error("ATMOS_BOUNDARY_setup",*) 'unsupported ATMOS_BOUNDARY_TYPE. Check!', trim(atmos_boundary_type)
481  call prc_abort
482  endif
483 
484  if ( use_nesting ) atmos_boundary_update_flag = .true.
485 
486 
487  !----- report data -----
488  log_newline
489  log_info("ATMOS_BOUNDARY_setup",*) 'Atmospheric boundary parameters '
490  log_info_cont(*) 'Atmospheric boundary type : ', atmos_boundary_type
491  log_newline
492  log_info_cont(*) 'Is VELZ used in atmospheric boundary? : ', atmos_boundary_use_velz
493  log_info_cont(*) 'Is VELX used in atmospheric boundary? : ', atmos_boundary_use_velx
494  log_info_cont(*) 'Is VELY used in atmospheric boundary? : ', atmos_boundary_use_vely
495  log_info_cont(*) 'Is PT used in atmospheric boundary? : ', atmos_boundary_use_pt
496  log_info_cont(*) 'Is DENS used in atmospheric boundary? : ', atmos_boundary_use_dens
497  log_info_cont(*) 'Is QV used in atmospheric boundary? : ', atmos_boundary_use_qv
498  log_info_cont(*) 'Is QHYD used in atmospheric boundary? : ', atmos_boundary_use_qhyd
499  log_info_cont(*) 'Is CHEM used in atmospheric boundary? : ', atmos_boundary_use_chem
500  log_newline
501  log_info_cont(*) 'Atmospheric boundary VELZ values : ', atmos_boundary_value_velz
502  log_info_cont(*) 'Atmospheric boundary VELX values : ', atmos_boundary_value_velx
503  log_info_cont(*) 'Atmospheric boundary VELY values : ', atmos_boundary_value_vely
504  log_info_cont(*) 'Atmospheric boundary PT values : ', atmos_boundary_value_pt
505  log_info_cont(*) 'Atmospheric boundary QTRC values : ', atmos_boundary_value_qtrc
506  log_newline
507  log_info_cont(*) 'Atmospheric boundary smoother factor : ', atmos_boundary_smoother_fact
508  log_info_cont(*) 'Atmospheric boundary z-fraction : ', atmos_boundary_fracz
509  log_info_cont(*) 'Atmospheric boundary x-fraction : ', atmos_boundary_fracx
510  log_info_cont(*) 'Atmospheric boundary y-fraction : ', atmos_boundary_fracy
511  log_info_cont(*) 'Atmospheric boundary z-relaxation time : ', atmos_boundary_tauz
512  log_info_cont(*) 'Atmospheric boundary x-relaxation time : ', atmos_boundary_taux
513  log_info_cont(*) 'Atmospheric boundary y-relaxation time : ', atmos_boundary_tauy
514  log_newline
515  log_newline
516  log_info_cont(*) 'Linear profile in vertically relax region : ', atmos_boundary_linear_v
517  log_info_cont(*) 'Linear profile in horizontally relax region : ', atmos_boundary_linear_h
518  log_info_cont(*) 'Non-linear factor in horizontally relax region : ', atmos_boundary_exp_h
519  log_newline
520  log_info_cont(*) 'Online nesting for lateral boundary : ', atmos_boundary_online
521  log_info_cont(*) 'Does lateral boundary exist in this domain? : ', l_bnd
522  log_newline
523  log_info_cont(*) 'Is grid nudging used for VELX & VELY? : ', atmos_grid_nudging_uv
524  log_info_cont(*) 'Is grid nudging used for POTT? : ', atmos_grid_nudging_pt
525  log_info_cont(*) 'Is grid nudging used for QV? : ', atmos_grid_nudging_qv
526  log_info_cont(*) 'Relaxation time for grid nudging : ', atmos_grid_nudging_tau
527  log_info_cont(*) 'Density adjustment : ', atmos_boundary_dens_adjust
528  if ( atmos_boundary_dens_adjust ) then
529  log_info_cont(*) 'Density relaxation time : ', atmos_boundary_dens_adjust_tau
530  end if
531 
532  if ( online_send_diagqhyd ) then
533  allocate( q_send_work(ka,ia,ja,online_send_qa) )
534  !$acc enter data create( Q_SEND_WORK )
535  end if
536  if ( online_recv_diagqhyd ) then
537  allocate( q_recv_work(ka,ia,ja,online_recv_qa) )
538  !$acc enter data create( Q_RECV_WORK )
539  end if
540 
541  return

References atmos_boundary_alpha_dens, atmos_boundary_alpha_pott, atmos_boundary_alpha_qtrc, atmos_boundary_alpha_velx, atmos_boundary_alpha_vely, atmos_boundary_alpha_velz, atmos_boundary_dens, atmos_boundary_mflux_offset_x, atmos_boundary_mflux_offset_y, atmos_boundary_pott, atmos_boundary_qtrc, atmos_boundary_smoother_fact, atmos_boundary_update_flag, atmos_boundary_velx, atmos_boundary_vely, atmos_boundary_velz, scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazuy_x, scale_atmos_hydrometeor::atmos_hydrometeor_dry, bnd_iq, bnd_qa, scale_const::const_undef, scale_file::file_aggregate, scale_atmos_hydrometeor::i_qv, scale_atmos_grid_cartesc_index::ia, scale_atmos_grid_cartesc_index::ie, scale_io::io_fid_conf, scale_atmos_grid_cartesc_index::is, scale_atmos_grid_cartesc_index::ja, scale_atmos_grid_cartesc_index::je, scale_atmos_grid_cartesc_index::js, scale_tracer::k, scale_atmos_grid_cartesc_index::ka, scale_atmos_grid_cartesc_index::ke, scale_atmos_grid_cartesc_index::ks, scale_comm_cartesc_nest::online_boundary_use_qhyd, scale_comm_cartesc_nest::online_iam_daughter, scale_comm_cartesc_nest::online_iam_parent, scale_comm_cartesc_nest::online_recv_diagqhyd, scale_comm_cartesc_nest::online_recv_qa, scale_comm_cartesc_nest::online_send_diagqhyd, scale_comm_cartesc_nest::online_send_qa, scale_comm_cartesc_nest::online_use_velz, scale_prc::prc_abort(), scale_tracer::qa, mod_atmos_phy_ch_vars::qe_ch, mod_atmos_phy_mp_vars::qe_mp, mod_atmos_phy_ch_vars::qs_ch, mod_atmos_phy_mp_vars::qs_mp, real, scale_precision::rp, scale_time::time_dtsec, and scale_comm_cartesc_nest::use_nesting.

Referenced by mod_atmos_driver::atmos_driver_setup().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_boundary_driver_set()

subroutine, public mod_atmos_bnd_driver::atmos_boundary_driver_set ( real(dp), intent(in)  time)

set

Definition at line 548 of file mod_atmos_bnd_driver.F90.

548  use scale_const, only: &
549  pi => const_pi
550  use mod_atmos_vars, only: &
551  dens, &
552  momz, &
553  momx, &
554  momy, &
555  rhot, &
556  qtrc, &
557  qv, &
558  qe
559  use mod_atmos_phy_mp_vars, only: &
560  qs_mp, &
561  qe_mp
562  implicit none
563  real(DP), intent(in) :: time
564 
565  real(RP) :: total
566  integer :: n
567 
568  if ( do_parent_process ) then !online [parent]
569  call atmos_boundary_firstsend( &
570  dens, momz, momx, momy, rhot, qtrc(:,:,:,qs_mp:qe_mp), qv, qe )
571  end if
572 
573  if ( l_bnd ) then
574 
575  if ( atmos_boundary_dens_adjust ) then
576  now_step = 0
577  allocate( offset_time_fact(0:update_nstep) )
578  total = 0.0_rp
579  !$omp parallel do reduction(+:total)
580  do n = 0, update_nstep
581  offset_time_fact(n) = 1.0_rp - cos( 2.0_rp * pi * ( n - 1 ) / update_nstep )
582  total = total + offset_time_fact(n)
583  end do
584  total = total / update_nstep
585  !$omp parallel do
586  do n = 0, update_nstep
587  offset_time_fact(n) = offset_time_fact(n) / total
588  end do
589  end if
590 
591  ! initialize boundary value (reading file or waiting parent domain)
592  if ( do_daughter_process ) then
593  call atmos_boundary_set_online( time )
594  else
595  if ( atmos_boundary_in_basename /= '' ) then
596  call atmos_boundary_set_file( time )
597  endif
598  endif
599 
600  elseif ( atmos_boundary_type == 'CONST' ) then
601 
602  call atmos_boundary_generate
603 
604  elseif ( atmos_boundary_type == 'INIT' ) then
605 
606  call atmos_boundary_setinitval( dens, & ! [IN]
607  momz, & ! [IN]
608  momx, & ! [IN]
609  momy, & ! [IN]
610  rhot, & ! [IN]
611  qtrc ) ! [IN]
612  endif
613 
614  if( atmos_boundary_out_basename /= '' ) then
615  call atmos_boundary_write
616  endif
617 
618  if ( atmos_boundary_update_flag ) then
619 
620  call history_bnd( &
621  atmos_boundary_dens, &
622  atmos_boundary_velz, &
623  atmos_boundary_velx, &
624  atmos_boundary_vely, &
625  atmos_boundary_pott, &
626  atmos_boundary_qtrc )
627  end if
628 
629  return

References atmos_boundary_alpha_dens, atmos_boundary_alpha_pott, atmos_boundary_alpha_qtrc, atmos_boundary_alpha_velx, atmos_boundary_alpha_vely, atmos_boundary_alpha_velz, atmos_boundary_dens, atmos_boundary_pott, atmos_boundary_qtrc, atmos_boundary_set_file(), atmos_boundary_set_online(), atmos_boundary_update_flag, atmos_boundary_velx, atmos_boundary_vely, atmos_boundary_velz, scale_atmos_grid_cartesc::atmos_grid_cartesc_cbfx, scale_atmos_grid_cartesc::atmos_grid_cartesc_cbfy, scale_atmos_grid_cartesc::atmos_grid_cartesc_cbfz, scale_atmos_grid_cartesc::atmos_grid_cartesc_fbfx, scale_atmos_grid_cartesc::atmos_grid_cartesc_fbfy, scale_atmos_grid_cartesc::atmos_grid_cartesc_fbfz, scale_atmos_refstate::atmos_refstate_dens, bnd_iq, bnd_qa, scale_const::const_eps, scale_const::const_pi, dens, scale_file_cartesc::file_cartesc_close(), scale_file_cartesc::file_cartesc_create(), scale_file_cartesc::file_cartesc_def_var(), scale_file_cartesc::file_cartesc_enddef(), scale_file_cartesc::file_cartesc_flush(), scale_file_cartesc::file_cartesc_open(), history_bnd(), scale_atmos_hydrometeor::i_qv, scale_atmos_grid_cartesc_index::ia, scale_atmos_grid_cartesc_index::ja, scale_tracer::k, scale_atmos_grid_cartesc_index::ke, scale_atmos_grid_cartesc_index::ks, mod_atmos_vars::momx, mod_atmos_vars::momy, mod_atmos_vars::momz, scale_prc::prc_abort(), scale_tracer::qa, mod_atmos_vars::qe, mod_atmos_phy_mp_vars::qe_mp, mod_atmos_phy_mp_vars::qs_mp, qtrc, mod_atmos_vars::qv, mod_atmos_vars::rhot, scale_time::time_dtsec, scale_tracer::tracer_name, and scale_tracer::tracer_unit.

Referenced by mod_rm_driver::restart_read().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_boundary_set_file()

subroutine mod_atmos_bnd_driver::atmos_boundary_set_file ( real(dp), intent(in)  time)

Set boundary value for real case experiment.

Definition at line 1383 of file mod_atmos_bnd_driver.F90.

1383  use scale_file_external_input, only: &
1384  file_external_input_get_ref, &
1385  i_prev
1386  implicit none
1387  real(DP), intent(in) :: time
1388 
1389  logical :: error
1390  !---------------------------------------------------------------------------
1391 
1392  if ( atmos_boundary_dens_adjust ) then
1393  call file_external_input_get_ref( 'DENS', dens_ref(:,:,:), error, i_prev )
1394  call file_external_input_get_ref( 'VELX', velx_ref(:,:,:), error, i_prev )
1395  call file_external_input_get_ref( 'VELY', vely_ref(:,:,:), error, i_prev )
1396  call calc_mass
1397  end if
1398 
1399  ! read boundary data from input file
1400  call atmos_boundary_update_file( time )
1401 
1402  return

References bnd_qa, calc_mass(), scale_comm_cartesc_nest::comm_cartesc_nest_recvwait_issue_recv(), scale_file_external_input::i_prev, scale_comm_cartesc_nest::online_parent_dtsec, scale_comm_cartesc_nest::online_parent_nstep, scale_comm_cartesc_nest::online_recv_qa, scale_prc::prc_abort(), scale_time::time_dtsec, and scale_time::time_nstep.

Referenced by atmos_boundary_driver_set().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_boundary_set_online()

subroutine mod_atmos_bnd_driver::atmos_boundary_set_online ( real(dp), intent(in)  time)

Set boundary value for real case experiment [online daughter].

Definition at line 1447 of file mod_atmos_bnd_driver.F90.

1447  use scale_time, only: &
1449  use scale_comm_cartesc_nest, only: &
1450  parent_dtsec => online_parent_dtsec, &
1451  parent_nstep => online_parent_nstep
1452  use scale_file_external_input, only: &
1453  file_external_input_regist
1454  implicit none
1455  real(DP), intent(in) :: time
1456 
1457  integer :: nstep
1458  integer :: iq, iqb
1459  !---------------------------------------------------------------------------
1460 
1461  ! import data from parent domain
1462  call atmos_boundary_update_online_daughter( time, .true., .true. )
1463 
1464  nstep = parent_nstep + 1
1465 
1466  call file_external_input_regist( 'DENS', & ! [IN]
1467  dens_ref(:,:,:), & ! [IN]
1468  'ZXY', & ! [IN]
1469  nstep, & ! [IN]
1470  time, & ! [IN]
1471  parent_dtsec ) ! [IN]
1472 
1473  call file_external_input_regist( 'VELX', & ! [IN]
1474  velx_ref(:,:,:), & ! [IN]
1475  'ZXY', & ! [IN]
1476  nstep, & ! [IN]
1477  time, & ! [IN]
1478  parent_dtsec ) ! [IN]
1479 
1480  call file_external_input_regist( 'VELY', & ! [IN]
1481  vely_ref(:,:,:), & ! [IN]
1482  'ZXY', & ! [IN]
1483  nstep, & ! [IN]
1484  time, & ! [IN]
1485  parent_dtsec ) ! [IN]
1486 
1487  call file_external_input_regist( 'PT', & ! [IN]
1488  pott_ref(:,:,:), & ! [IN]
1489  'ZXY', & ! [IN]
1490  nstep, & ! [IN]
1491  time, & ! [IN]
1492  parent_dtsec ) ! [IN]
1493 
1494  do iq = 1, qa
1495  iqb = bnd_iq(iq)
1496  if ( iqb > 0 ) &
1497  call file_external_input_regist( tracer_name(iq), & ! [IN]
1498  qtrc_ref(:,:,:,iqb), & ! [IN]
1499  'ZXY', & ! [IN]
1500  nstep, & ! [IN]
1501  time, & ! [IN]
1502  parent_dtsec ) ! [IN]
1503  end do
1504 
1505  if ( atmos_boundary_use_velz ) then
1506  call file_external_input_regist( 'VELZ', & ! [IN]
1507  velz_ref(:,:,:), & ! [IN]
1508  'ZXY', & ! [IN]
1509  nstep, & ! [IN]
1510  time, & ! [IN]
1511  parent_dtsec ) ! [IN]
1512 
1513  end if
1514 
1515  call atmos_boundary_update_online_daughter( time, .false., .true. )
1516 
1517  return

References bnd_iq, scale_atmos_hydrometeor::n_hyd, scale_comm_cartesc_nest::online_parent_dtsec, scale_comm_cartesc_nest::online_parent_nstep, scale_tracer::qa, mod_atmos_phy_mp_vars::qa_mp, scale_time::time_nowdaysec, and scale_tracer::tracer_name.

Referenced by atmos_boundary_driver_set().

Here is the caller graph for this function:

◆ atmos_boundary_driver_finalize()

subroutine, public mod_atmos_bnd_driver::atmos_boundary_driver_finalize

Finalize boundary value.

Definition at line 1553 of file mod_atmos_bnd_driver.F90.

1553  use scale_comm_cartesc_nest, only: &
1556  use scale_file_cartesc, only: &
1558  implicit none
1559 
1560  !---------------------------------------------------------------------------
1561 
1562  if ( do_parent_process ) then !online [parent]
1564  endif
1565 
1566  if ( do_daughter_process ) then !online [daughter]
1568  endif
1569 
1570  !$acc exit data delete(BND_IQ)
1571  deallocate( bnd_iq )
1572 
1573  !$acc exit data delete(ATMOS_BOUNDARY_DENS, ATMOS_BOUNDARY_VELZ, ATMOS_BOUNDARY_VELX, ATMOS_BOUNDARY_VELY, ATMOS_BOUNDARY_POTT, ATMOS_BOUNDARY_QTRC)
1574  deallocate( atmos_boundary_dens )
1575  deallocate( atmos_boundary_velz )
1576  deallocate( atmos_boundary_velx )
1577  deallocate( atmos_boundary_vely )
1578  deallocate( atmos_boundary_pott )
1579  deallocate( atmos_boundary_qtrc )
1580 
1581  !$acc exit data delete(ATMOS_BOUNDARY_alpha_DENS, ATMOS_BOUNDARY_alpha_VELZ, ATMOS_BOUNDARY_alpha_VELX, ATMOS_BOUNDARY_alpha_VELY, ATMOS_BOUNDARY_alpha_POTT, ATMOS_BOUNDARY_alpha_QTRC)
1582  deallocate( atmos_boundary_alpha_dens )
1583  deallocate( atmos_boundary_alpha_velz )
1584  deallocate( atmos_boundary_alpha_velx )
1585  deallocate( atmos_boundary_alpha_vely )
1586  deallocate( atmos_boundary_alpha_pott )
1587  deallocate( atmos_boundary_alpha_qtrc )
1588 
1589  !$acc exit data delete(ATMOS_BOUNDARY_MFLUX_OFFSET_X, ATMOS_BOUNDARY_MFLUX_OFFSET_Y)
1590  deallocate( atmos_boundary_mflux_offset_x )
1591  deallocate( atmos_boundary_mflux_offset_y )
1592 
1593  if ( l_bnd ) then
1594  !$acc exit data delete(DENS_ref, VELX_ref, VELY_ref, POTT_ref, QTRC_ref)
1595  deallocate( dens_ref )
1596  deallocate( velx_ref )
1597  deallocate( vely_ref )
1598  deallocate( pott_ref )
1599  deallocate( qtrc_ref )
1600 
1601  if ( atmos_boundary_use_velz ) then
1602  !$acc exit data delete(VELZ_ref)
1603  deallocate( velz_ref )
1604  end if
1605 
1606  if ( atmos_boundary_dens_adjust ) then
1607  !$acc exit data delete(AREAZUY_W, AREAZUY_E, MFLUX_OFFSET_X, MFLUX_OFFSET_Y, zero_x, zero_y)
1608  deallocate( areazuy_w, areazuy_e )
1609  deallocate( mflux_offset_x, mflux_offset_y )
1610  deallocate( zero_x )
1611  deallocate( zero_y )
1612  end if
1613  end if
1614 
1615  if ( allocated( q_send_work ) ) then
1616  !$acc exit data delete(Q_SEND_WORK)
1617  deallocate( q_send_work )
1618  end if
1619  if ( allocated( q_recv_work ) ) then
1620  !$acc exit data delete(Q_RECV_WORK)
1621  deallocate( q_recv_work )
1622  end if
1623 
1624 
1625  return

References atmos_boundary_alpha_dens, atmos_boundary_alpha_pott, atmos_boundary_alpha_qtrc, atmos_boundary_alpha_velx, atmos_boundary_alpha_vely, atmos_boundary_alpha_velz, atmos_boundary_dens, atmos_boundary_mflux_offset_x, atmos_boundary_mflux_offset_y, atmos_boundary_pott, atmos_boundary_qtrc, atmos_boundary_velx, atmos_boundary_vely, atmos_boundary_velz, bnd_iq, scale_comm_cartesc_nest::comm_cartesc_nest_recv_cancel_recv(), scale_comm_cartesc_nest::comm_cartesc_nest_recvwait_issue_send(), and scale_file_cartesc::file_cartesc_close().

Referenced by mod_atmos_driver::atmos_driver_finalize().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_boundary_driver_update()

subroutine, public mod_atmos_bnd_driver::atmos_boundary_driver_update ( real(dp), intent(in)  time)

Update boundary value with a constant time boundary.

Definition at line 1632 of file mod_atmos_bnd_driver.F90.

1632  use scale_prc, only: &
1633  prc_abort
1634  use mod_atmos_phy_mp_vars, only: &
1635  qs_mp
1636  use scale_comm_cartesc_nest, only: &
1638  implicit none
1639  real(DP), intent(in) :: time
1640 
1641  !---------------------------------------------------------------------------
1642 
1643  if ( l_bnd ) then
1644 
1645  if ( do_daughter_process ) then !online [daughter]
1646  call atmos_boundary_update_online_daughter( time, .false., .false. )
1647  else
1648  call atmos_boundary_update_file( time )
1649  end if
1650 
1651  call set_boundary
1652 
1653  elseif ( do_parent_process ) then
1654  ! do nothing
1655  else
1656  log_error("ATMOS_BOUNDARY_driver_update",*) '[BUG] invalid path'
1657  call prc_abort
1658  end if
1659 
1660  call history_bnd( atmos_boundary_dens, &
1661  atmos_boundary_velz, &
1662  atmos_boundary_velx, &
1663  atmos_boundary_vely, &
1664  atmos_boundary_pott, &
1665  atmos_boundary_qtrc )
1666 
1667  ! To be enable to do asynchronous communicaton
1668  if ( do_daughter_process ) then !online [daughter]
1670  endif
1671 
1672  return

References atmos_boundary_dens, atmos_boundary_pott, atmos_boundary_qtrc, atmos_boundary_velx, atmos_boundary_vely, atmos_boundary_velz, scale_comm_cartesc_nest::comm_cartesc_nest_test_recv(), history_bnd(), scale_prc::prc_abort(), mod_atmos_phy_mp_vars::qs_mp, and set_boundary().

Referenced by mod_atmos_driver::atmos_driver_update().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_boundary_driver_send()

subroutine, public mod_atmos_bnd_driver::atmos_boundary_driver_send

Send data to child domain.

Definition at line 1678 of file mod_atmos_bnd_driver.F90.

1678  use scale_comm_cartesc_nest, only: &
1680  use mod_atmos_vars, only: &
1681  dens, &
1682  momz, &
1683  momx, &
1684  momy, &
1685  rhot, &
1686  qtrc, &
1687  qv, &
1688  qe
1689  use mod_atmos_phy_mp_vars, only: &
1690  qs_mp, &
1691  qe_mp
1692  implicit none
1693 
1694  !---------------------------------------------------------------------------
1695 
1696  if ( do_parent_process ) then !online [parent]
1697  ! should be called every time step
1698  call atmos_boundary_update_online_parent( dens,momz,momx,momy,rhot,qtrc(:,:,:,qs_mp:qe_mp), qv, qe )
1699 
1700  ! To be enable to do asynchronous communicaton
1702  endif
1703 
1704  return

References atmos_boundary_dens, atmos_boundary_pott, atmos_boundary_qtrc, atmos_boundary_velx, atmos_boundary_vely, atmos_boundary_velz, mod_atmos_phy_mp_driver::atmos_phy_mp_driver_qhyd2qtrc(), bnd_iq, calc_mass(), scale_comm_cartesc_nest::comm_cartesc_nest_nestdown_recv(), scale_comm_cartesc_nest::comm_cartesc_nest_nestdown_send(), scale_comm_cartesc_nest::comm_cartesc_nest_recvwait_issue_recv(), scale_comm_cartesc_nest::comm_cartesc_nest_recvwait_issue_send(), scale_comm_cartesc_nest::comm_cartesc_nest_test_send(), dens, scale_file_external_input::file_external_input_query(), scale_atmos_grid_cartesc_index::ia, scale_atmos_grid_cartesc_index::ja, scale_atmos_grid_cartesc_index::ka, scale_atmos_grid_cartesc_index::ke, scale_atmos_grid_cartesc_index::ks, mod_atmos_vars::momx, mod_atmos_vars::momy, mod_atmos_vars::momz, scale_atmos_hydrometeor::n_hyd, scale_comm_cartesc_nest::online_recv_diagqhyd, scale_comm_cartesc_nest::online_recv_qa, scale_comm_cartesc_nest::online_send_diagqhyd, scale_comm_cartesc_nest::online_send_qa, scale_prc::prc_abort(), scale_tracer::qa, mod_atmos_phy_mp_vars::qa_mp, mod_atmos_vars::qe, mod_atmos_phy_mp_vars::qe_mp, mod_atmos_phy_mp_vars::qs_mp, qtrc, mod_atmos_vars::qv, mod_atmos_vars::rhot, set_offset(), and scale_tracer::tracer_name.

Referenced by mod_atmos_driver::atmos_driver_update().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ set_boundary()

subroutine mod_atmos_bnd_driver::set_boundary

Definition at line 2003 of file mod_atmos_bnd_driver.F90.

2003  use scale_prc_cartesc, only: &
2004  prc_has_w, &
2005  prc_has_e, &
2006  prc_has_s, &
2007  prc_has_n
2008  use mod_atmos_vars, only: &
2009  dens, &
2010  momz, &
2011  momx, &
2012  momy, &
2013  rhot, &
2014  qtrc
2015  implicit none
2016 
2017  integer :: i, j, k, iq, iqb
2018 
2019  !$acc data copy(DENS, MOMZ, MOMX, MOMY, RHOT, QTRC)
2020 
2021  ! fill HALO in western region
2022  if ( .NOT. prc_has_w ) then
2023  !$omp parallel do default(none) OMP_SCHEDULE_ collapse(2) &
2024  !$omp shared(JA,JS,IS,KS,KE,QA,DENS,MOMX,RHOT,QTRC) &
2025  !$omp shared(ATMOS_BOUNDARY_DENS,ATMOS_BOUNDARY_VELX) &
2026  !$omp shared(ATMOS_BOUNDARY_POTT,ATMOS_BOUNDARY_QTRC) &
2027  !$omp shared(BND_QA,BND_IQ) &
2028  !$omp private(i,j,k,iq,iqb)
2029  !$acc kernels
2030  !$acc loop collapse(3) independent
2031  do j = 1, ja
2032  do i = 1, is-1
2033  do k = ks, ke
2034  dens(k,i,j) = atmos_boundary_dens(k,i,j)
2035  momx(k,i,j) = atmos_boundary_velx(k,i,j) &
2036  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i+1,j) ) * 0.5_rp
2037  rhot(k,i,j) = atmos_boundary_pott(k,i,j) * atmos_boundary_dens(k,i,j)
2038  !$acc loop seq
2039  do iq = 1, qa
2040  iqb = bnd_iq(iq)
2041  if ( iqb > 0 ) then
2042  qtrc(k,i,j,iq) = atmos_boundary_qtrc(k,i,j,iqb)
2043  else
2044  qtrc(k,i,j,iq) = qtrc(k,is,j,iq)
2045  end if
2046  end do
2047  end do
2048  end do
2049  end do
2050  !$acc end kernels
2051  !$omp parallel do
2052  !$acc kernels
2053  do j = 1, ja-1
2054  do i = 1, is-1
2055  do k = ks, ke
2056  momy(k,i,j) = atmos_boundary_vely(k,i,j) &
2057  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i,j+1) ) * 0.5_rp
2058  end do
2059  end do
2060  end do
2061  !$acc end kernels
2062  !$acc kernels
2063  do i = 1, is-1
2064  do k = ks, ke
2065  momy(k,i,ja) = atmos_boundary_vely(k,i,ja) &
2066  * atmos_boundary_dens(k,i,ja)
2067  end do
2068  end do
2069  !$acc end kernels
2070  if ( atmos_boundary_use_velz ) then
2071  !$omp parallel do
2072  !$acc kernels
2073  do j = 1, ja
2074  do i = 1, is-1
2075  do k = ks, ke-1
2076  momz(k,i,j) = atmos_boundary_velz(k,i,j) &
2077  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k+1,i,j) ) * 0.5_rp
2078  end do
2079  end do
2080  end do
2081  !$acc end kernels
2082  else
2083  !$omp parallel do
2084  !$acc kernels
2085  do j = 1, ja
2086  !$acc loop independent
2087  do i = 1, is-1
2088  do k = ks, ke-1
2089  momz(k,i,j) = momz(k,is,j)
2090  end do
2091  end do
2092  end do
2093  !$acc end kernels
2094  end if
2095  end if
2096 
2097  ! fill HALO in eastern region
2098  if ( .NOT. prc_has_e ) then
2099  !$omp parallel do default(none) OMP_SCHEDULE_ collapse(2) &
2100  !$omp shared(JA,IE,IA,KS,KE,QA) &
2101  !$omp shared(DENS,RHOT,QTRC) &
2102  !$omp shared(ATMOS_BOUNDARY_DENS,ATMOS_BOUNDARY_VELX) &
2103  !$omp shared(ATMOS_BOUNDARY_POTT,ATMOS_BOUNDARY_QTRC) &
2104  !$omp shared(BND_QA,BND_IQ) &
2105  !$omp private(i,j,k,iq,iqb)
2106  !$acc kernels
2107  !$acc loop collapse(3) independent
2108  do j = 1, ja
2109  do i = ie+1, ia
2110  do k = ks, ke
2111  dens(k,i,j) = atmos_boundary_dens(k,i,j)
2112  rhot(k,i,j) = atmos_boundary_pott(k,i,j) * atmos_boundary_dens(k,i,j)
2113  !$acc loop seq
2114  do iq = 1, qa
2115  iqb = bnd_iq(iq)
2116  if ( iqb > 0 ) then
2117  qtrc(k,i,j,iq) = atmos_boundary_qtrc(k,i,j,iqb)
2118  else
2119  qtrc(k,i,j,iq) = qtrc(k,ie,j,iq)
2120  end if
2121  end do
2122  end do
2123  end do
2124  end do
2125  !$acc end kernels
2126  !$omp parallel do
2127  !$acc kernels
2128  do j = 1, ja
2129  do i = ie, ia-1
2130  do k = ks, ke
2131  momx(k,i,j) = atmos_boundary_velx(k,i,j) &
2132  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i+1,j) ) * 0.5_rp
2133  end do
2134  end do
2135  end do
2136  !$acc end kernels
2137  !$omp parallel do
2138  !$acc kernels
2139  do j = 1, ja
2140  do k = ks, ke
2141  momx(k,ia,j) = atmos_boundary_velx(k,ia,j) * atmos_boundary_dens(k,ia,j)
2142  end do
2143  end do
2144  !$acc end kernels
2145  !$omp parallel do
2146  !$acc kernels
2147  do j = 1, ja-1
2148  do i = ie+1, ia
2149  do k = ks, ke
2150  momy(k,i,j) = atmos_boundary_vely(k,i,j) &
2151  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i,j+1) ) * 0.5_rp
2152  end do
2153  end do
2154  end do
2155  !$acc end kernels
2156  !$acc kernels
2157  do i = ie+1, ia
2158  do k = ks, ke
2159  momy(k,i,ja) = atmos_boundary_vely(k,i,ja) &
2160  * atmos_boundary_dens(k,i,ja)
2161  end do
2162  end do
2163  !$acc end kernels
2164  if ( atmos_boundary_use_velz ) then
2165  !$omp parallel do
2166  !$acc kernels
2167  do j = 1, ja
2168  do i = ie+1, ia
2169  do k = ks, ke-1
2170  momz(k,i,j) = atmos_boundary_velz(k,i,j) &
2171  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k+1,i,j) ) * 0.5_rp
2172  end do
2173  end do
2174  end do
2175  !$acc end kernels
2176  else
2177  !$omp parallel do
2178  !$acc kernels
2179  do j = 1, ja
2180  do i = ie+1, ia
2181  do k = ks, ke-1
2182  momz(k,i,j) = momz(k,ie,j)
2183  end do
2184  end do
2185  end do
2186  !$acc end kernels
2187  end if
2188  end if
2189 
2190  ! fill HALO in southern region
2191  if ( .NOT. prc_has_s ) then
2192  !$acc kernels
2193  !$acc loop collapse(3) independent
2194  do j = 1, js-1
2195  do i = 1, ia
2196  do k = ks, ke
2197  dens(k,i,j) = atmos_boundary_dens(k,i,j)
2198  momy(k,i,j) = atmos_boundary_vely(k,i,j) &
2199  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i,j+1) ) * 0.5_rp
2200  rhot(k,i,j) = atmos_boundary_pott(k,i,j) * atmos_boundary_dens(k,i,j)
2201  !$acc loop seq
2202  do iq = 1, qa
2203  iqb = bnd_iq(iq)
2204  if ( iqb > 0 ) then
2205  qtrc(k,i,j,iq) = atmos_boundary_qtrc(k,i,j,iqb)
2206  else
2207  qtrc(k,i,j,iq) = qtrc(k,i,js,iq)
2208  end if
2209  end do
2210  end do
2211  end do
2212  end do
2213  !$acc end kernels
2214  !$acc kernels
2215  do j = 1, js-1
2216  do i = 1, ia-1
2217  do k = ks, ke
2218  momx(k,i,j) = atmos_boundary_velx(k,i,j) &
2219  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i+1,j) ) * 0.5_rp
2220  end do
2221  end do
2222  end do
2223  !$acc end kernels
2224  !$acc kernels
2225  do j = 1, js-1
2226  do k = ks, ke
2227  momx(k,ia,j) = atmos_boundary_velx(k,ia,j) &
2228  * atmos_boundary_dens(k,ia,j)
2229  end do
2230  end do
2231  !$acc end kernels
2232  if ( atmos_boundary_use_velz ) then
2233  !$acc kernels
2234  do j = 1, js-1
2235  do i = 1, ia
2236  do k = ks, ke-1
2237  momz(k,i,j) = atmos_boundary_velz(k,i,j) &
2238  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k+1,i,j) ) * 0.5_rp
2239  end do
2240  end do
2241  end do
2242  !$acc end kernels
2243  else
2244  !$acc kernels
2245  !$acc loop independent
2246  do j = 1, js-1
2247  do i = 1, ia
2248  do k = ks, ke-1
2249  momz(k,i,j) = momz(k,i,js)
2250  end do
2251  end do
2252  end do
2253  !$acc end kernels
2254  end if
2255  end if
2256 
2257  ! fill HALO in northern region
2258  if ( .NOT. prc_has_n ) then
2259  !$acc kernels
2260  !$acc loop collapse(3) independent
2261  do j = je+1, ja
2262  do i = 1, ia
2263  do k = ks, ke
2264  dens(k,i,j) = atmos_boundary_dens(k,i,j)
2265  rhot(k,i,j) = atmos_boundary_pott(k,i,j) * atmos_boundary_dens(k,i,j)
2266  !$acc loop seq
2267  do iq = 1, qa
2268  iqb = bnd_iq(iq)
2269  if ( iqb > 0 ) then
2270  qtrc(k,i,j,iq) = atmos_boundary_qtrc(k,i,j,iqb)
2271  else
2272  qtrc(k,i,j,iq) = qtrc(k,i,je,iq)
2273  end if
2274  end do
2275  end do
2276  end do
2277  end do
2278  !$acc end kernels
2279  !$acc kernels
2280  do j = je, ja-1
2281  do i = 1, ia
2282  do k = ks, ke
2283  momy(k,i,j) = atmos_boundary_vely(k,i,j) &
2284  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i,j+1) ) * 0.5_rp
2285  end do
2286  end do
2287  end do
2288  !$acc end kernels
2289  !$acc kernels
2290  do i = 1, ia
2291  do k = ks, ke
2292  momy(k,i,ja) = atmos_boundary_vely(k,i,ja) * atmos_boundary_dens(k,i,ja)
2293  end do
2294  end do
2295  !$acc end kernels
2296  !$acc kernels
2297  do j = je+1, ja
2298  do i = 1, ia-1
2299  do k = ks, ke
2300  momx(k,i,j) = atmos_boundary_velx(k,i,j) &
2301  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i+1,j) ) * 0.5_rp
2302  end do
2303  end do
2304  end do
2305  !$acc end kernels
2306  !$acc kernels
2307  do j = je+1, ja
2308  do k = ks, ke
2309  momx(k,ia,j) = atmos_boundary_velx(k,ia,j) &
2310  * atmos_boundary_dens(k,ia,j)
2311  end do
2312  end do
2313  !$acc end kernels
2314  if ( atmos_boundary_use_velz ) then
2315  !$acc kernels
2316  do j = je+1, ja
2317  do i = 1, ia
2318  do k = ks, ke-1
2319  momz(k,i,j) = atmos_boundary_velz(k,i,j) &
2320  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k+1,i,j) ) * 0.5_rp
2321  end do
2322  end do
2323  end do
2324  !$acc end kernels
2325  else
2326  !$acc kernels
2327  do j = je+1, ja
2328  do i = 1, ia
2329  do k = ks, ke-1
2330  momz(k,i,j) = momz(k,i,je)
2331  end do
2332  end do
2333  end do
2334  !$acc end kernels
2335  end if
2336  end if
2337 
2338  !$acc end data
2339 
2340  return

References atmos_boundary_dens, atmos_boundary_pott, atmos_boundary_qtrc, atmos_boundary_velx, atmos_boundary_vely, atmos_boundary_velz, bnd_iq, dens, scale_atmos_grid_cartesc_index::ia, scale_atmos_grid_cartesc_index::ie, scale_atmos_grid_cartesc_index::is, scale_atmos_grid_cartesc_index::ja, scale_atmos_grid_cartesc_index::je, scale_atmos_grid_cartesc_index::js, scale_atmos_grid_cartesc_index::ke, scale_atmos_grid_cartesc_index::ks, mod_atmos_vars::momx, mod_atmos_vars::momy, mod_atmos_vars::momz, scale_prc_cartesc::prc_has_e, scale_prc_cartesc::prc_has_n, scale_prc_cartesc::prc_has_s, scale_prc_cartesc::prc_has_w, scale_tracer::qa, qtrc, and mod_atmos_vars::rhot.

Referenced by atmos_boundary_driver_update().

Here is the caller graph for this function:

◆ history_bnd()

subroutine mod_atmos_bnd_driver::history_bnd ( real(rp), dimension(ka,ia,ja), intent(in)  ATMOS_BOUNDARY_DENS,
real(rp), dimension(ka,ia,ja), intent(in)  ATMOS_BOUNDARY_VELZ,
real(rp), dimension(ka,ia,ja), intent(in)  ATMOS_BOUNDARY_VELX,
real(rp), dimension(ka,ia,ja), intent(in)  ATMOS_BOUNDARY_VELY,
real(rp), dimension(ka,ia,ja), intent(in)  ATMOS_BOUNDARY_POTT,
real(rp), dimension(ka,ia,ja,bnd_qa), intent(in)  ATMOS_BOUNDARY_QTRC 
)

Definition at line 2350 of file mod_atmos_bnd_driver.F90.

2350  use scale_file_history, only: &
2351  file_history_in
2352  use mod_atmos_phy_mp_vars, only: &
2353  qs_mp
2354  implicit none
2355  real(RP), intent(in) :: ATMOS_BOUNDARY_DENS(KA,IA,JA)
2356  real(RP), intent(in) :: ATMOS_BOUNDARY_VELZ(KA,IA,JA)
2357  real(RP), intent(in) :: ATMOS_BOUNDARY_VELX(KA,IA,JA)
2358  real(RP), intent(in) :: ATMOS_BOUNDARY_VELY(KA,IA,JA)
2359  real(RP), intent(in) :: ATMOS_BOUNDARY_POTT(KA,IA,JA)
2360  real(RP), intent(in) :: ATMOS_BOUNDARY_QTRC(KA,IA,JA,BND_QA)
2361 
2362  integer :: iq, iqb
2363 
2364  call file_history_in( atmos_boundary_dens(:,:,:), 'DENS_BND', 'Boundary Density', 'kg/m3' )
2365  call file_history_in( atmos_boundary_velz(:,:,:), 'VELZ_BND', 'Boundary velocity z-direction', 'm/s', dim_type='ZHXY' )
2366  call file_history_in( atmos_boundary_velx(:,:,:), 'VELX_BND', 'Boundary velocity x-direction', 'm/s', dim_type='ZXHY' )
2367  call file_history_in( atmos_boundary_vely(:,:,:), 'VELY_BND', 'Boundary velocity y-direction', 'm/s', dim_type='ZXYH' )
2368  call file_history_in( atmos_boundary_pott(:,:,:), 'PT_BND', 'Boundary potential temperature', 'K' )
2369  do iq = 1, qa
2370  iqb = bnd_iq(iq)
2371  if ( iqb > 0 ) then
2372  call file_history_in( atmos_boundary_qtrc(:,:,:,iqb), trim(tracer_name(iq))//'_BND', &
2373  trim(tracer_name(iq))//' in boundary', 'kg/kg' )
2374  end if
2375  enddo
2376 
2377  return

References bnd_iq, scale_tracer::qa, mod_atmos_phy_mp_vars::qs_mp, and scale_tracer::tracer_name.

Referenced by atmos_boundary_driver_set(), and atmos_boundary_driver_update().

Here is the caller graph for this function:

◆ calc_mass()

subroutine mod_atmos_bnd_driver::calc_mass

Definition at line 2381 of file mod_atmos_bnd_driver.F90.

2381  use scale_prc_cartesc, only: &
2382  prc_has_w, &
2383  prc_has_e, &
2384  prc_has_s, &
2385  prc_has_n
2386  use scale_statistics, only: &
2387  statistics_total
2388  use scale_atmos_grid_cartesc_real, only: &
2389  vol => atmos_grid_cartesc_real_vol, &
2390  totvol => atmos_grid_cartesc_real_totvol, &
2391  areazxv_y => atmos_grid_cartesc_real_areazxv_y, &
2392  totareazuy_x => atmos_grid_cartesc_real_totareazuy_x, &
2393  totareazxv_y => atmos_grid_cartesc_real_totareazxv_y
2394  use scale_atmos_refstate, only: &
2395  dens_ref => atmos_refstate_dens
2396  use mod_atmos_vars, only: &
2397  dens
2398  implicit none
2399 
2400  real(DP) :: masstot, masstot_current
2401  real(DP) :: massflx
2402  real(DP) :: offset_band, offset_bias
2403  real(DP) :: ref_tot
2404  real(DP) :: flx_w, flx_e, flx_s, flx_n
2405  real(DP) :: ref_w, ref_e, ref_s, ref_n
2406 
2407  real(RP), target :: work_x(KA,JA), work_y(KA,IA)
2408  real(RP), pointer :: ptr(:,:)
2409 
2410  integer :: k, i, j
2411 
2412  !$acc data create(work_x, work_y)
2413 
2414  ! total mass
2415  call statistics_total( ka, ks, ke, ia, is, ie, ja, js, je, &
2416  dens_ref(:,:,:), & ! (in)
2417  "DENS_bnd", & ! (in)
2418  vol(:,:,:), totvol, & ! (in)
2419  log_suppress = .true., global = .true., & ! (in)
2420  sum = masstot ) ! (out)
2421 
2422 !!$ call STATISTICS_total( KA, KS, KE, IA, IS, IE, JA, JS, JE, &
2423 !!$ DENS(:,:,:), "DENS_bnd_update", & ! (in)
2424 !!$ VOL(:,:,:), TOTVOL, & ! (in)
2425 !!$ log_suppress = .true., global = .true., & ! (in)
2426 !!$ sum = masstot_current ) ! (out)
2427 
2428 
2429  ! West
2430  if ( .NOT. prc_has_w ) then
2431  !$omp parallel do
2432  !$acc kernels
2433  do j = js, je
2434  do k = ks, ke
2435  work_x(k,j) = velx_ref(k,is-1,j) &
2436  * ( dens_ref(k,is-1,j) + dens_ref(k,is,j) ) * 0.5_rp
2437  end do
2438  end do
2439  !$acc end kernels
2440  ptr => work_x
2441  else
2442  ptr => zero_x
2443  end if
2444  call statistics_total( ka, ks, ke, ja, js, je, &
2445  ptr(:,:), "MFLUX_bnd_w", & ! (in)
2446  areazuy_w(:,:), totareazuy_x(is-1), & ! (in)
2447  log_suppress = .true., global = .true., & ! (in)
2448  sum = flx_w ) ! (out)
2449  if ( .NOT. prc_has_w ) then
2450  !$omp parallel do
2451  !$acc kernels
2452  do j = js, je
2453  do k = ks, ke
2454  work_x(k,j) = dens_ref(k,is,j)
2455  end do
2456  end do
2457  !$acc end kernels
2458  end if
2459  call statistics_total( ka, ks, ke, ja, js, je, &
2460  ptr(:,:), "DENS_ref_w", & ! (in)
2461  areazuy_w(:,:), totareazuy_x(is-1), & ! (in)
2462  log_suppress = .true., global = .true., & ! (in)
2463  sum = ref_w ) ! (out)
2464 
2465  ! East
2466  if ( .NOT. prc_has_e ) then
2467  !$omp parallel do
2468  !$acc kernels
2469  do j = js, je
2470  do k = ks, ke
2471  work_x(k,j) = velx_ref(k,ie,j) &
2472  * ( dens_ref(k,ie,j) + dens_ref(k,ie+1,j) ) * 0.5_rp
2473  end do
2474  end do
2475  !$acc end kernels
2476  ptr => work_x
2477  else
2478  ptr => zero_x
2479  end if
2480  call statistics_total( ka, ks, ke, ja, js, je, &
2481  ptr(:,:), "MFLUX_bnd_e", & ! (in)
2482  areazuy_e(:,:), totareazuy_x(ie), & ! (in)
2483  log_suppress = .true., global = .true., & ! (in)
2484  sum = flx_e ) ! (out)
2485  if ( .NOT. prc_has_e ) then
2486  !$omp parallel do
2487  !$acc kernels
2488  do j = js, je
2489  do k = ks, ke
2490  work_x(k,j) = dens_ref(k,ie,j)
2491  end do
2492  end do
2493  !$acc end kernels
2494  end if
2495  call statistics_total( ka, ks, ke, ja, js, je, &
2496  ptr(:,:), "DENS_ref_e", & ! (in)
2497  areazuy_e(:,:), totareazuy_x(ie), & ! (in)
2498  log_suppress = .true., global = .true., & ! (in)
2499  sum = ref_e ) ! (out)
2500 
2501  ! South
2502  if ( .NOT. prc_has_s ) then
2503  !$omp parallel do
2504  !$acc kernels
2505  do i = is, ie
2506  do k = ks, ke
2507  work_y(k,i) = vely_ref(k,i,js-1) &
2508  * ( dens_ref(k,i,js-1) + dens_ref(k,i,js) ) * 0.5_rp
2509  end do
2510  end do
2511  !$acc end kernels
2512  ptr => work_y
2513  else
2514  ptr => zero_y
2515  end if
2516  call statistics_total( ka, ks, ke, ia, is, ie, &
2517  ptr(:,:), "MFLUX_bnd_s", & ! (in)
2518  areazxv_y(:,:,js-1), totareazxv_y(js-1), & ! (in)
2519  log_suppress = .true., global = .true., & ! (in)
2520  sum = flx_s ) ! (out)
2521  if ( .NOT. prc_has_s ) then
2522  !$omp parallel do
2523  !$acc kernels
2524  do i = is, ie
2525  do k = ks, ke
2526  work_y(k,i) = dens_ref(k,i,js)
2527  end do
2528  end do
2529  !$acc end kernels
2530  end if
2531  call statistics_total( ka, ks, ke, ia, is, ie, &
2532  ptr(:,:), "DENS_ref_s", & ! (in)
2533  areazxv_y(:,:,js-1), totareazxv_y(js-1), & ! (in)
2534  log_suppress = .true., global = .true., & ! (in)
2535  sum = ref_s ) ! (out)
2536 
2537  ! North
2538  if ( .NOT. prc_has_n ) then
2539  !$omp parallel do
2540  !$acc kernels
2541  do i = is, ie
2542  do k = ks, ke
2543  work_y(k,i) = vely_ref(k,i,je) &
2544  * ( dens_ref(k,i,je) + dens_ref(k,i,je+1) ) * 0.5_rp
2545  end do
2546  end do
2547  !$acc end kernels
2548  ptr => work_y
2549  else
2550  ptr => zero_y
2551  end if
2552  call statistics_total( ka, ks, ke, ia, is, ie, &
2553  ptr(:,:), "MFLX_bnd_n", & ! (in)
2554  areazxv_y(:,:,je), totareazxv_y(je), & ! (in)
2555  log_suppress = .true., global = .true., & ! (in)
2556  sum = flx_n ) ! (out)
2557  if ( .NOT. prc_has_n ) then
2558  !$omp parallel do
2559  !$acc kernels
2560  do i = is, ie
2561  do k = ks, ke
2562  work_y(k,i) = dens_ref(k,i,je)
2563  end do
2564  end do
2565  !$acc end kernels
2566  end if
2567  call statistics_total( ka, ks, ke, ia, is, ie, &
2568  ptr(:,:), "DENS_ref_n", & ! (in)
2569  areazxv_y(:,:,je), totareazxv_y(je), & ! (in)
2570  log_suppress = .true., global = .true., & ! (in)
2571  sum = ref_n ) ! (out)
2572 
2573  massflx = flx_w - flx_e + flx_s - flx_n
2574 
2575  offset_band = ( masstot - masstot_now ) / update_dt &
2576  - ( massflx + massflx_now ) * 0.5_dp
2577 ! offset_bias = ( MASSTOT_now - masstot_current ) / UPDATE_DT
2578 
2579  log_info("ATMOS_BOUNDARY_calc_mass",*) "Offset_band is: ", offset_band, "(", masstot, masstot_now, massflx, massflx_now, ")"
2580 
2581  ref_tot = ref_w + ref_e + ref_s + ref_n
2582  offset_band = offset_band / ref_tot
2583 ! offset_bias = offset_bias / ref_tot
2584 
2585  log_info_cont(*) " per dens ", offset_band
2586 
2587  ! density of the reference state is used as weight
2588  if ( .not. prc_has_w ) then
2589  !$omp parallel do
2590  !$acc kernels
2591  do j = js, je
2592  do k = ks, ke
2593  mflux_offset_x(k,j,1,1) = offset_band * dens_ref(k,is,j)
2594 ! MFLUX_OFFSET_X(k,j,1,2) = offset_bias * DENS_ref(k,IS,j)
2595  end do
2596  end do
2597  !$acc end kernels
2598  end if
2599  if ( .not. prc_has_e ) then
2600  !$omp parallel do
2601  !$acc kernels
2602  do j = js, je
2603  do k = ks, ke
2604  mflux_offset_x(k,j,2,1) = - offset_band * dens_ref(k,ie,j)
2605 ! MFLUX_OFFSET_X(k,j,2,2) = - offset_bias * DENS_ref(k,IE,j)
2606  end do
2607  end do
2608  !$acc end kernels
2609  end if
2610  if ( .not. prc_has_s ) then
2611  !$omp parallel do
2612  !$acc kernels
2613  do i = is, ie
2614  do k = ks, ke
2615  mflux_offset_y(k,i,1,1) = offset_band * dens_ref(k,i,js)
2616 ! MFLUX_OFFSET_Y(k,i,1,2) = offset_bias * DENS_ref(k,i,JS)
2617  end do
2618  end do
2619  !$acc end kernels
2620  end if
2621  if ( .not. prc_has_n ) then
2622  !$omp parallel do
2623  !$acc kernels
2624  do i = is, ie
2625  do k = ks, ke
2626  mflux_offset_y(k,i,2,1) = - offset_band * dens_ref(k,i,je)
2627 ! MFLUX_OFFSET_Y(k,i,2,2) = - offset_bias * DENS_ref(k,i,JE)
2628  end do
2629  end do
2630  !$acc end kernels
2631  end if
2632 
2633  masstot_now = masstot
2634  massflx_now = massflx
2635 
2636  !$acc end data
2637 
2638  return

References scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazxv_y, scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totareazuy_x, scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totareazxv_y, scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totvol, scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_vol, scale_atmos_refstate::atmos_refstate_dens, dens, scale_atmos_grid_cartesc_index::ie, scale_atmos_grid_cartesc_index::is, scale_atmos_grid_cartesc_index::je, scale_atmos_grid_cartesc_index::js, scale_atmos_grid_cartesc_index::ke, scale_atmos_grid_cartesc_index::ks, scale_prc_cartesc::prc_has_e, scale_prc_cartesc::prc_has_n, scale_prc_cartesc::prc_has_s, and scale_prc_cartesc::prc_has_w.

Referenced by atmos_boundary_driver_send(), and atmos_boundary_set_file().

Here is the caller graph for this function:

◆ set_offset()

subroutine mod_atmos_bnd_driver::set_offset

Definition at line 2643 of file mod_atmos_bnd_driver.F90.

2643  integer :: k, i, j, n
2644 
2645  !$omp parallel do
2646  !$acc kernels
2647  do j = js, je
2648  do k = ks, ke
2649  do n = 1, 2
2650  atmos_boundary_mflux_offset_x(k,j,n) = mflux_offset_x(k,j,n,1) * offset_time_fact(now_step) !&
2651 ! + MFLUX_OFFSET_X(k,j,n,2)
2652  end do
2653  end do
2654  end do
2655  !$acc end kernels
2656 
2657  !$omp parallel do
2658  !$acc kernels
2659  do i = is, ie
2660  do k = ks, ke
2661  do n = 1, 2
2662  atmos_boundary_mflux_offset_y(k,i,n) = mflux_offset_y(k,i,n,1) * offset_time_fact(now_step) !&
2663 ! + MFLUX_OFFSET_Y(k,i,n,2)
2664  end do
2665  end do
2666  end do
2667  !$acc end kernels
2668 
2669  return

References atmos_boundary_mflux_offset_x, atmos_boundary_mflux_offset_y, scale_atmos_grid_cartesc_index::ie, scale_atmos_grid_cartesc_index::is, scale_atmos_grid_cartesc_index::je, scale_atmos_grid_cartesc_index::js, scale_atmos_grid_cartesc_index::ke, and scale_atmos_grid_cartesc_index::ks.

Referenced by atmos_boundary_driver_send().

Here is the caller graph for this function:

Variable Documentation

◆ bnd_qa

integer, public mod_atmos_bnd_driver::bnd_qa

◆ of

integer allocatable public mod_atmos_bnd_driver::of

Definition at line 42 of file mod_atmos_bnd_driver.F90.

◆ tracer

integer allocatable public mod_atmos_bnd_driver::tracer

Definition at line 42 of file mod_atmos_bnd_driver.F90.

◆ at

integer, public mod_atmos_bnd_driver::at

Definition at line 42 of file mod_atmos_bnd_driver.F90.

◆ boundary

integer, public mod_atmos_bnd_driver::boundary

Definition at line 42 of file mod_atmos_bnd_driver.F90.

◆ bnd_iq

integer, dimension(:), allocatable, public mod_atmos_bnd_driver::bnd_iq

◆ index

integer, allocatable, public mod_atmos_bnd_driver::index

Definition at line 43 of file mod_atmos_bnd_driver.F90.

◆ atmos_boundary_dens

real(rp), dimension(:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_dens

◆ reference

real(rp), allocatable, public mod_atmos_bnd_driver::reference

Definition at line 45 of file mod_atmos_bnd_driver.F90.

◆ dens

real(rp), dimension (0-1), allocatable, public mod_atmos_bnd_driver::dens

◆ atmos_boundary_velz

real(rp), dimension(:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_velz

◆ velz

real(rp), dimension (0-1), allocatable, public mod_atmos_bnd_driver::velz

Definition at line 46 of file mod_atmos_bnd_driver.F90.

◆ atmos_boundary_velx

real(rp), dimension(:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_velx

◆ velx

real(rp), dimension (0-1), allocatable, public mod_atmos_bnd_driver::velx

Definition at line 47 of file mod_atmos_bnd_driver.F90.

◆ atmos_boundary_vely

real(rp), dimension(:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_vely

◆ vely

real(rp), dimension (0-1), allocatable, public mod_atmos_bnd_driver::vely

Definition at line 48 of file mod_atmos_bnd_driver.F90.

◆ atmos_boundary_pott

real(rp), dimension(:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_pott

◆ pott

real(rp), dimension (0-1), allocatable, public mod_atmos_bnd_driver::pott

Definition at line 49 of file mod_atmos_bnd_driver.F90.

◆ atmos_boundary_qtrc

real(rp), dimension(:,:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_qtrc

◆ qtrc

real(rp), dimension (0-1), allocatable, public mod_atmos_bnd_driver::qtrc

◆ atmos_boundary_alpha_dens

real(rp), dimension(:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_alpha_dens

Definition at line 52 of file mod_atmos_bnd_driver.F90.

52  real(RP), public, allocatable :: ATMOS_BOUNDARY_alpha_DENS(:,:,:)

Referenced by atmos_boundary_driver_finalize(), atmos_boundary_driver_set(), atmos_boundary_driver_setup(), and mod_atmos_dyn_driver::atmos_dyn_driver().

◆ damping

real(rp), allocatable, public mod_atmos_bnd_driver::damping

Definition at line 52 of file mod_atmos_bnd_driver.F90.

◆ coefficient

real(rp), allocatable, public mod_atmos_bnd_driver::coefficient

Definition at line 52 of file mod_atmos_bnd_driver.F90.

◆ for

logical allocatable public mod_atmos_bnd_driver::for

Definition at line 52 of file mod_atmos_bnd_driver.F90.

◆ atmos_boundary_alpha_velz

real(rp), dimension(:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_alpha_velz

Definition at line 53 of file mod_atmos_bnd_driver.F90.

53  real(RP), public, allocatable :: ATMOS_BOUNDARY_alpha_VELZ(:,:,:)

Referenced by atmos_boundary_driver_finalize(), atmos_boundary_driver_set(), atmos_boundary_driver_setup(), and mod_atmos_dyn_driver::atmos_dyn_driver().

◆ atmos_boundary_alpha_velx

real(rp), dimension(:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_alpha_velx

Definition at line 54 of file mod_atmos_bnd_driver.F90.

54  real(RP), public, allocatable :: ATMOS_BOUNDARY_alpha_VELX(:,:,:)

Referenced by atmos_boundary_driver_finalize(), atmos_boundary_driver_set(), atmos_boundary_driver_setup(), and mod_atmos_dyn_driver::atmos_dyn_driver().

◆ atmos_boundary_alpha_vely

real(rp), dimension(:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_alpha_vely

Definition at line 55 of file mod_atmos_bnd_driver.F90.

55  real(RP), public, allocatable :: ATMOS_BOUNDARY_alpha_VELY(:,:,:)

Referenced by atmos_boundary_driver_finalize(), atmos_boundary_driver_set(), atmos_boundary_driver_setup(), and mod_atmos_dyn_driver::atmos_dyn_driver().

◆ atmos_boundary_alpha_pott

real(rp), dimension(:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_alpha_pott

Definition at line 56 of file mod_atmos_bnd_driver.F90.

56  real(RP), public, allocatable :: ATMOS_BOUNDARY_alpha_POTT(:,:,:)

Referenced by atmos_boundary_driver_finalize(), atmos_boundary_driver_set(), atmos_boundary_driver_setup(), and mod_atmos_dyn_driver::atmos_dyn_driver().

◆ atmos_boundary_alpha_qtrc

real(rp), dimension(:,:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_alpha_qtrc

Definition at line 57 of file mod_atmos_bnd_driver.F90.

57  real(RP), public, allocatable :: ATMOS_BOUNDARY_alpha_QTRC(:,:,:,:)

Referenced by atmos_boundary_driver_finalize(), atmos_boundary_driver_set(), atmos_boundary_driver_setup(), and mod_atmos_dyn_driver::atmos_dyn_driver().

◆ atmos_boundary_mflux_offset_x

real(rp), dimension(:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_mflux_offset_x

Definition at line 59 of file mod_atmos_bnd_driver.F90.

59  real(RP), public, allocatable :: ATMOS_BOUNDARY_MFLUX_OFFSET_X(:,:,:)

Referenced by atmos_boundary_driver_finalize(), atmos_boundary_driver_setup(), mod_atmos_dyn_driver::atmos_dyn_driver(), and set_offset().

◆ mass

real(rp), allocatable, public mod_atmos_bnd_driver::mass

Definition at line 59 of file mod_atmos_bnd_driver.F90.

◆ flux

real(rp), allocatable, public mod_atmos_bnd_driver::flux

Definition at line 59 of file mod_atmos_bnd_driver.F90.

◆ offset

real(rp), dimension (south, north), allocatable, public mod_atmos_bnd_driver::offset

Definition at line 59 of file mod_atmos_bnd_driver.F90.

◆ atmos_boundary_mflux_offset_y

real(rp), dimension(:,:,:), allocatable, public mod_atmos_bnd_driver::atmos_boundary_mflux_offset_y

Definition at line 60 of file mod_atmos_bnd_driver.F90.

60  real(RP), public, allocatable :: ATMOS_BOUNDARY_MFLUX_OFFSET_Y(:,:,:)

Referenced by atmos_boundary_driver_finalize(), atmos_boundary_driver_setup(), mod_atmos_dyn_driver::atmos_dyn_driver(), and set_offset().

◆ atmos_boundary_smoother_fact

real(rp), public mod_atmos_bnd_driver::atmos_boundary_smoother_fact = 0.2_RP

Definition at line 62 of file mod_atmos_bnd_driver.F90.

62  real(RP), public :: ATMOS_BOUNDARY_SMOOTHER_FACT = 0.2_rp

Referenced by atmos_boundary_driver_setup(), and mod_atmos_dyn_driver::atmos_dyn_driver().

◆ fact

real(rp), public mod_atmos_bnd_driver::fact

Definition at line 62 of file mod_atmos_bnd_driver.F90.

◆ smoother

real(rp), public mod_atmos_bnd_driver::smoother

Definition at line 62 of file mod_atmos_bnd_driver.F90.

◆ to

real(rp), public mod_atmos_bnd_driver::to

Definition at line 62 of file mod_atmos_bnd_driver.F90.

◆ atmos_boundary_update_flag

logical, public mod_atmos_bnd_driver::atmos_boundary_update_flag = .false.

Definition at line 64 of file mod_atmos_bnd_driver.F90.

64  logical, public :: ATMOS_BOUNDARY_UPDATE_FLAG = .false.

Referenced by atmos_boundary_driver_set(), atmos_boundary_driver_setup(), and mod_atmos_driver::atmos_driver_update().

◆ switch

logical, public mod_atmos_bnd_driver::switch

Definition at line 64 of file mod_atmos_bnd_driver.F90.

◆ real

mod_atmos_bnd_driver::real

Definition at line 64 of file mod_atmos_bnd_driver.F90.

Referenced by atmos_boundary_driver_setup().

◆ case

logical, public mod_atmos_bnd_driver::case

Definition at line 64 of file mod_atmos_bnd_driver.F90.

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
mod_atmos_vars::qe
real(rp), dimension(:,:,:,:), allocatable, target, public qe
Definition: mod_atmos_vars.F90:105
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
scale_prc_cartesc::prc_has_s
logical, public prc_has_s
Definition: scale_prc_cartesC.F90:51
scale_atmos_refstate::atmos_refstate_dens
real(rp), dimension(:,:,:), allocatable, public atmos_refstate_dens
refernce density [kg/m3]
Definition: scale_atmos_refstate.F90:39
scale_comm_cartesc_nest::comm_cartesc_nest_test_recv
subroutine, public comm_cartesc_nest_test_recv
[check communication status] Inter-communication (daughter side)
Definition: scale_comm_cartesC_nest.F90:3107
mod_atmos_phy_mp_vars::qs_mp
integer, public qs_mp
Definition: mod_atmos_phy_mp_vars.F90:79
scale_comm_cartesc_nest
module Communication CartesianC nesting
Definition: scale_comm_cartesC_nest.F90:12
scale_comm_cartesc_nest::online_recv_diagqhyd
logical, public online_recv_diagqhyd
Definition: scale_comm_cartesC_nest.F90:87
scale_atmos_hydrometeor
module atmosphere / hydrometeor
Definition: scale_atmos_hydrometeor.F90:12
scale_atmos_refstate
module atmosphere / reference state
Definition: scale_atmos_refstate.F90:12
scale_comm_cartesc_nest::online_send_qa
integer, public online_send_qa
number of tracer sent to the daughter domain
Definition: scale_comm_cartesC_nest.F90:90
scale_comm_cartesc_nest::online_parent_nstep
integer, public online_parent_nstep
parent nsteps
Definition: scale_comm_cartesC_nest.F90:93
scale_atmos_hydrometeor::atmos_hydrometeor_dry
logical, public atmos_hydrometeor_dry
Definition: scale_atmos_hydrometeor.F90:114
mod_atmos_vars::rhot
real(rp), dimension(:,:,:), allocatable, target, public rhot
Definition: mod_atmos_vars.F90:80
mod_atmos_phy_ch_vars::qs_ch
integer, public qs_ch
Definition: mod_atmos_phy_ch_vars.F90:62
scale_atmos_grid_cartesc_real
module Atmosphere GRID CartesC Real(real space)
Definition: scale_atmos_grid_cartesC_real.F90:11
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_file
module file
Definition: scale_file.F90:15
scale_prc_cartesc::prc_has_n
logical, public prc_has_n
Definition: scale_prc_cartesC.F90:49
scale_prc_cartesc::prc_has_e
logical, public prc_has_e
Definition: scale_prc_cartesC.F90:50
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_comm_cartesc_nest::online_iam_parent
logical, public online_iam_parent
a flag to say "I am a parent"
Definition: scale_comm_cartesC_nest.F90:80
scale_comm_cartesc_nest::online_send_diagqhyd
logical, public online_send_diagqhyd
Definition: scale_comm_cartesC_nest.F90:88
mod_atmos_vars::dens
real(rp), dimension(:,:,:), allocatable, target, public dens
Definition: mod_atmos_vars.F90:76
scale_comm_cartesc_nest::online_boundary_use_qhyd
logical, public online_boundary_use_qhyd
Definition: scale_comm_cartesC_nest.F90:85
scale_const
module CONSTANT
Definition: scale_const.F90:11
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_vars::momz
real(rp), dimension(:,:,:), allocatable, target, public momz
Definition: mod_atmos_vars.F90:77
scale_file_external_input::i_prev
integer, parameter, public i_prev
[index] previous
Definition: scale_file_external_input.F90:174
scale_comm_cartesc_nest::comm_cartesc_nest_recvwait_issue_send
subroutine, public comm_cartesc_nest_recvwait_issue_send
Sub-command for data transfer from parent to daughter: nestdown (parent side)
Definition: scale_comm_cartesC_nest.F90:2513
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazuy_x
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazuy_x
virtical area (zuy, normal x) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:67
scale_file_cartesc::file_cartesc_close
subroutine, public file_cartesc_close(fid)
Close a netCDF file.
Definition: scale_file_cartesC.F90:1044
scale_prc_cartesc
module process / cartesC
Definition: scale_prc_cartesC.F90:11
mod_atmos_phy_ch_vars
module Atmosphere / Physics Chemistry
Definition: mod_atmos_phy_ch_vars.F90:12
mod_atmos_vars::momx
real(rp), dimension(:,:,:), allocatable, target, public momx
Definition: mod_atmos_vars.F90:78
scale_comm_cartesc_nest::online_iam_daughter
logical, public online_iam_daughter
a flag to say "I am a daughter"
Definition: scale_comm_cartesC_nest.F90:81
scale_comm_cartesc_nest::online_recv_qa
integer, public online_recv_qa
number of tracer received from the parent domain
Definition: scale_comm_cartesC_nest.F90:89
mod_atmos_vars::momy
real(rp), dimension(:,:,:), allocatable, target, public momy
Definition: mod_atmos_vars.F90:79
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_const::const_pi
real(rp), parameter, public const_pi
pi
Definition: scale_const.F90:32
scale_atmos_hydrometeor::i_qv
integer, public i_qv
Definition: scale_atmos_hydrometeor.F90:93
scale_comm_cartesc_nest::comm_cartesc_nest_test_send
subroutine, public comm_cartesc_nest_test_send
[check communication status] Inter-communication (parent side)
Definition: scale_comm_cartesC_nest.F90:3075
scale_file::file_aggregate
logical, public file_aggregate
Definition: scale_file.F90:196
scale_comm_cartesc_nest::online_use_velz
logical, public online_use_velz
Definition: scale_comm_cartesC_nest.F90:83
scale_time::time_dtsec
real(dp), public time_dtsec
time interval of model [sec]
Definition: scale_time.F90:33
scale_comm_cartesc_nest::use_nesting
logical, public use_nesting
Definition: scale_comm_cartesC_nest.F90:79
mod_atmos_vars
module ATMOSPHERIC Variables
Definition: mod_atmos_vars.F90:12
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totareazuy_x
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_real_totareazuy_x
total area (zuy, normal x) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:81
mod_atmos_phy_mp_vars::qe_mp
integer, public qe_mp
Definition: mod_atmos_phy_mp_vars.F90:80
mod_atmos_phy_ch_vars::qe_ch
integer, public qe_ch
Definition: mod_atmos_phy_ch_vars.F90:63
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
scale_comm_cartesc_nest::online_parent_dtsec
real(dp), public online_parent_dtsec
parent DT [sec]
Definition: scale_comm_cartesC_nest.F90:92
scale_file_external_input
module file / external_input
Definition: scale_file_external_input.F90:12
scale_const::const_undef
real(rp), public const_undef
Definition: scale_const.F90:43
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazxv_y
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazxv_y
virtical area (zxv, normal y) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:68
scale_prc_cartesc::prc_has_w
logical, public prc_has_w
Definition: scale_prc_cartesC.F90:48
scale_file_cartesc
module file / cartesianC
Definition: scale_file_cartesC.F90:11
scale_comm_cartesc_nest::comm_cartesc_nest_recv_cancel_recv
subroutine, public comm_cartesc_nest_recv_cancel_recv
Sub-command for data transfer from parent to daughter: nestdown (daughter side)
Definition: scale_comm_cartesC_nest.F90:2670
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totareazxv_y
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_real_totareazxv_y
total area (zxv, normal y) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:82