SCALE-RM
Data Types | 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
 set More...
 
subroutine atmos_boundary_set_file
 Set boundary value for real case experiment. More...
 
subroutine atmos_boundary_set_online
 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
 Update boundary value with a constant time boundary. More...
 
subroutine update_ref_index
 Update indices of array of boundary references. More...
 

Variables

integer, public bnd_qa
 
integer, public of
 
integer, public tracer
 
integer, public at
 
integer, public boundary
 
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), public atmos_boundary_smoother_fact = 0.2_RP
 
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_CHECK_COORDINATES logical .true.
    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_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_POTT 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_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_POTT 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_POTT 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_UPDATE_DT real(DP) 0.0_DP inteval time of boudary data update [s]
    ATMOS_BOUNDARY_START_DATE integer, dimension(6) (/ -9999, 0, 0, 0, 0, 0 /) boundary initial date
    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_BOUNDARY_INTERP_TYPE character(len=H_LONG) 'lerp_initpoint' type of boundary interporation

History Output
namedescriptionunitvariable
DENS_BND Boundary Density kg/m3 ATMOS_BOUNDARY_DENS
POTT_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 199 of file mod_atmos_bnd_driver.F90.

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_smoother_fact, atmos_boundary_update_flag, atmos_boundary_velx, atmos_boundary_vely, atmos_boundary_velz, bnd_qa, scale_comm_cartesc_nest::comm_cartesc_nest_bnd_qa, scale_const::const_undef, scale_atmos_grid_cartesc_index::ia, scale_io::io_fid_conf, scale_atmos_grid_cartesc_index::ja, scale_atmos_grid_cartesc_index::ka, scale_comm_cartesc_nest::offline, scale_comm_cartesc_nest::online_boundary_diagqhyd, scale_comm_cartesc_nest::online_boundary_use_qhyd, scale_comm_cartesc_nest::online_iam_daughter, scale_comm_cartesc_nest::online_iam_parent, scale_prc::prc_abort(), mod_atmos_phy_ch_vars::qa_ch, mod_atmos_phy_mp_vars::qa_mp, scale_time::time_dtsec, and scale_comm_cartesc_nest::use_nesting.

Referenced by mod_atmos_driver::atmos_driver_setup().

199  use scale_prc, only: &
200  prc_abort
201  use scale_const, only: &
203  use scale_time, only: &
204  dt => time_dtsec
205  use scale_comm_cartesc_nest, only: &
208  use_nesting, &
209  offline, &
212  nestqa => comm_cartesc_nest_bnd_qa
213  use mod_atmos_phy_mp_vars, only: &
214  qa_mp
215  use mod_atmos_phy_ch_vars, only: &
216  qa_ch
217  implicit none
218 
219  namelist / param_atmos_boundary / &
220  atmos_boundary_type, &
221  atmos_boundary_in_basename, &
222  atmos_boundary_in_check_coordinates, &
223  atmos_boundary_out_basename, &
224  atmos_boundary_out_title, &
225  atmos_boundary_out_dtype, &
226  atmos_boundary_use_velz, &
227  atmos_boundary_use_velx, &
228  atmos_boundary_use_vely, &
229  atmos_boundary_use_pott, &
230  atmos_boundary_use_dens, &
231  atmos_boundary_use_qv, &
232  atmos_boundary_use_qhyd, &
233  atmos_boundary_use_chem, &
234  atmos_boundary_value_velz, &
235  atmos_boundary_value_velx, &
236  atmos_boundary_value_vely, &
237  atmos_boundary_value_pott, &
238  atmos_boundary_value_qtrc, &
239  atmos_boundary_alphafact_dens, &
240  atmos_boundary_alphafact_velz, &
241  atmos_boundary_alphafact_velx, &
242  atmos_boundary_alphafact_vely, &
243  atmos_boundary_alphafact_pott, &
244  atmos_boundary_alphafact_qtrc, &
245  atmos_boundary_smoother_fact, &
246  atmos_boundary_fracz, &
247  atmos_boundary_fracx, &
248  atmos_boundary_fracy, &
249  atmos_boundary_tauz, &
250  atmos_boundary_taux, &
251  atmos_boundary_tauy, &
252  atmos_boundary_update_dt, &
253  atmos_boundary_start_date, &
254  atmos_boundary_linear_v, &
255  atmos_boundary_linear_h, &
256  atmos_boundary_exp_h, &
257  atmos_boundary_interp_type
258 
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  !--- read namelist
271  rewind(io_fid_conf)
272  read(io_fid_conf,nml=param_atmos_boundary,iostat=ierr)
273  if( ierr < 0 ) then !--- missing
274  log_info("ATMOS_BOUNDARY_setup",*) 'Not found namelist. Default used.'
275  elseif( ierr > 0 ) then !--- fatal error
276  log_error("ATMOS_BOUNDARY_setup",*) 'Not appropriate names in namelist PARAM_ATMOS_BOUNDARY. Check!'
277  call prc_abort
278  endif
279  log_nml(param_atmos_boundary)
280 
281  ! setting switches
282  if( .NOT. use_nesting ) then
283  atmos_boundary_online = .false.
284  else
285  if( offline ) then
286  atmos_boundary_online = .false.
287  else
288  atmos_boundary_online = .true.
289  endif
290  endif
291  do_parent_process = .false.
292  do_daughter_process = .false.
293  atmos_boundary_online_master = .false.
294  if ( atmos_boundary_online ) then
295  if ( online_iam_parent ) then
296  do_parent_process = .true.
297  if ( .NOT. online_iam_daughter ) then
298  atmos_boundary_online_master = .true.
299  endif
300  endif
301  if ( online_iam_daughter ) then
302  do_daughter_process = .true.
303  atmos_boundary_use_qhyd = online_boundary_use_qhyd
304  endif
305  endif
306 
307  if( atmos_boundary_use_qhyd ) then
308  bnd_qa = qa_mp
309  if( atmos_boundary_use_chem ) then
310  bnd_qa = bnd_qa + qa_ch
311  endif
312  else if ( qa_mp > 0 ) then
313  bnd_qa = 1
314  else
315  bnd_qa = 0
316  end if
317 
318  allocate( atmos_boundary_dens(ka,ia,ja) )
319  allocate( atmos_boundary_velz(ka,ia,ja) )
320  allocate( atmos_boundary_velx(ka,ia,ja) )
321  allocate( atmos_boundary_vely(ka,ia,ja) )
322  allocate( atmos_boundary_pott(ka,ia,ja) )
323  allocate( atmos_boundary_qtrc(ka,ia,ja,bnd_qa) )
324  atmos_boundary_dens(:,:,:) = const_undef
325  atmos_boundary_velz(:,:,:) = const_undef
326  atmos_boundary_velx(:,:,:) = const_undef
327  atmos_boundary_vely(:,:,:) = const_undef
328  atmos_boundary_pott(:,:,:) = const_undef
329  atmos_boundary_qtrc(:,:,:,:) = const_undef
330 
331  allocate( atmos_boundary_alpha_dens(ka,ia,ja) )
332  allocate( atmos_boundary_alpha_velz(ka,ia,ja) )
333  allocate( atmos_boundary_alpha_velx(ka,ia,ja) )
334  allocate( atmos_boundary_alpha_vely(ka,ia,ja) )
335  allocate( atmos_boundary_alpha_pott(ka,ia,ja) )
336  allocate( atmos_boundary_alpha_qtrc(ka,ia,ja,bnd_qa) )
337  atmos_boundary_alpha_dens(:,:,:) = 0.0_rp
338  atmos_boundary_alpha_velz(:,:,:) = 0.0_rp
339  atmos_boundary_alpha_velx(:,:,:) = 0.0_rp
340  atmos_boundary_alpha_vely(:,:,:) = 0.0_rp
341  atmos_boundary_alpha_pott(:,:,:) = 0.0_rp
342  atmos_boundary_alpha_qtrc(:,:,:,:) = 0.0_rp
343 
344  if ( atmos_boundary_type == 'REAL' .OR. do_daughter_process ) then
345  l_bnd = .true.
346  else
347  l_bnd = .false.
348  end if
349 
350  if ( l_bnd ) then
351 
352  select case(atmos_boundary_interp_type)
353  case('same_parent')
354  get_boundary => get_boundary_same_parent
355  case('nearest_neighbor')
356  get_boundary => get_boundary_nearest_neighbor
357  case('lerp_initpoint')
358  get_boundary => get_boundary_lerp_initpoint
359  case('lerp_midpoint')
360  get_boundary => get_boundary_lerp_midpoint
361  case default
362  log_error("ATMOS_BOUNDARY_setup",*) 'Wrong parameter in ATMOS_BOUNDARY_interp_TYPE. Check!'
363  call prc_abort
364  end select
365 
366  allocate( atmos_boundary_ref_dens(ka,ia,ja,ref_size) )
367  allocate( atmos_boundary_ref_velz(ka,ia,ja,ref_size) )
368  allocate( atmos_boundary_ref_velx(ka,ia,ja,ref_size) )
369  allocate( atmos_boundary_ref_vely(ka,ia,ja,ref_size) )
370  allocate( atmos_boundary_ref_pott(ka,ia,ja,ref_size) )
371  allocate( atmos_boundary_ref_qtrc(ka,ia,ja,bnd_qa,ref_size) )
372  atmos_boundary_ref_dens(:,:,:,:) = const_undef
373  atmos_boundary_ref_velz(:,:,:,:) = const_undef
374  atmos_boundary_ref_velx(:,:,:,:) = const_undef
375  atmos_boundary_ref_vely(:,:,:,:) = const_undef
376  atmos_boundary_ref_pott(:,:,:,:) = const_undef
377  atmos_boundary_ref_qtrc(:,:,:,:,:) = const_undef
378 
379  ! initialize boundary value (reading file or waiting parent domain)
380  if ( do_daughter_process ) then
381  call atmos_boundary_initialize_online
382  else
383  if ( atmos_boundary_in_basename /= '' ) then
384  call atmos_boundary_initialize_file
385  else
386  log_error("ATMOS_BOUNDARY_setup",*) 'You need specify ATMOS_BOUNDARY_IN_BASENAME'
387  call prc_abort
388  endif
389  endif
390 
391  call atmos_boundary_setalpha
392 
393  atmos_boundary_update_flag = .true.
394 
395  elseif ( atmos_boundary_type == 'NONE' ) then
396 
397  atmos_boundary_update_flag = .false.
398 
399  elseif ( atmos_boundary_type == 'CONST' ) then
400 
401  call atmos_boundary_setalpha
402 
403  atmos_boundary_update_flag = .false.
404 
405  elseif ( atmos_boundary_type == 'INIT' ) then
406 
407  call atmos_boundary_setalpha
408 
409  atmos_boundary_update_flag = .false.
410 
411  elseif ( atmos_boundary_type == 'OFFLINE' ) then
412 
413  if ( atmos_boundary_in_basename /= '' ) then
414  call atmos_boundary_read
415  else
416  log_error("ATMOS_BOUNDARY_setup",*) 'You need specify ATMOS_BOUNDARY_IN_BASENAME'
417  call prc_abort
418  endif
419 
420  atmos_boundary_update_flag = .false.
421 
422  else
423  log_error("ATMOS_BOUNDARY_setup",*) 'unsupported ATMOS_BOUNDARY_TYPE. Check!', trim(atmos_boundary_type)
424  call prc_abort
425  endif
426 
427  if ( use_nesting ) atmos_boundary_update_flag = .true.
428 
429  !----- report data -----
430  log_newline
431  log_info("ATMOS_BOUNDARY_setup",*) 'Atmospheric boundary parameters '
432  log_info_cont(*) 'Atmospheric boundary type : ', atmos_boundary_type
433  log_newline
434  log_info_cont(*) 'Is VELZ used in atmospheric boundary? : ', atmos_boundary_use_velz
435  log_info_cont(*) 'Is VELX used in atmospheric boundary? : ', atmos_boundary_use_velx
436  log_info_cont(*) 'Is VELY used in atmospheric boundary? : ', atmos_boundary_use_vely
437  log_info_cont(*) 'Is POTT used in atmospheric boundary? : ', atmos_boundary_use_pott
438  log_info_cont(*) 'Is DENS used in atmospheric boundary? : ', atmos_boundary_use_dens
439  log_info_cont(*) 'Is QV used in atmospheric boundary? : ', atmos_boundary_use_qv
440  log_info_cont(*) 'Is QHYD used in atmospheric boundary? : ', atmos_boundary_use_qhyd
441  log_info_cont(*) 'Is CHEM used in atmospheric boundary? : ', atmos_boundary_use_chem
442  log_newline
443  log_info_cont(*) 'Atmospheric boundary VELZ values : ', atmos_boundary_value_velz
444  log_info_cont(*) 'Atmospheric boundary VELX values : ', atmos_boundary_value_velx
445  log_info_cont(*) 'Atmospheric boundary VELY values : ', atmos_boundary_value_vely
446  log_info_cont(*) 'Atmospheric boundary POTT values : ', atmos_boundary_value_pott
447  log_info_cont(*) 'Atmospheric boundary QTRC values : ', atmos_boundary_value_qtrc
448  log_newline
449  log_info_cont(*) 'Atmospheric boundary smoother factor : ', atmos_boundary_smoother_fact
450  log_info_cont(*) 'Atmospheric boundary z-fraction : ', atmos_boundary_fracz
451  log_info_cont(*) 'Atmospheric boundary x-fraction : ', atmos_boundary_fracx
452  log_info_cont(*) 'Atmospheric boundary y-fraction : ', atmos_boundary_fracy
453  log_info_cont(*) 'Atmospheric boundary z-relaxation time : ', atmos_boundary_tauz
454  log_info_cont(*) 'Atmospheric boundary x-relaxation time : ', atmos_boundary_taux
455  log_info_cont(*) 'Atmospheric boundary y-relaxation time : ', atmos_boundary_tauy
456  log_newline
457  log_info_cont(*) 'Atmospheric boundary update dt : ', atmos_boundary_update_dt
458  log_info_cont(*) 'Atmospheric boundary start date : ', atmos_boundary_start_date(:)
459  log_newline
460  log_info_cont(*) 'Linear profile in vertically relax region : ', atmos_boundary_linear_v
461  log_info_cont(*) 'Linear profile in horizontally relax region : ', atmos_boundary_linear_h
462  log_info_cont(*) 'Non-linear factor in horizontally relax region : ', atmos_boundary_exp_h
463  log_newline
464  log_info_cont(*) 'Online nesting for lateral boundary : ', atmos_boundary_online
465 
466  log_info_cont(*) 'Does lateral boundary exist in this domain? : ', l_bnd
467  if ( l_bnd ) then
468  log_info_cont(*) 'Lateral boundary interporation type : ', atmos_boundary_interp_type
469  endif
470 
471  if ( online_boundary_diagqhyd ) then
472  allocate( q_work(ka,ia,ja,nestqa) )
473  end if
474 
475  return
logical, public online_iam_parent
a flag to say "I am a parent"
module Atmosphere / Physics Cloud Microphysics
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:55
real(rp), public const_undef
Definition: scale_const.F90:41
integer, public comm_cartesc_nest_bnd_qa
number of tracer treated in nesting system
real(dp), public time_dtsec
time interval of model [sec]
Definition: scale_time.F90:38
logical, public online_iam_daughter
a flag to say "I am a daughter"
module PROCESS
Definition: scale_prc.F90:11
module TIME
Definition: scale_time.F90:16
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
module CONSTANT
Definition: scale_const.F90:11
module Communication CartesianC nesting
module Atmosphere / Physics Chemistry
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 ( )

set

Definition at line 481 of file mod_atmos_bnd_driver.F90.

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_qa, scale_calendar::calendar_combine_daysec(), scale_calendar::calendar_date2char(), scale_calendar::calendar_date2daysec(), scale_const::const_eps, scale_const::const_pi, dens, scale_file_cartesc::file_cartesc_close(), scale_file_cartesc::file_cartesc_open(), scale_atmos_grid_cartesc_index::ia, scale_atmos_grid_cartesc_index::ieb, scale_atmos_grid_cartesc_index::isb, scale_atmos_grid_cartesc_index::ja, scale_atmos_grid_cartesc_index::jeb, scale_atmos_grid_cartesc_index::jsb, 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_comm_cartesc_nest::online_use_velz, scale_prc::prc_abort(), 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_nowdate, scale_tracer::tracer_name, and scale_tracer::tracer_unit.

Referenced by mod_rm_driver::restart_read().

481  use mod_atmos_vars, only: &
482  dens, &
483  momz, &
484  momx, &
485  momy, &
486  rhot, &
487  qtrc, &
488  qv, &
489  qe
490  use mod_atmos_phy_mp_vars, only: &
491  qs_mp, &
492  qe_mp
493  implicit none
494 
495  if ( do_parent_process ) then !online [parent]
496  call atmos_boundary_firstsend( &
497  dens, momz, momx, momy, rhot, qtrc(:,:,:,qs_mp:qe_mp), qv, qe )
498  end if
499 
500  if ( l_bnd ) then
501 
502  ! initialize boundary value (reading file or waiting parent domain)
503  if ( do_daughter_process ) then
504  call atmos_boundary_set_online
505  else
506  if ( atmos_boundary_in_basename /= '' ) then
507  call atmos_boundary_set_file
508  endif
509  endif
510 
511  elseif ( atmos_boundary_type == 'CONST' ) then
512 
513  call atmos_boundary_generate
514 
515  elseif ( atmos_boundary_type == 'INIT' ) then
516 
517  call atmos_boundary_setinitval( dens, & ! [IN]
518  momz, & ! [IN]
519  momx, & ! [IN]
520  momy, & ! [IN]
521  rhot, & ! [IN]
522  qtrc ) ! [IN]
523  endif
524 
525  if( atmos_boundary_out_basename /= '' ) then
526  call atmos_boundary_write
527  endif
528 
529  if ( atmos_boundary_update_flag ) then
530 
531  call history_bnd( &
532  atmos_boundary_dens, &
533  atmos_boundary_velz, &
534  atmos_boundary_velx, &
535  atmos_boundary_vely, &
536  atmos_boundary_pott, &
537  atmos_boundary_qtrc )
538  end if
539 
540  return
real(rp), dimension(:,:,:), allocatable, target, public momz
real(rp), dimension(:,:,:), allocatable, target, public rhot
module Atmosphere / Physics Cloud Microphysics
module ATMOSPHERIC Variables
real(rp), dimension(:,:,:), allocatable, target, public momx
real(rp), dimension(:,:,:), allocatable, target, public dens
real(rp), dimension(:,:,:), allocatable, pointer, target, public qv
real(rp), dimension(:,:,:), allocatable, target, public momy
real(rp), dimension(:,:,:,:), allocatable, target, public qe
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
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 ( )

Set boundary value for real case experiment.

Definition at line 1276 of file mod_atmos_bnd_driver.F90.

References atmos_boundary_dens, atmos_boundary_pott, atmos_boundary_qtrc, atmos_boundary_velx, atmos_boundary_vely, atmos_boundary_velz, bnd_qa, scale_calendar::calendar_combine_daysec(), scale_calendar::calendar_date2daysec(), scale_comm_cartesc_nest::comm_cartesc_nest_bnd_qa, scale_comm_cartesc_nest::comm_cartesc_nest_recvwait_issue(), scale_atmos_grid_cartesc_index::ia, scale_atmos_grid_cartesc_index::ja, scale_atmos_grid_cartesc_index::ka, scale_comm_cartesc_nest::online_use_velz, scale_comm_cartesc_nest::parent_dtsec, scale_prc::prc_abort(), scale_time::time_dtsec, and scale_time::time_nowdate.

Referenced by atmos_boundary_driver_set().

1276  use scale_prc, only: &
1277  prc_abort
1278  use scale_time, only: &
1279  time_nowdate, &
1280  time_dtsec
1281  use scale_calendar, only: &
1284  implicit none
1285 
1286  real(RP) :: bnd_dens(ka,ia,ja) ! damping coefficient for DENS (0-1)
1287  real(RP) :: bnd_velz(ka,ia,ja) ! damping coefficient for VELZ (0-1)
1288  real(RP) :: bnd_velx(ka,ia,ja) ! damping coefficient for VELX (0-1)
1289  real(RP) :: bnd_vely(ka,ia,ja) ! damping coefficient for VELY (0-1)
1290  real(RP) :: bnd_pott(ka,ia,ja) ! damping coefficient for POTT (0-1)
1291  real(RP) :: bnd_qtrc(ka,ia,ja,bnd_qa) ! damping coefficient for QTRC (0-1)
1292 
1293  integer :: run_time_startdate(6)
1294  integer :: run_time_startday
1295  real(DP) :: run_time_startsec
1296  real(DP) :: run_time_startms
1297  integer :: run_time_offset_year
1298  real(DP) :: run_time_nowdaysec
1299 
1300  real(DP) :: boundary_diff_daysec
1301  real(RP) :: boundary_inc_offset
1302  integer :: fillgaps_steps
1303 
1304  integer :: i, j, k, iq
1305  !---------------------------------------------------------------------------
1306 
1307  if ( atmos_boundary_update_dt <= 0.0_dp ) then
1308  log_error("ATMOS_BOUNDARY_set_file",*) 'You need specify ATMOS_BOUNDARY_UPDATE_DT as larger than 0.0'
1309  call prc_abort
1310  endif
1311  update_nstep = nint( atmos_boundary_update_dt / time_dtsec )
1312  if ( abs(update_nstep * time_dtsec - atmos_boundary_update_dt) > 1e-10_dp ) then
1313  log_error("ATMOS_BOUNDARY_set_file",*) 'ATMOS_BOUNDARY_UPDATE_DT is not multiple of DT'
1314  call prc_abort
1315  end if
1316 
1317  !--- recalculate time of the run [no offset]
1318  run_time_startdate(:) = time_nowdate(:)
1319  run_time_startms = 0.0_dp
1320  run_time_offset_year = 0
1321 
1322  call calendar_date2daysec( run_time_startday, & ! [OUT]
1323  run_time_startsec, & ! [OUT]
1324  run_time_startdate(:), & ! [IN]
1325  run_time_startms, & ! [IN]
1326  run_time_offset_year ) ! [IN]
1327 
1328  run_time_nowdaysec = calendar_combine_daysec( run_time_startday, run_time_startsec )
1329 
1330  boundary_diff_daysec = run_time_nowdaysec - boundary_time_initdaysec
1331  boundary_timestep = 1 + int( boundary_diff_daysec / atmos_boundary_update_dt )
1332  boundary_inc_offset = mod( boundary_diff_daysec, atmos_boundary_update_dt )
1333  fillgaps_steps = int( boundary_inc_offset / time_dtsec )
1334 
1335  log_info("ATMOS_BOUNDARY_set_file",*) 'BOUNDARY TIMESTEP NUMBER FOR INIT:', boundary_timestep
1336  log_info("ATMOS_BOUNDARY_set_file",*) 'BOUNDARY OFFSET:', boundary_inc_offset
1337  log_info("ATMOS_BOUNDARY_set_file",*) 'BOUNDARY FILLGAPS STEPS:', fillgaps_steps
1338 
1339  ! read boundary data from input file
1340  call atmos_boundary_update_file( ref_now )
1341 
1342  boundary_timestep = boundary_timestep + 1
1343  call atmos_boundary_update_file( ref_new )
1344 
1345  ! copy now to old
1346  !$omp parallel do default(none) private(i,j,k,iq) OMP_SCHEDULE_ collapse(2) &
1347  !$omp shared(JA,IA,KA,ATMOS_BOUNDARY_ref_DENS,ref_old,ref_now,ATMOS_BOUNDARY_ref_VELX) &
1348  !$omp shared(ATMOS_BOUNDARY_ref_VELY,ATMOS_BOUNDARY_ref_POTT,BND_QA,ATMOS_BOUNDARY_ref_QTRC)
1349  do j = 1, ja
1350  do i = 1, ia
1351  do k = 1, ka
1352  atmos_boundary_ref_dens(k,i,j,ref_old) = atmos_boundary_ref_dens(k,i,j,ref_now)
1353  atmos_boundary_ref_velx(k,i,j,ref_old) = atmos_boundary_ref_velx(k,i,j,ref_now)
1354  atmos_boundary_ref_vely(k,i,j,ref_old) = atmos_boundary_ref_vely(k,i,j,ref_now)
1355  atmos_boundary_ref_pott(k,i,j,ref_old) = atmos_boundary_ref_pott(k,i,j,ref_now)
1356  do iq = 1, bnd_qa
1357  atmos_boundary_ref_qtrc(k,i,j,iq,ref_old) = atmos_boundary_ref_qtrc(k,i,j,iq,ref_now)
1358  end do
1359  end do
1360  end do
1361  end do
1362 
1363  ! set boundary data
1364  do j = 1, ja
1365  do i = 1, ia
1366  do k = 1, ka
1367  atmos_boundary_dens(k,i,j) = atmos_boundary_ref_dens(k,i,j,ref_now)
1368  atmos_boundary_velx(k,i,j) = atmos_boundary_ref_velx(k,i,j,ref_now)
1369  atmos_boundary_vely(k,i,j) = atmos_boundary_ref_vely(k,i,j,ref_now)
1370  atmos_boundary_pott(k,i,j) = atmos_boundary_ref_pott(k,i,j,ref_now)
1371  do iq = 1, bnd_qa
1372  atmos_boundary_qtrc(k,i,j,iq) = atmos_boundary_ref_qtrc(k,i,j,iq,ref_now)
1373  end do
1374  end do
1375  end do
1376  end do
1377 
1378  if ( atmos_boundary_use_velz ) then
1379  do j = 1, ja
1380  do i = 1, ia
1381  do k = 1, ka
1382  atmos_boundary_velz(k,i,j) = atmos_boundary_value_velz
1383  end do
1384  end do
1385  end do
1386  end if
1387 
1388  now_step = fillgaps_steps
1389 
1390  ! get time boundary
1391  call get_boundary( bnd_dens(:,:,:), & ! [OUT]
1392  bnd_velz(:,:,:), & ! [OUT]
1393  bnd_velx(:,:,:), & ! [OUT]
1394  bnd_vely(:,:,:), & ! [OUT]
1395  bnd_pott(:,:,:), & ! [OUT]
1396  bnd_qtrc(:,:,:,:), & ! [OUT]
1397  now_step, & ! [IN]
1398  update_nstep ) ! [IN]
1399 
1400  ! fill in gaps of the offset
1401  do j = 1, ja
1402  do i = 1, ia
1403  do k = 1, ka
1404  atmos_boundary_dens(k,i,j) = bnd_dens(k,i,j)
1405  atmos_boundary_velx(k,i,j) = bnd_velx(k,i,j)
1406  atmos_boundary_vely(k,i,j) = bnd_vely(k,i,j)
1407  atmos_boundary_pott(k,i,j) = bnd_pott(k,i,j)
1408  do iq = 1, bnd_qa
1409  atmos_boundary_qtrc(k,i,j,iq) = bnd_qtrc(k,i,j,iq)
1410  end do
1411  end do
1412  end do
1413  end do
1414 
1415  return
real(dp) function, public calendar_combine_daysec(absday, abssec)
Combine day and second.
real(dp), public time_dtsec
time interval of model [sec]
Definition: scale_time.F90:38
module PROCESS
Definition: scale_prc.F90:11
module TIME
Definition: scale_time.F90:16
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
module CALENDAR
integer, dimension(6), public time_nowdate
current time [YYYY MM DD HH MM SS]
Definition: scale_time.F90:69
subroutine, public calendar_date2daysec(absday, abssec, ymdhms, subsec, offset_year)
Convert from gregorian date to absolute day/second.
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 ( )

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

Definition at line 1450 of file mod_atmos_bnd_driver.F90.

References atmos_boundary_dens, atmos_boundary_pott, atmos_boundary_qtrc, atmos_boundary_velx, atmos_boundary_vely, atmos_boundary_velz, bnd_qa, scale_comm_cartesc_nest::comm_cartesc_nest_bnd_qa, scale_atmos_grid_cartesc_index::ia, scale_atmos_grid_cartesc_index::ja, scale_atmos_grid_cartesc_index::ka, scale_atmos_hydrometeor::n_hyd, scale_comm_cartesc_nest::online_use_velz, scale_comm_cartesc_nest::parent_nstep, scale_prc::prc_abort(), mod_atmos_phy_mp_vars::qa_mp, scale_time::time_dtsec, and scale_time::time_nstep.

Referenced by atmos_boundary_driver_set().

1450  use scale_prc, only: &
1451  prc_abort
1452  use scale_time, only: &
1453  time_dtsec, &
1454  time_nstep
1455  use scale_comm_cartesc_nest, only: &
1456  online_use_velz, &
1457  parent_nstep
1458  implicit none
1459 
1460  ! parameters
1461  integer, parameter :: handle = 2
1462 
1463  ! works
1464  integer :: i, j, k, iq
1465  !---------------------------------------------------------------------------
1466 
1467  ! import data from parent domain
1468  boundary_timestep = 1
1469  log_info("ATMOS_BOUNDARY_set_online",*) 'BOUNDARY TIMESTEP NUMBER FOR INIT:', boundary_timestep
1470 
1471  call atmos_boundary_update_online_daughter( ref_now )
1472 
1473  boundary_timestep = boundary_timestep + 1
1474  log_info("ATMOS_BOUNDARY_set_online",*) 'BOUNDARY TIMESTEP NUMBER FOR INIT:', boundary_timestep
1475 
1476  call atmos_boundary_update_online_daughter( ref_new )
1477 
1478  ! copy now to old
1479  do j = 1, ja
1480  do i = 1, ia
1481  do k = 1, ka
1482  atmos_boundary_ref_dens(k,i,j,ref_old) = atmos_boundary_ref_dens(k,i,j,ref_now)
1483  atmos_boundary_ref_velx(k,i,j,ref_old) = atmos_boundary_ref_velx(k,i,j,ref_now)
1484  atmos_boundary_ref_vely(k,i,j,ref_old) = atmos_boundary_ref_vely(k,i,j,ref_now)
1485  atmos_boundary_ref_pott(k,i,j,ref_old) = atmos_boundary_ref_pott(k,i,j,ref_now)
1486  do iq = 1, bnd_qa
1487  atmos_boundary_ref_qtrc(k,i,j,iq,ref_old) = atmos_boundary_ref_qtrc(k,i,j,iq,ref_now)
1488  end do
1489  end do
1490  end do
1491  end do
1492 
1493  ! set boundary data
1494  do j = 1, ja
1495  do i = 1, ia
1496  do k = 1, ka
1497  atmos_boundary_dens(k,i,j) = atmos_boundary_ref_dens(k,i,j,ref_now)
1498  atmos_boundary_velx(k,i,j) = atmos_boundary_ref_velx(k,i,j,ref_now)
1499  atmos_boundary_vely(k,i,j) = atmos_boundary_ref_vely(k,i,j,ref_now)
1500  atmos_boundary_pott(k,i,j) = atmos_boundary_ref_pott(k,i,j,ref_now)
1501  do iq = 1, bnd_qa
1502  atmos_boundary_qtrc(k,i,j,iq) = atmos_boundary_ref_qtrc(k,i,j,iq,ref_now)
1503  end do
1504  end do
1505  end do
1506  end do
1507 
1508  if ( online_use_velz ) then
1509  do j = 1, ja
1510  do i = 1, ia
1511  do k = 1, ka
1512  atmos_boundary_velz(k,i,j) = atmos_boundary_ref_velz(k,i,j,ref_now)
1513  end do
1514  end do
1515  end do
1516  else if ( atmos_boundary_use_velz ) then
1517  do j = 1, ja
1518  do i = 1, ia
1519  do k = 1, ka
1520  atmos_boundary_velz(k,i,j) = atmos_boundary_value_velz
1521  end do
1522  end do
1523  end do
1524  end if
1525 
1526  update_nstep = nint( atmos_boundary_update_dt / time_dtsec )
1527  if ( update_nstep * time_dtsec /= atmos_boundary_update_dt ) then
1528  log_error("ATMOS_BOUNDARY_set_online",*) 'DT of the parent is not multiple of the DT'
1529  call prc_abort
1530  end if
1531  if ( update_nstep * parent_nstep(handle) /= time_nstep ) then
1532  log_error("ATMOS_BOUNDARY_set_online",*) 'DURATION must be the same as that of the parent'
1533  call prc_abort
1534  end if
1535 
1536  now_step = 0 ! should be set as zero in initialize process
1537 
1538  return
integer, public time_nstep
total steps [number]
Definition: scale_time.F90:75
integer, dimension(2), public parent_nstep
parent step [number]
real(dp), public time_dtsec
time interval of model [sec]
Definition: scale_time.F90:38
module PROCESS
Definition: scale_prc.F90:11
module TIME
Definition: scale_time.F90:16
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
module Communication CartesianC nesting
Here is the call graph for this function:
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 1576 of file mod_atmos_bnd_driver.F90.

References scale_comm_cartesc_nest::comm_cartesc_nest_bnd_qa, scale_comm_cartesc_nest::comm_cartesc_nest_recv_cancel(), scale_comm_cartesc_nest::comm_cartesc_nest_recvwait_issue(), and scale_file_cartesc::file_cartesc_close().

Referenced by mod_atmos_driver::atmos_driver_finalize().

1576  use scale_comm_cartesc_nest, only: &
1579  nestqa => comm_cartesc_nest_bnd_qa
1580  use scale_file_cartesc, only: &
1582  implicit none
1583 
1584  ! works
1585  integer :: handle
1586  !---------------------------------------------------------------------------
1587 
1588  if ( do_parent_process ) then !online [parent]
1589  handle = 1
1590  call comm_cartesc_nest_recvwait_issue( handle, nestqa )
1591  endif
1592 
1593  if ( do_daughter_process ) then !online [daughter]
1594  handle = 2
1595  call comm_cartesc_nest_recv_cancel( handle )
1596  endif
1597 
1598  if ( atmos_boundary_fid > 0 ) then
1599  call file_cartesc_close( atmos_boundary_fid )
1600  atmos_boundary_fid = -1
1601  end if
1602 
1603  return
integer, public comm_cartesc_nest_bnd_qa
number of tracer treated in nesting system
subroutine, public comm_cartesc_nest_recv_cancel(HANDLE)
Sub-command for data transfer from parent to daughter: nestdown.
subroutine, public comm_cartesc_nest_recvwait_issue(HANDLE, BND_QA)
Sub-command for data transfer from parent to daughter: nestdown.
module Communication CartesianC nesting
module file / cartesianC
subroutine, public file_cartesc_close(fid)
Close a netCDF file.
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 ( )

Update boundary value with a constant time boundary.

Definition at line 1609 of file mod_atmos_bnd_driver.F90.

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_qa, scale_comm_cartesc_nest::comm_cartesc_nest_bnd_qa, scale_comm_cartesc_nest::comm_cartesc_nest_nestdown(), scale_comm_cartesc_nest::comm_cartesc_nest_recvwait_issue(), scale_comm_cartesc_nest::comm_cartesc_nest_test(), scale_comm_cartesc_nest::daughter_ia, scale_comm_cartesc_nest::daughter_ja, scale_comm_cartesc_nest::daughter_ka, dens, scale_file_cartesc::file_cartesc_flush(), 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::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_boundary_diagqhyd, scale_comm_cartesc_nest::online_use_velz, scale_comm_cartesc_nest::parent_ia, scale_comm_cartesc_nest::parent_ja, scale_comm_cartesc_nest::parent_ka, scale_prc::prc_abort(), 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, 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, scale_time::time_dtsec, scale_tracer::tracer_name, and update_ref_index().

Referenced by mod_atmos_driver::atmos_driver_update().

1609  use scale_prc, only: &
1610  prc_abort
1611  use scale_prc_cartesc, only: &
1612  prc_has_w, &
1613  prc_has_e, &
1614  prc_has_s, &
1615  prc_has_n
1616  use scale_comm_cartesc_nest, only: &
1617  online_use_velz, &
1619  use mod_atmos_vars, only: &
1620  dens, &
1621  momz, &
1622  momx, &
1623  momy, &
1624  rhot, &
1625  qtrc, &
1626  qv, &
1627  qe
1628  use mod_atmos_phy_mp_vars, only: &
1629  qs_mp, &
1630  qe_mp
1631  implicit none
1632 
1633  real(RP) :: bnd_dens(ka,ia,ja) ! damping coefficient for DENS (0-1)
1634  real(RP) :: bnd_velz(ka,ia,ja) ! damping coefficient for VELZ (0-1)
1635  real(RP) :: bnd_velx(ka,ia,ja) ! damping coefficient for VELX (0-1)
1636  real(RP) :: bnd_vely(ka,ia,ja) ! damping coefficient for VELY (0-1)
1637  real(RP) :: bnd_pott(ka,ia,ja) ! damping coefficient for POTT (0-1)
1638  real(RP) :: bnd_qtrc(ka,ia,ja,bnd_qa) ! damping coefficient for QTRC (0-1)
1639 
1640  integer :: handle
1641  integer :: i, j, k, iq, iqa
1642  !---------------------------------------------------------------------------
1643 
1644  if ( do_parent_process ) then !online [parent]
1645  ! should be called every time step
1646  call atmos_boundary_update_online_parent( dens,momz,momx,momy,rhot,qtrc(:,:,:,qs_mp:qe_mp), qv, qe )
1647  endif
1648 
1649  if ( l_bnd ) then
1650  ! update referce vars
1651  if ( now_step >= update_nstep ) then
1652  now_step = 0
1653  boundary_timestep = boundary_timestep + 1
1654 
1655  call update_ref_index
1656 
1657  if ( do_daughter_process ) then !online [daughter]
1658  call atmos_boundary_update_online_daughter( ref_new )
1659  else
1660  call atmos_boundary_update_file( ref_new )
1661  end if
1662  end if
1663 
1664  ! step boundary
1665  now_step = now_step + 1
1666 
1667  ! get boundaryal coefficients
1668  call get_boundary( bnd_dens(:,:,:), & ! [OUT]
1669  bnd_velz(:,:,:), & ! [OUT]
1670  bnd_velx(:,:,:), & ! [OUT]
1671  bnd_vely(:,:,:), & ! [OUT]
1672  bnd_pott(:,:,:), & ! [OUT]
1673  bnd_qtrc(:,:,:,:), & ! [OUT]
1674  now_step, & ! [IN]
1675  update_nstep ) ! [IN]
1676 
1677  ! update boundary vars
1678  do j = 1, ja
1679  do i = 1, ia
1680  do k = 1, ka
1681  atmos_boundary_dens(k,i,j) = bnd_dens(k,i,j)
1682  atmos_boundary_velx(k,i,j) = bnd_velx(k,i,j)
1683  atmos_boundary_vely(k,i,j) = bnd_vely(k,i,j)
1684  atmos_boundary_pott(k,i,j) = bnd_pott(k,i,j)
1685  do iq = 1, bnd_qa
1686  atmos_boundary_qtrc(k,i,j,iq) = bnd_qtrc(k,i,j,iq)
1687  end do
1688  end do
1689  end do
1690  end do
1691  if ( online_use_velz ) then
1692  do j = 1, ja
1693  do i = 1, ia
1694  do k = 1, ka
1695  atmos_boundary_velz(k,i,j) = bnd_velz(k,i,j)
1696  end do
1697  end do
1698  end do
1699  end if
1700 
1701  ! fill HALO in western region
1702  if ( .NOT. prc_has_w ) then
1703  !$omp parallel do default(none) &
1704  !$omp shared(JS,IS,KA,DENS,ATMOS_BOUNDARY_DENS,MOMX,ATMOS_BOUNDARY_VELX,RHOT) &
1705  !$omp shared(ATMOS_BOUNDARY_POTT,ATMOS_BOUNDARY_QTRC,BND_QA,QS_MP,QTRC,QA,JA) &
1706  !$omp private(i,j,k,iq,iqa) OMP_SCHEDULE_ collapse(2)
1707  do j = 1, ja
1708  do i = 1, is-1
1709  do k = 1, ka
1710  dens(k,i,j) = atmos_boundary_dens(k,i,j)
1711  momx(k,i,j) = atmos_boundary_velx(k,i,j) &
1712  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i+1,j) ) * 0.5_rp
1713  rhot(k,i,j) = atmos_boundary_pott(k,i,j) * atmos_boundary_dens(k,i,j)
1714  do iq = 1, bnd_qa
1715  iqa = iq + qs_mp - 1
1716  qtrc(k,i,j,iqa) = atmos_boundary_qtrc(k,i,j,iq)
1717  end do
1718  do iq = 1, qa
1719  if ( iq < qs_mp .or. iq >= bnd_qa + qs_mp ) then
1720  qtrc(k,i,j,iq) = qtrc(k,is,j,iq) &
1721  * ( 0.5_rp - sign(0.5_rp, atmos_boundary_velx(k,is-1,j)) )
1722  end if
1723  end do
1724  end do
1725  end do
1726  end do
1727  do j = 1, ja-1
1728  do i = 1, is-1
1729  do k = 1, ka
1730  momy(k,i,j) = atmos_boundary_vely(k,i,j) &
1731  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i,j+1) ) * 0.5_rp
1732  end do
1733  end do
1734  end do
1735  do i = 1, is-1
1736  do k = 1, ka
1737  momy(k,i,ja) = atmos_boundary_vely(k,i,ja) &
1738  * atmos_boundary_dens(k,i,ja)
1739  end do
1740  end do
1741  if ( online_use_velz ) then
1742  do j = 1, ja
1743  do i = 1, is-1
1744  do k = ks, ke-1
1745  momz(k,i,j) = atmos_boundary_velz(k,i,j) &
1746  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k+1,i,j) ) * 0.5_rp
1747  end do
1748  end do
1749  end do
1750  else
1751  do j = 1, ja
1752  do i = 1, is-1
1753  do k = ks, ke-1
1754  momz(k,i,j) = momz(k,is,j)
1755  end do
1756  end do
1757  end do
1758  end if
1759  end if
1760 
1761  ! fill HALO in eastern region
1762  if ( .NOT. prc_has_e ) then
1763  !$omp parallel do default(none) &
1764  !$omp shared(JA,IE,IA,KA,DENS,ATMOS_BOUNDARY_DENS,ATMOS_BOUNDARY_VELX,RHOT) &
1765  !$omp shared(ATMOS_BOUNDARY_POTT,ATMOS_BOUNDARY_QTRC,BND_QA,QS_MP,QTRC,QA) &
1766  !$omp private(i,j,k,iq,iqa) OMP_SCHEDULE_ collapse(2)
1767  do j = 1, ja
1768  do i = ie+1, ia
1769  do k = 1, ka
1770  dens(k,i,j) = atmos_boundary_dens(k,i,j)
1771  rhot(k,i,j) = atmos_boundary_pott(k,i,j) * atmos_boundary_dens(k,i,j)
1772  do iq = 1, bnd_qa
1773  iqa = iq + qs_mp - 1
1774  qtrc(k,i,j,iqa) = atmos_boundary_qtrc(k,i,j,iq)
1775  end do
1776  do iq = 1, qa
1777  if ( iq < qs_mp .or. iq >= bnd_qa + qs_mp ) then
1778  qtrc(k,i,j,iq) = qtrc(k,ie,j,iq) &
1779  * ( 0.5_rp + sign(0.5_rp, atmos_boundary_velx(k,ie,j)) )
1780  end if
1781  end do
1782  end do
1783  end do
1784  end do
1785  do j = 1, ja
1786  do i = ie, ia-1
1787  do k = 1, ka
1788  momx(k,i,j) = atmos_boundary_velx(k,i,j) &
1789  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i+1,j) ) * 0.5_rp
1790  end do
1791  end do
1792  end do
1793  do j = 1, ja
1794  do k = 1, ka
1795  momx(k,ia,j) = atmos_boundary_velx(k,ia,j) * atmos_boundary_dens(k,ia,j)
1796  end do
1797  end do
1798  do j = 1, ja-1
1799  do i = ie+1, ia
1800  do k = 1, ka
1801  momy(k,i,j) = atmos_boundary_vely(k,i,j) &
1802  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i,j+1) ) * 0.5_rp
1803  end do
1804  end do
1805  end do
1806  do i = ie+1, ia
1807  do k = 1, ka
1808  momy(k,i,ja) = atmos_boundary_vely(k,i,ja) &
1809  * atmos_boundary_dens(k,i,ja)
1810  end do
1811  end do
1812  if ( online_use_velz ) then
1813  do j = 1, ja
1814  do i = ie+1, ia
1815  do k = ks, ke-1
1816  momz(k,i,j) = atmos_boundary_velz(k,i,j) &
1817  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k+1,i,j) ) * 0.5_rp
1818  end do
1819  end do
1820  end do
1821  else
1822  do j = 1, ja
1823  do i = ie+1, ia
1824  do k = ks, ke-1
1825  momz(k,i,j) = momz(k,ie,j)
1826  end do
1827  end do
1828  end do
1829  end if
1830  end if
1831 
1832  ! fill HALO in southern region
1833  if ( .NOT. prc_has_s ) then
1834  !$omp parallel do default(none) &
1835  !$omp shared(JS,IA,KA,DENS,ATMOS_BOUNDARY_DENS,MOMY,ATMOS_BOUNDARY_VELY,RHOT) &
1836  !$omp shared(ATMOS_BOUNDARY_POTT,ATMOS_BOUNDARY_QTRC,BND_QA,QS_MP,QTRC,QA) &
1837  !$omp private(i,j,k,iq,iqa) OMP_SCHEDULE_ collapse(2)
1838  do j = 1, js-1
1839  do i = 1, ia
1840  do k = 1, ka
1841  dens(k,i,j) = atmos_boundary_dens(k,i,j)
1842  momy(k,i,j) = atmos_boundary_vely(k,i,j) &
1843  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i,j+1) ) * 0.5_rp
1844  rhot(k,i,j) = atmos_boundary_pott(k,i,j) * atmos_boundary_dens(k,i,j)
1845  do iq = 1, bnd_qa
1846  iqa = iq + qs_mp - 1
1847  qtrc(k,i,j,iqa) = atmos_boundary_qtrc(k,i,j,iq)
1848  end do
1849  do iq = 1, qa
1850  if ( iq < qs_mp .or. iq >= bnd_qa + qs_mp ) then
1851  qtrc(k,i,j,iq) = qtrc(k,i,js,iq) &
1852  * ( 0.5_rp - sign(0.5_rp, atmos_boundary_vely(k,i,js-1)) )
1853  end if
1854  end do
1855  end do
1856  end do
1857  end do
1858  do j = 1, js-1
1859  do i = 1, ia-1
1860  do k = 1, ka
1861  momx(k,i,j) = atmos_boundary_velx(k,i,j) &
1862  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i+1,j) ) * 0.5_rp
1863  end do
1864  end do
1865  end do
1866  do j = 1, js-1
1867  do k = 1, ka
1868  momx(k,ia,j) = atmos_boundary_velx(k,ia,j) &
1869  * atmos_boundary_dens(k,ia,j)
1870  end do
1871  end do
1872  if ( online_use_velz ) then
1873  do j = 1, js-1
1874  do i = 1, ia
1875  do k = ks, ke-1
1876  momz(k,i,j) = atmos_boundary_velz(k,i,j) &
1877  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k+1,i,j) ) * 0.5_rp
1878  end do
1879  end do
1880  end do
1881  else
1882  do j = 1, js-1
1883  do i = 1, ia
1884  do k = ks, ke-1
1885  momz(k,i,j) = momz(k,i,js)
1886  end do
1887  end do
1888  end do
1889  end if
1890  end if
1891 
1892  ! fill HALO in northern region
1893  if ( .NOT. prc_has_n ) then
1894  !$omp parallel do default(none) &
1895  !$omp shared(JE,JA,IA,KA,DENS,ATMOS_BOUNDARY_DENS,ATMOS_BOUNDARY_VELY,RHOT) &
1896  !$omp shared(ATMOS_BOUNDARY_POTT,ATMOS_BOUNDARY_QTRC,BND_QA,QS_MP,QTRC,QA) &
1897  !$omp private(i,j,k,iq,iqa) OMP_SCHEDULE_ collapse(2)
1898  do j = je+1, ja
1899  do i = 1, ia
1900  do k = 1, ka
1901  dens(k,i,j) = atmos_boundary_dens(k,i,j)
1902  rhot(k,i,j) = atmos_boundary_pott(k,i,j) * atmos_boundary_dens(k,i,j)
1903  do iq = 1, bnd_qa
1904  iqa = iq + qs_mp - 1
1905  qtrc(k,i,j,iqa) = atmos_boundary_qtrc(k,i,j,iq)
1906  end do
1907  do iq = bnd_qa+1, qa
1908  if ( iq < qs_mp .or. iq >= bnd_qa + qs_mp ) then
1909  qtrc(k,i,j,iq) = qtrc(k,i,je,iq) &
1910  * ( 0.5_rp + sign(0.5_rp, atmos_boundary_vely(k,i,je)) )
1911  end if
1912  end do
1913  end do
1914  end do
1915  end do
1916  do j = je, ja-1
1917  do i = 1, ia
1918  do k = 1, ka
1919  momy(k,i,j) = atmos_boundary_vely(k,i,j) &
1920  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i,j+1) ) * 0.5_rp
1921  end do
1922  end do
1923  end do
1924  do i = 1, ia
1925  do k = 1, ka
1926  momy(k,i,ja) = atmos_boundary_vely(k,i,ja) * atmos_boundary_dens(k,i,ja)
1927  end do
1928  end do
1929  do j = je+1, ja
1930  do i = 1, ia-1
1931  do k = 1, ka
1932  momx(k,i,j) = atmos_boundary_velx(k,i,j) &
1933  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k,i+1,j) ) * 0.5_rp
1934  end do
1935  end do
1936  end do
1937  do j = je+1, ja
1938  do k = 1, ka
1939  momx(k,ia,j) = atmos_boundary_velx(k,ia,j) &
1940  * atmos_boundary_dens(k,ia,j)
1941  end do
1942  end do
1943  if ( online_use_velz ) then
1944  do j = je+1, ja
1945  do i = 1, ia
1946  do k = ks, ke-1
1947  momz(k,i,j) = atmos_boundary_velz(k,i,j) &
1948  * ( atmos_boundary_dens(k,i,j) + atmos_boundary_dens(k+1,i,j) ) * 0.5_rp
1949  end do
1950  end do
1951  end do
1952  else
1953  do j = je+1, ja
1954  do i = 1, ia
1955  do k = ks, ke-1
1956  momz(k,i,j) = momz(k,i,je)
1957  end do
1958  end do
1959  end do
1960  end if
1961  end if
1962 
1963  elseif ( do_parent_process ) then
1964  ! do nothing
1965  else
1966  log_error("ATMOS_BOUNDARY_update",*) '[BUG] invalid path'
1967  call prc_abort
1968  end if
1969 
1970  call history_bnd( atmos_boundary_dens, &
1971  atmos_boundary_velz, &
1972  atmos_boundary_velx, &
1973  atmos_boundary_vely, &
1974  atmos_boundary_pott, &
1975  atmos_boundary_qtrc )
1976 
1977  ! To be enable to do asynchronous communicaton
1978  if ( do_parent_process ) then !online [parent]
1979  handle = 1
1980  call comm_cartesc_nest_test( handle )
1981  endif
1982  if ( do_daughter_process ) then !online [daughter]
1983  handle = 2
1984  call comm_cartesc_nest_test( handle )
1985  endif
1986 
1987  return
real(rp), dimension(:,:,:), allocatable, target, public momz
real(rp), dimension(:,:,:), allocatable, target, public rhot
module Atmosphere / Physics Cloud Microphysics
module ATMOSPHERIC Variables
real(rp), dimension(:,:,:), allocatable, target, public momx
module process / cartesC
real(rp), dimension(:,:,:), allocatable, target, public dens
logical, public prc_has_s
logical, public prc_has_n
logical, public prc_has_e
module PROCESS
Definition: scale_prc.F90:11
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
real(rp), dimension(:,:,:), allocatable, pointer, target, public qv
subroutine, public comm_cartesc_nest_test(HANDLE)
[check communication status] Inter-communication
module Communication CartesianC nesting
real(rp), dimension(:,:,:), allocatable, target, public momy
real(rp), dimension(:,:,:,:), allocatable, target, public qe
logical, public prc_has_w
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
Here is the call graph for this function:
Here is the caller graph for this function:

◆ update_ref_index()

subroutine mod_atmos_bnd_driver::update_ref_index ( )

Update indices of array of boundary references.

Definition at line 2539 of file mod_atmos_bnd_driver.F90.

References bnd_qa, mod_atmos_phy_mp_vars::qs_mp, and scale_tracer::tracer_name.

Referenced by atmos_boundary_driver_update().

2539  implicit none
2540 
2541  ! works
2542  integer :: ref_tmp
2543  !---------------------------------------------------------------------------
2544 
2545  ref_tmp = ref_old
2546  ref_old = ref_now
2547  ref_now = ref_new
2548  ref_new = ref_tmp
2549 
2550  return
Here is the caller graph for this function:

Variable Documentation

◆ bnd_qa

integer, public mod_atmos_bnd_driver::bnd_qa

◆ of

integer, public mod_atmos_bnd_driver::of

Definition at line 41 of file mod_atmos_bnd_driver.F90.

◆ tracer

integer, public mod_atmos_bnd_driver::tracer

Definition at line 41 of file mod_atmos_bnd_driver.F90.

◆ at

integer, public mod_atmos_bnd_driver::at

Definition at line 41 of file mod_atmos_bnd_driver.F90.

◆ boundary

integer, public mod_atmos_bnd_driver::boundary

Definition at line 41 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 43 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 44 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 45 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 46 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 47 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 50 of file mod_atmos_bnd_driver.F90.

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

50  real(RP), public, allocatable :: atmos_boundary_alpha_dens(:,:,:)

◆ damping

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

Definition at line 50 of file mod_atmos_bnd_driver.F90.

◆ coefficient

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

Definition at line 50 of file mod_atmos_bnd_driver.F90.

◆ for

logical allocatable public mod_atmos_bnd_driver::for

Definition at line 50 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 51 of file mod_atmos_bnd_driver.F90.

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

51  real(RP), public, allocatable :: atmos_boundary_alpha_velz(:,:,:)

◆ atmos_boundary_alpha_velx

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

Definition at line 52 of file mod_atmos_bnd_driver.F90.

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

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

◆ atmos_boundary_alpha_vely

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

Definition at line 53 of file mod_atmos_bnd_driver.F90.

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

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

◆ atmos_boundary_alpha_pott

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

Definition at line 54 of file mod_atmos_bnd_driver.F90.

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

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

◆ atmos_boundary_alpha_qtrc

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

Definition at line 55 of file mod_atmos_bnd_driver.F90.

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

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

◆ atmos_boundary_smoother_fact

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

Definition at line 58 of file mod_atmos_bnd_driver.F90.

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

58  real(RP), public :: atmos_boundary_smoother_fact = 0.2_rp ! fact for smoother to damping

◆ atmos_boundary_update_flag

logical, public mod_atmos_bnd_driver::atmos_boundary_update_flag = .false.

Definition at line 60 of file mod_atmos_bnd_driver.F90.

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

60  logical, public :: atmos_boundary_update_flag = .false.

◆ switch

logical, public mod_atmos_bnd_driver::switch

Definition at line 60 of file mod_atmos_bnd_driver.F90.

◆ real

mod_atmos_bnd_driver::real

Definition at line 60 of file mod_atmos_bnd_driver.F90.

◆ case

logical, public mod_atmos_bnd_driver::case

Definition at line 60 of file mod_atmos_bnd_driver.F90.