SCALE-RM
Functions/Subroutines | Variables
mod_atmos_vars Module Reference

module ATMOSPHERIC Variables More...

Functions/Subroutines

subroutine, public atmos_vars_setup
 Setup. More...
 
subroutine, public atmos_vars_fillhalo (FILL_BND)
 HALO Communication. More...
 
subroutine, public atmos_vars_restart_open
 Open restart file for reading atmospheric variables. More...
 
subroutine, public atmos_vars_restart_read
 Read restart of atmospheric variables. More...
 
subroutine, public atmos_vars_history_setpres
 Set pressure for history output. More...
 
subroutine, public atmos_vars_restart_check
 Check and compare between last data and sample data. More...
 
subroutine, public atmos_vars_history
 History output set for atmospheric variables. More...
 
subroutine, public atmos_vars_total
 Budget monitor for atmosphere. More...
 
subroutine, public atmos_vars_diagnostics
 Calc diagnostic variables. More...
 
subroutine, public atmos_vars_monitor
 monitor output More...
 
subroutine, public atmos_vars_restart_create
 Create atmospheric restart file. More...
 
subroutine, public atmos_vars_restart_enddef
 Exit netCDF define mode. More...
 
subroutine, public atmos_vars_restart_close
 Close restart file. More...
 
subroutine, public atmos_vars_restart_def_var
 Define atmospheric variables in restart file. More...
 
subroutine, public atmos_vars_restart_write
 Write restart of atmospheric variables. More...
 

Variables

logical, public atmos_restart_output = .false.
 Output restart file? More...
 
character(len=h_long), public atmos_restart_in_basename = ''
 Basename of the input file. More...
 
logical, public atmos_restart_in_postfix_timelabel = .false.
 Add timelabel to the basename of input file? More...
 
character(len=h_long), public atmos_restart_out_basename = ''
 Basename of the output file. More...
 
logical, public atmos_restart_out_postfix_timelabel = .true.
 Add timelabel to the basename of output file? More...
 
character(len=h_mid), public atmos_restart_out_title = 'ATMOS restart'
 Title of the output file. More...
 
character(len=h_short), public atmos_restart_out_dtype = 'DEFAULT'
 REAL4 or REAL8. More...
 
logical, public atmos_restart_check = .false.
 Check value consistency? More...
 
character(len=h_long), public atmos_restart_check_basename = 'restart_check'
 
real(rp), public atmos_restart_check_criterion = 1.E-6_RP
 
real(rp), dimension(:,:,:), allocatable, target, public dens
 
real(rp), dimension(:,:,:), allocatable, target, public momz
 
real(rp), dimension(:,:,:), allocatable, target, public momx
 
real(rp), dimension(:,:,:), allocatable, target, public momy
 
real(rp), dimension(:,:,:), allocatable, target, public rhot
 
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
 
real(rp), dimension(:,:,:), allocatable, target, public dens_avw
 
real(rp), dimension(:,:,:), allocatable, target, public momz_avw
 
real(rp), dimension(:,:,:), allocatable, target, public momx_avw
 
real(rp), dimension(:,:,:), allocatable, target, public momy_avw
 
real(rp), dimension(:,:,:), allocatable, target, public rhot_avw
 
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc_avw
 
real(rp), dimension(:,:,:), pointer, public dens_av
 
real(rp), dimension(:,:,:), pointer, public momz_av
 
real(rp), dimension(:,:,:), pointer, public momx_av
 
real(rp), dimension(:,:,:), pointer, public momy_av
 
real(rp), dimension(:,:,:), pointer, public rhot_av
 
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
 
real(rp), dimension(:,:,:), allocatable, public dens_tp
 
real(rp), dimension(:,:,:), allocatable, public momz_tp
 
real(rp), dimension(:,:,:), allocatable, public momx_tp
 
real(rp), dimension(:,:,:), allocatable, public momy_tp
 
real(rp), dimension(:,:,:), allocatable, public rhot_tp
 
real(rp), dimension(:,:,:,:), allocatable, public rhoq_tp
 
real(rp), dimension(:,:,:), allocatable, public pott
 
real(rp), dimension(:,:,:), allocatable, public temp
 
real(rp), dimension(:,:,:), allocatable, public pres
 
real(rp), dimension(:,:,:), allocatable, public phyd
 
real(rp), dimension(:,:,:), allocatable, public w
 
real(rp), dimension(:,:,:), allocatable, public u
 
real(rp), dimension(:,:,:), allocatable, public v
 
real(rp), dimension(:,:,:), allocatable, public n2
 

Detailed Description

module ATMOSPHERIC Variables

Description
Container for atmospheric variables
Author
Team SCALE
History
  • 2011-11-11 (H.Yashiro) [new]
  • 2012-03-23 (H.Yashiro) [mod] Explicit index parameter inclusion
  • 2012-06-13 (S.Nishizawa) [mod] follows the change of mod_hist
NAMELIST
  • PARAM_ATMOS_VARS
    nametypedefault valuecomment
    ATMOS_RESTART_IN_BASENAME character(len=H_LONG) '' Basename of the input file
    ATMOS_RESTART_IN_POSTFIX_TIMELABEL logical .false. Add timelabel to the basename of input file?
    ATMOS_RESTART_IN_CHECK_COORDINATES logical .true.
    ATMOS_RESTART_OUTPUT logical .false. Output restart file?
    ATMOS_RESTART_OUT_BASENAME character(len=H_LONG) '' Basename of the output file
    ATMOS_RESTART_OUT_POSTFIX_TIMELABEL logical .true. Add timelabel to the basename of output file?
    ATMOS_RESTART_OUT_TITLE character(len=H_MID) 'ATMOS restart' Title of the output file
    ATMOS_RESTART_OUT_DTYPE character(len=H_SHORT) 'DEFAULT' REAL4 or REAL8
    ATMOS_RESTART_CHECK logical .false. Check value consistency?
    ATMOS_RESTART_CHECK_BASENAME character(len=H_LONG) 'restart_check'
    ATMOS_RESTART_CHECK_CRITERION real(RP) 1.E-6_RP
    ATMOS_VARS_CHECKRANGE logical .false.
    ATMOS_VARS_CHECKCFL real(RP) 0.0_RP

History Output
namedescriptionunitvariable
CAPE convection avail. pot. energy m2/s2 CAPE
CIN convection inhibition m2/s2 CIN
CPTOT Total heat capacity J/kg/K CPTOT
DENS_MEAN horiz. mean of density kg/m3 DENS_MEAN
DENS_PRIM horiz. deviation of density kg/m3 DENS_PRIM
DIV divergence 1/s DIV
ENGI internal energy J/m3 ENGI
ENGK kinetic energy J/m3 ENGK
ENGP potential energy J/m3 ENGP
ENGT total energy J/m3 ENGT
HDIV horizontal divergence 1/s HDIV
IWP ice water path g/m2 IWP
LCL lifted condensation level m LCL
LFC level of free convection m LFC
LNB level of neutral buoyancy m LNB
LWP liquid water path g/m2 LWP
LWPT liq. potential temp. K POTL
MSE moist static energy m2/s2 MSE
N2 squared Brunt-Vaisala frequency 1/s2 N2
PBLH PBL height m PBLH
PREC surface precipitation rate (total) kg/m2/s PREC
PRES pressure Pa PRES
PT potential temp. K POTT
PT_MEAN horiz. mean of pot. K PT_MEAN
PT_PRIM horiz. deviation of pot. temp. K POTT_PRIM
PT_W_PRIM resolved scale heat flux W/s PT_W_PRIM
PW precipitable water g/m2 PW
QDRY dry air kg/kg QDRY
QHYD total hydrometeors kg/kg QHYD
QHYD_MEAN horiz. mean of QHYD 1 QHYD_MEAN
QICE total ice water kg/kg QICE
QICE_MEAN horiz. mean of QICE 1 QICE_MEAN
QLIQ total liquid water kg/kg QLIQ
QLIQ_MEAN horiz. mean of QLIQ 1 QLIQ_MEAN
QTOT total water kg/kg QTOT
QV_MEAN horiz. mean of QV 1 QV_MEAN
RAIN surface rain rate (total) kg/m2/s RAIN
RH relative humidity(liq) % RHL
RHA relative humidity(liq+ice) % RHA
RHI relative humidity(ice) % RHI
RTOT Total gas constant J/kg/K RTOT
SNOW surface snow rate (total) kg/m2/s SNOW
T temperature K TEMP
TKE_RS resolved scale TKE m2/s2 TKE_RS
TRACER_NAME(iq) TRACER_DESC(iq) TRACER_UNIT(iq) QTRC
T_MEAN horiz. mean of t K T_MEAN
U velocity u m/s U
U_MEAN horiz. mean of u m/s U_MEAN
U_PRIM horiz. deviation of u m/s U_PRIM
Uabs absolute velocity m/s Uabs
V velocity v m/s V
DENS density kg/m3 DENS
MOMX momentum x kg/m2/s MOMX
MOMY momentum y kg/m2/s MOMY
MOMZ momentum z kg/m2/s MOMZ
RHOT rho * theta kg/m3*K RHOT
VOR vertical vorticity 1/s VOR
V_MEAN horiz. mean of v m/s V_MEAN
V_PRIM horiz. deviation of v m/s V_PRIM
W velocity w m/s W
W_MEAN horiz. mean of w m/s W_MEAN
W_PRIM horiz. deviation of w m/s W_PRIM
W_PRIM2 variance of w m2/s2 W_PRIM2
W_PRIM3 skewness of w m3/s3 W_PRIM3

Function/Subroutine Documentation

◆ atmos_vars_setup()

subroutine, public mod_atmos_vars::atmos_vars_setup ( )

Setup.

Definition at line 254 of file mod_atmos_vars.f90.

References mod_atmos_dyn_vars::atmos_dyn_vars_setup(), mod_atmos_phy_ae_vars::atmos_phy_ae_vars_setup(), mod_atmos_phy_ch_vars::atmos_phy_ch_vars_setup(), mod_atmos_phy_cp_vars::atmos_phy_cp_vars_setup(), mod_atmos_phy_mp_vars::atmos_phy_mp_vars_setup(), mod_atmos_phy_rd_vars::atmos_phy_rd_vars_setup(), mod_atmos_phy_sf_vars::atmos_phy_sf_vars_setup(), mod_atmos_phy_tb_vars::atmos_phy_tb_vars_setup(), atmos_restart_check, atmos_restart_check_basename, atmos_restart_check_criterion, atmos_restart_in_basename, atmos_restart_in_postfix_timelabel, atmos_restart_out_basename, atmos_restart_out_dtype, atmos_restart_out_postfix_timelabel, atmos_restart_out_title, atmos_restart_output, mod_atmos_admin::atmos_use_average, dens, dens_av, dens_avw, dens_tp, scale_history::hist_reg(), scale_index::i_dens, scale_index::i_momx, scale_index::i_momy, scale_index::i_momz, scale_index::i_rhot, scale_grid_index::ia, scale_stdio::io_fid_conf, scale_stdio::io_fid_log, scale_stdio::io_fid_nml, scale_stdio::io_l, scale_stdio::io_nml, scale_grid_index::ja, scale_grid_index::ka, scale_grid_index::ke, scale_grid_index::ks, momx, momx_av, momx_avw, momx_tp, momy, momy_av, momy_avw, momy_tp, momz, momz_av, momz_avw, momz_tp, scale_monitor::monit_reg(), n2, phyd, pott, scale_process::prc_mpistop(), pres, scale_tracer::qa, qtrc, qtrc_av, qtrc_avw, rhoq_tp, rhot, rhot_av, rhot_avw, rhot_tp, temp, scale_tracer::tracer_desc, scale_tracer::tracer_name, scale_tracer::tracer_unit, u, v, and w.

Referenced by mod_rm_driver::scalerm(), and mod_rm_prep::scalerm_prep().

254  use scale_process, only: &
256  use scale_history, only: &
257  hist_reg
258  use scale_monitor, only: &
259  monit_reg
260  use mod_atmos_admin, only: &
262  use mod_atmos_dyn_vars, only: &
264  use mod_atmos_phy_mp_vars, only: &
266  use mod_atmos_phy_ae_vars, only: &
268  use mod_atmos_phy_ch_vars, only: &
270  use mod_atmos_phy_rd_vars, only: &
272  use mod_atmos_phy_sf_vars, only: &
274  use mod_atmos_phy_tb_vars, only: &
276  use mod_atmos_phy_cp_vars, only: &
278  implicit none
279 
280  namelist / param_atmos_vars / &
281  atmos_restart_in_basename, &
282  atmos_restart_in_postfix_timelabel, &
283  atmos_restart_in_check_coordinates, &
284  atmos_restart_output, &
285  atmos_restart_out_basename, &
286  atmos_restart_out_postfix_timelabel, &
287  atmos_restart_out_title, &
288  atmos_restart_out_dtype, &
289  atmos_restart_check, &
290  atmos_restart_check_basename, &
291  atmos_restart_check_criterion, &
292  atmos_vars_checkrange, &
293  atmos_vars_checkcfl
294 
295  integer :: ierr
296  integer :: iv, iq
297  !---------------------------------------------------------------------------
298 
299  if( io_l ) write(io_fid_log,*)
300  if( io_l ) write(io_fid_log,*) '++++++ Module[VARS] / Categ[ATMOS] / Origin[SCALE-RM]'
301 
302  allocate( dens(ka,ia,ja) )
303  allocate( momz(ka,ia,ja) )
304  allocate( momx(ka,ia,ja) )
305  allocate( momy(ka,ia,ja) )
306  allocate( rhot(ka,ia,ja) )
307  allocate( qtrc(ka,ia,ja,max(qa,1)) )
308 
309  if ( atmos_use_average ) then
310  allocate( dens_avw(ka,ia,ja) )
311  allocate( momz_avw(ka,ia,ja) )
312  allocate( momx_avw(ka,ia,ja) )
313  allocate( momy_avw(ka,ia,ja) )
314  allocate( rhot_avw(ka,ia,ja) )
315  allocate( qtrc_avw(ka,ia,ja,max(qa,1)) )
316 
317  dens_av => dens_avw
318  momz_av => momz_avw
319  momx_av => momx_avw
320  momy_av => momy_avw
321  rhot_av => rhot_avw
322  qtrc_av => qtrc_avw
323  else
324  dens_av => dens
325  momz_av => momz
326  momx_av => momx
327  momy_av => momy
328  rhot_av => rhot
329  qtrc_av => qtrc
330  endif
331 
332  allocate( dens_tp(ka,ia,ja) )
333  allocate( momz_tp(ka,ia,ja) )
334  allocate( momx_tp(ka,ia,ja) )
335  allocate( momy_tp(ka,ia,ja) )
336  allocate( rhot_tp(ka,ia,ja) )
337  allocate( rhoq_tp(ka,ia,ja,max(qa,1)) )
338 
339  allocate( pott(ka,ia,ja) )
340  allocate( temp(ka,ia,ja) )
341  allocate( pres(ka,ia,ja) )
342  allocate( phyd(ka,ia,ja) )
343  allocate( w(ka,ia,ja) )
344  allocate( u(ka,ia,ja) )
345  allocate( v(ka,ia,ja) )
346  allocate( n2(ka,ia,ja) )
347 
348  momz(1:ks-1,:,:) = 0.0_rp
349  momz(ke:ka,:,:) = 0.0_rp
350 
351  !--- read namelist
352  rewind(io_fid_conf)
353  read(io_fid_conf,nml=param_atmos_vars,iostat=ierr)
354  if( ierr < 0 ) then !--- missing
355  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
356  elseif( ierr > 0 ) then !--- fatal error
357  write(*,*) 'xxx Not appropriate names in namelist PARAM_ATMOS_VARS. Check!'
358  call prc_mpistop
359  endif
360  if( io_nml ) write(io_fid_nml,nml=param_atmos_vars)
361 
362  if( io_l ) write(io_fid_log,*)
363  if( io_l ) write(io_fid_log,*) '*** List of prognostic variables (ATMOS) ***'
364  if( io_l ) write(io_fid_log,'(1x,A,A24,A,A48,A,A12,A)') &
365  '*** |', 'VARNAME ','|', &
366  'DESCRIPTION ', '[', 'UNIT ', ']'
367  do iv = 1, vmax
368  if( io_l ) write(io_fid_log,'(1x,A,I3,A,A24,A,A48,A,A12,A)') &
369  '*** NO.',iv,'|',var_name(iv),'|', var_desc(iv),'[', var_unit(iv),']'
370  enddo
371  do iq = 1, qa
372  if( io_l ) write(io_fid_log,'(1x,A,I3,A,A24,A,A48,A,A12,A)') &
373  '*** NO.',5+iq,'|',tracer_name(iq),'|', tracer_desc(iq),'[', tracer_unit(iq),']'
374  enddo
375 
376  if( io_l ) write(io_fid_log,*)
377  if ( atmos_restart_in_basename /= '' ) then
378  if( io_l ) write(io_fid_log,*) '*** Restart input? : YES, file = ', trim(atmos_restart_in_basename)
379  if( io_l ) write(io_fid_log,*) '*** Add timelabel? : ', atmos_restart_in_postfix_timelabel
380  else
381  if( io_l ) write(io_fid_log,*) '*** Restart input? : NO'
382  endif
383  if ( atmos_restart_output &
384  .AND. atmos_restart_out_basename /= '' ) then
385  if( io_l ) write(io_fid_log,*) '*** Restart output? : YES, file = ', trim(atmos_restart_out_basename)
386  if( io_l ) write(io_fid_log,*) '*** Add timelabel? : ', atmos_restart_out_postfix_timelabel
387  else
388  if( io_l ) write(io_fid_log,*) '*** Restart output? : NO'
389  atmos_restart_output = .false.
390  endif
391 
392  if ( atmos_restart_check_basename == '' ) then
393  atmos_restart_check = .false.
394  endif
395 
396  if( io_l ) write(io_fid_log,*)
397  if( io_l ) write(io_fid_log,*) '*** Check restart consistency? : ', atmos_restart_check
398  if( io_l ) write(io_fid_log,*) '*** Check value range of variables? : ', atmos_vars_checkrange
399  if ( atmos_vars_checkcfl > 0.0_rp ) then
400  if( io_l ) write(io_fid_log,*) '*** Check CFL condition? : YES'
401  if( io_l ) write(io_fid_log,*) '*** Limit of Courant number : ', atmos_vars_checkcfl
402  else
403  if( io_l ) write(io_fid_log,*) '*** Check CFL condition? : NO'
404  endif
405 
414 
415 
416 
417  !##### todo: the part below should be moved to the mod_atmos_diag #####
418 
419  allocate( aq_hist_id(max(qa,1)))
420 
421  var_hist_id(:) = -1
422  aq_hist_id(:) = -1
423  ad_hist_id(:) = -1
424  ad_monit_id(:) = -1
425  ad_prep_sw(:) = -1
426 
427  call hist_reg( var_hist_id(i_dens), var_name(i_dens), var_desc(i_dens), var_unit(i_dens), ndim=3 )
428  call hist_reg( var_hist_id(i_momz), var_name(i_momz), var_desc(i_momz), var_unit(i_momz), ndim=3, zdim='half' )
429  call hist_reg( var_hist_id(i_momx), var_name(i_momx), var_desc(i_momx), var_unit(i_momx), ndim=3, xdim='half' )
430  call hist_reg( var_hist_id(i_momy), var_name(i_momy), var_desc(i_momy), var_unit(i_momy), ndim=3, ydim='half' )
431  call hist_reg( var_hist_id(i_rhot), var_name(i_rhot), var_desc(i_rhot), var_unit(i_rhot), ndim=3 )
432  do iq = 1, qa
433  call hist_reg( aq_hist_id(iq), tracer_name(iq), tracer_desc(iq), tracer_unit(iq), ndim=3 )
434  enddo
435 
436  call hist_reg( ad_hist_id(i_w) , 'W', 'velocity w', 'm/s', ndim=3 )
437  call hist_reg( ad_hist_id(i_u) , 'U', 'velocity u', 'm/s', ndim=3 )
438  call hist_reg( ad_hist_id(i_v) , 'V', 'velocity v', 'm/s', ndim=3 )
439  call hist_reg( ad_hist_id(i_pott) , 'PT', 'potential temp.', 'K', ndim=3 )
440 
441  call hist_reg( ad_hist_id(i_qdry) , 'QDRY', 'dry air', 'kg/kg', ndim=3 )
442  call hist_reg( ad_hist_id(i_qtot) , 'QTOT', 'total water', 'kg/kg', ndim=3 )
443  call hist_reg( ad_hist_id(i_qhyd) , 'QHYD', 'total hydrometeors', 'kg/kg', ndim=3 )
444  call hist_reg( ad_hist_id(i_qliq) , 'QLIQ', 'total liquid water', 'kg/kg', ndim=3 )
445  call hist_reg( ad_hist_id(i_qice) , 'QICE', 'total ice water', 'kg/kg', ndim=3 )
446 
447  call hist_reg( ad_hist_id(i_lwp) , 'LWP', 'liquid water path', 'g/m2', ndim=2 )
448  call hist_reg( ad_hist_id(i_iwp) , 'IWP', 'ice water path', 'g/m2', ndim=2 )
449  call hist_reg( ad_hist_id(i_pw ) , 'PW', 'precipitable water', 'g/m2', ndim=2 )
450 
451  call hist_reg( ad_hist_id(i_rtot) , 'RTOT', 'Total gas constant', 'J/kg/K', ndim=3 )
452  call hist_reg( ad_hist_id(i_cptot) , 'CPTOT', 'Total heat capacity', 'J/kg/K', ndim=3 )
453  call hist_reg( ad_hist_id(i_pres) , 'PRES', 'pressure', 'Pa', ndim=3 )
454  call hist_reg( ad_hist_id(i_temp) , 'T', 'temperature', 'K', ndim=3 )
455 
456  call hist_reg( ad_hist_id(i_potl) , 'LWPT', 'liq. potential temp.', 'K', ndim=3 )
457  call hist_reg( ad_hist_id(i_rha) , 'RHA', 'relative humidity(liq+ice)', '%', ndim=3 )
458  call hist_reg( ad_hist_id(i_rhl) , 'RH', 'relative humidity(liq)', '%', ndim=3 )
459  call hist_reg( ad_hist_id(i_rhi) , 'RHI', 'relative humidity(ice)', '%', ndim=3 )
460 
461  call hist_reg( ad_hist_id(i_vor) , 'VOR', 'vertical vorticity', '1/s', ndim=3 )
462  call hist_reg( ad_hist_id(i_div) , 'DIV', 'divergence', '1/s', ndim=3 )
463  call hist_reg( ad_hist_id(i_hdiv) , 'HDIV', 'horizontal divergence', '1/s', ndim=3 )
464  call hist_reg( ad_hist_id(i_uabs) , 'Uabs', 'absolute velocity', 'm/s', ndim=3 )
465 
466  call hist_reg( ad_hist_id(i_n2) , 'N2', 'squared Brunt-Vaisala frequency','1/s2', ndim=3 )
467 
468  call hist_reg( ad_hist_id(i_cape) , 'CAPE', 'convection avail. pot. energy', 'm2/s2', ndim=2 )
469  call hist_reg( ad_hist_id(i_cin) , 'CIN', 'convection inhibition', 'm2/s2', ndim=2 )
470  call hist_reg( ad_hist_id(i_lcl) , 'LCL', 'lifted condensation level', 'm', ndim=2 )
471  call hist_reg( ad_hist_id(i_lfc) , 'LFC', 'level of free convection', 'm', ndim=2 )
472  call hist_reg( ad_hist_id(i_lnb) , 'LNB', 'level of neutral buoyancy', 'm', ndim=2 )
473 
474  call hist_reg( ad_hist_id(i_pblh) , 'PBLH', 'PBL height', 'm', ndim=2 )
475  call hist_reg( ad_hist_id(i_mse) , 'MSE', 'moist static energy', 'm2/s2', ndim=3 )
476 
477  call hist_reg( ad_hist_id(i_dens_mean), 'DENS_MEAN', 'horiz. mean of density', 'kg/m3', ndim=1 )
478  call hist_reg( ad_hist_id(i_w_mean) , 'W_MEAN', 'horiz. mean of w', 'm/s', ndim=1 )
479  call hist_reg( ad_hist_id(i_u_mean) , 'U_MEAN', 'horiz. mean of u', 'm/s', ndim=1 )
480  call hist_reg( ad_hist_id(i_v_mean) , 'V_MEAN', 'horiz. mean of v', 'm/s', ndim=1 )
481  call hist_reg( ad_hist_id(i_pott_mean), 'PT_MEAN', 'horiz. mean of pot.', 'K', ndim=1 )
482  call hist_reg( ad_hist_id(i_t_mean) , 'T_MEAN', 'horiz. mean of t', 'K', ndim=1 )
483  call hist_reg( ad_hist_id(i_qv_mean) , 'QV_MEAN', 'horiz. mean of QV', '1', ndim=1 )
484  call hist_reg( ad_hist_id(i_qhyd_mean), 'QHYD_MEAN', 'horiz. mean of QHYD', '1', ndim=1 )
485  call hist_reg( ad_hist_id(i_qliq_mean), 'QLIQ_MEAN', 'horiz. mean of QLIQ', '1', ndim=1 )
486  call hist_reg( ad_hist_id(i_qice_mean), 'QICE_MEAN', 'horiz. mean of QICE', '1', ndim=1 )
487 
488  call hist_reg( ad_hist_id(i_dens_prim), 'DENS_PRIM', 'horiz. deviation of density', 'kg/m3', ndim=3 )
489  call hist_reg( ad_hist_id(i_w_prim ), 'W_PRIM', 'horiz. deviation of w', 'm/s', ndim=3 )
490  call hist_reg( ad_hist_id(i_u_prim ), 'U_PRIM', 'horiz. deviation of u', 'm/s', ndim=3 )
491  call hist_reg( ad_hist_id(i_v_prim ), 'V_PRIM', 'horiz. deviation of v', 'm/s', ndim=3 )
492  call hist_reg( ad_hist_id(i_pott_prim), 'PT_PRIM', 'horiz. deviation of pot. temp.', 'K', ndim=3 )
493  call hist_reg( ad_hist_id(i_w_prim2 ), 'W_PRIM2', 'variance of w', 'm2/s2', ndim=3 )
494  call hist_reg( ad_hist_id(i_pt_w_prim), 'PT_W_PRIM', 'resolved scale heat flux', 'W/s', ndim=3 )
495  call hist_reg( ad_hist_id(i_w_prim3 ), 'W_PRIM3', 'skewness of w', 'm3/s3', ndim=3 )
496  call hist_reg( ad_hist_id(i_tke_rs ), 'TKE_RS', 'resolved scale TKE', 'm2/s2', ndim=3 )
497 
498  call hist_reg( ad_hist_id(i_engt) , 'ENGT', 'total energy', 'J/m3', ndim=3 )
499  call hist_reg( ad_hist_id(i_engp) , 'ENGP', 'potential energy', 'J/m3', ndim=3 )
500  call hist_reg( ad_hist_id(i_engk) , 'ENGK', 'kinetic energy', 'J/m3', ndim=3 )
501  call hist_reg( ad_hist_id(i_engi) , 'ENGI', 'internal energy', 'J/m3', ndim=3 )
502 
503  !-----< monitor output setup >-----
504 
505  call monit_reg( ad_monit_id(i_qdry) , 'QDRY', 'dry air mass', 'kg', ndim=3, isflux=.false. )
506  call monit_reg( ad_monit_id(i_qtot) , 'QTOT', 'water mass', 'kg', ndim=3, isflux=.false. )
507  call monit_reg( ad_monit_id(i_evap) , 'EVAP', 'evaporation', 'kg', ndim=2, isflux=.true. )
508  call monit_reg( ad_monit_id(i_prcp) , 'PRCP', 'precipitation', 'kg', ndim=2, isflux=.true. )
509 
510  call monit_reg( ad_monit_id(i_engt) , 'ENGT', 'total energy', 'J', ndim=3, isflux=.false. )
511  call monit_reg( ad_monit_id(i_engp) , 'ENGP', 'potential energy', 'J', ndim=3, isflux=.false. )
512  call monit_reg( ad_monit_id(i_engk) , 'ENGK', 'kinetic energy', 'J', ndim=3, isflux=.false. )
513  call monit_reg( ad_monit_id(i_engi) , 'ENGI', 'internal energy', 'J', ndim=3, isflux=.false. )
514 
515  call monit_reg( ad_monit_id(i_engflxt) , 'ENGFLXT', 'total energy flux', 'J', ndim=2, isflux=.true. )
516 
517  call monit_reg( ad_monit_id(i_engsfc_sh) , 'ENGSFC_SH', 'SFC specific heat flux', 'J', ndim=2, isflux=.true. )
518  call monit_reg( ad_monit_id(i_engsfc_lh) , 'ENGSFC_LH', 'SFC latent heat flux', 'J', ndim=2, isflux=.true. )
519  call monit_reg( ad_monit_id(i_engsfc_rd) , 'ENGSFC_RD', 'SFC net radiation flux', 'J', ndim=2, isflux=.true. )
520  call monit_reg( ad_monit_id(i_engtoa_rd) , 'ENGTOA_RD', 'TOA net radiation flux', 'J', ndim=2, isflux=.true. )
521 
522  call monit_reg( ad_monit_id(i_engsfc_lw_up), 'ENGSFC_LW_up', 'SFC LW upward flux', 'J', ndim=2, isflux=.true. )
523  call monit_reg( ad_monit_id(i_engsfc_lw_dn), 'ENGSFC_LW_dn', 'SFC LW downward flux', 'J', ndim=2, isflux=.true. )
524  call monit_reg( ad_monit_id(i_engsfc_sw_up), 'ENGSFC_SW_up', 'SFC SW upward flux', 'J', ndim=2, isflux=.true. )
525  call monit_reg( ad_monit_id(i_engsfc_sw_dn), 'ENGSFC_SW_dn', 'SFC SW downward flux', 'J', ndim=2, isflux=.true. )
526 
527  call monit_reg( ad_monit_id(i_engtoa_lw_up), 'ENGTOA_LW_up', 'TOA LW upward flux', 'J', ndim=2, isflux=.true. )
528  call monit_reg( ad_monit_id(i_engtoa_lw_dn), 'ENGTOA_LW_dn', 'TOA LW downward flux', 'J', ndim=2, isflux=.true. )
529  call monit_reg( ad_monit_id(i_engtoa_sw_up), 'ENGTOA_SW_up', 'TOA SW upward flux', 'J', ndim=2, isflux=.true. )
530  call monit_reg( ad_monit_id(i_engtoa_sw_dn), 'ENGTOA_SW_dn', 'TOA SW downward flux', 'J', ndim=2, isflux=.true. )
531 
532  if ( ad_hist_id(i_qdry) > 0 &
533  .OR. ad_monit_id(i_qdry) > 0 ) then
534  ad_prep_sw(i_qdry) = 1
535  endif
536  if ( ad_hist_id(i_qtot) > 0 &
537  .OR. ad_monit_id(i_qtot) > 0 ) then
538  ad_prep_sw(i_qdry) = 1
539  ad_prep_sw(i_qtot) = 1
540  endif
541  if ( ad_hist_id(i_qhyd) > 0 ) then
542  ad_prep_sw(i_qhyd) = 1
543  endif
544  if ( ad_hist_id(i_qliq) > 0 ) then
545  ad_prep_sw(i_qliq) = 1
546  endif
547  if ( ad_hist_id(i_qice) > 0 ) then
548  ad_prep_sw(i_qice) = 1
549  endif
550 
551  if ( ad_hist_id(i_lwp) > 0 ) then
552  ad_prep_sw(i_qliq) = 1
553  ad_prep_sw(i_lwp) = 1
554  endif
555  if ( ad_hist_id(i_iwp) > 0 ) then
556  ad_prep_sw(i_qice) = 1
557  ad_prep_sw(i_iwp) = 1
558  endif
559  if ( ad_hist_id(i_pw) > 0 ) then
560  ad_prep_sw(i_pw) = 1
561  endif
562 
563  if ( ad_hist_id(i_rtot) > 0 ) then
564  ad_prep_sw(i_qdry) = 1
565  ad_prep_sw(i_rtot) = 1
566  endif
567  if ( ad_hist_id(i_cptot) > 0 ) then
568  ad_prep_sw(i_qdry) = 1
569  ad_prep_sw(i_cptot) = 1
570  endif
571 
572  if ( ad_hist_id(i_potl) > 0 ) then
573  ad_prep_sw(i_qdry) = 1
574  ad_prep_sw(i_rtot) = 1
575  ad_prep_sw(i_cptot) = 1
576  ad_prep_sw(i_potl) = 1
577  endif
578  if ( ad_hist_id(i_rha) > 0 &
579  .OR. ad_hist_id(i_rhl) > 0 &
580  .OR. ad_hist_id(i_rhi) > 0 ) then
581  ad_prep_sw(i_qdry) = 1
582  ad_prep_sw(i_rtot) = 1
583  ad_prep_sw(i_cptot) = 1
584  ad_prep_sw(i_qsat) = 1
585  endif
586 
587 
588  if ( ad_hist_id(i_vor) > 0 ) then
589  ad_prep_sw(i_vor) = 1
590  endif
591 
592  if ( ad_prep_sw(i_div) > 0 ) then
593  ad_prep_sw(i_hdiv) = 1
594  endif
595 
596  if ( ad_hist_id(i_uabs) > 0 ) then
597  ad_prep_sw(i_uabs) = 1
598  endif
599 
600  if ( ad_hist_id(i_cape) > 0 &
601  .OR. ad_hist_id(i_cin) > 0 &
602  .OR. ad_hist_id(i_lcl) > 0 &
603  .OR. ad_hist_id(i_lfc) > 0 &
604  .OR. ad_hist_id(i_lnb) > 0 ) then
605  ad_prep_sw(i_cape) = 1
606  ad_prep_sw(i_cin) = 1
607  ad_prep_sw(i_lcl) = 1
608  ad_prep_sw(i_lfc) = 1
609  ad_prep_sw(i_lnb) = 1
610  endif
611 
612  if ( ad_hist_id(i_pblh) > 0 ) then
613  ad_prep_sw(i_pblh) = 1
614  endif
615 
616  if ( ad_hist_id(i_mse) > 0 ) then
617  ad_prep_sw(i_cptot) = 1
618  ad_prep_sw(i_mse) = 1
619  endif
620 
621  if ( ad_hist_id(i_dens_prim) > 0 ) then
622  ad_prep_sw(i_dens_prim) = 1
623  ad_prep_sw(i_dens_mean) = 1
624  endif
625 
626  if ( ad_hist_id(i_w_prim) > 0 ) then
627  ad_prep_sw(i_w_prim) = 1
628  ad_prep_sw(i_dens_mean) = 1
629  ad_prep_sw(i_w_mean) = 1
630  endif
631 
632  if ( ad_hist_id(i_u_prim) > 0 ) then
633  ad_prep_sw(i_u_prim) = 1
634  ad_prep_sw(i_dens_mean) = 1
635  ad_prep_sw(i_u_mean) = 1
636  endif
637 
638  if ( ad_hist_id(i_v_prim) > 0 ) then
639  ad_prep_sw(i_v_prim) = 1
640  ad_prep_sw(i_dens_mean) = 1
641  ad_prep_sw(i_v_mean) = 1
642  endif
643 
644  if ( ad_hist_id(i_pott_prim) > 0 ) then
645  ad_prep_sw(i_pott_prim) = 1
646  ad_prep_sw(i_dens_mean) = 1
647  ad_prep_sw(i_pott_mean) = 1
648  endif
649 
650  if ( ad_hist_id(i_dens_mean) > 0 ) then
651  ad_prep_sw(i_dens_mean) = 1
652  endif
653 
654  if ( ad_hist_id(i_w_mean) > 0 ) then
655  ad_prep_sw(i_w_mean) = 1
656  endif
657 
658  if ( ad_hist_id(i_u_mean) > 0 ) then
659  ad_prep_sw(i_u_mean) = 1
660  endif
661 
662  if ( ad_hist_id(i_v_mean) > 0 ) then
663  ad_prep_sw(i_v_mean) = 1
664  endif
665 
666  if ( ad_hist_id(i_pott_mean) > 0 ) then
667  ad_prep_sw(i_pott_mean) = 1
668  end if
669 
670  if ( ad_hist_id(i_t_mean) > 0 ) then
671  ad_prep_sw(i_t_mean) = 1
672  end if
673 
674  if ( ad_hist_id(i_qv_mean) > 0 ) then
675  ad_prep_sw(i_qv_mean) = 1
676  end if
677 
678  if ( ad_hist_id(i_qhyd_mean) > 0 ) then
679  ad_prep_sw(i_qhyd) = 1
680  ad_prep_sw(i_qhyd_mean) = 1
681  end if
682 
683  if ( ad_hist_id(i_qliq_mean) > 0 ) then
684  ad_prep_sw(i_qliq) = 1
685  ad_prep_sw(i_qliq_mean) = 1
686  end if
687 
688  if ( ad_hist_id(i_qice_mean) > 0 ) then
689  ad_prep_sw(i_qice) = 1
690  ad_prep_sw(i_qice_mean) = 1
691  end if
692 
693  if ( ad_hist_id(i_w_prim2) > 0 ) then
694  ad_prep_sw(i_w_prim) = 1
695  ad_prep_sw(i_w_prim2) = 1
696  ad_prep_sw(i_dens_mean) = 1
697  ad_prep_sw(i_w_mean) = 1
698  endif
699 
700  if ( ad_hist_id(i_pt_w_prim) > 0 ) then
701  ad_prep_sw(i_w_prim) = 1
702  ad_prep_sw(i_pott_prim) = 1
703  ad_prep_sw(i_pt_w_prim) = 1
704  ad_prep_sw(i_dens_mean) = 1
705  ad_prep_sw(i_w_mean) = 1
706  ad_prep_sw(i_pott_mean) = 1
707  endif
708 
709  if ( ad_hist_id(i_w_prim3) > 0 ) then
710  ad_prep_sw(i_w_prim) = 1
711  ad_prep_sw(i_w_prim3) = 1
712  ad_prep_sw(i_dens_mean) = 1
713  ad_prep_sw(i_w_mean) = 1
714  endif
715 
716  if ( ad_hist_id(i_tke_rs) > 0 ) then
717  ad_prep_sw(i_w_prim) = 1
718  ad_prep_sw(i_u_prim) = 1
719  ad_prep_sw(i_v_prim) = 1
720  ad_prep_sw(i_tke_rs) = 1
721  ad_prep_sw(i_dens_mean) = 1
722  ad_prep_sw(i_w_mean) = 1
723  ad_prep_sw(i_u_mean) = 1
724  ad_prep_sw(i_v_mean) = 1
725  endif
726 
727  if ( ad_hist_id(i_engp) > 0 &
728  .OR. ad_monit_id(i_engp) > 0 ) then
729  ad_prep_sw(i_engp) = 1
730  endif
731  if ( ad_hist_id(i_engk) > 0 &
732  .OR. ad_monit_id(i_engk) > 0 ) then
733  ad_prep_sw(i_engk) = 1
734  endif
735  if ( ad_hist_id(i_engi) > 0 &
736  .OR. ad_monit_id(i_engi) > 0 ) then
737  ad_prep_sw(i_qdry) = 1
738  ad_prep_sw(i_rtot) = 1
739  ad_prep_sw(i_cptot) = 1
740  ad_prep_sw(i_engi) = 1
741  endif
742  if ( ad_hist_id(i_engt) > 0 &
743  .OR. ad_monit_id(i_engt) > 0 ) then
744  ad_prep_sw(i_engp) = 1
745  ad_prep_sw(i_engk) = 1
746  ad_prep_sw(i_qdry) = 1
747  ad_prep_sw(i_rtot) = 1
748  ad_prep_sw(i_cptot) = 1
749  ad_prep_sw(i_engi) = 1
750  ad_prep_sw(i_engt) = 1
751  endif
752 
753  return
module ATMOS admin
real(rp), dimension(:,:,:), allocatable, target, public momz
module Atmosphere / Physics Cumulus
subroutine, public atmos_phy_ch_vars_setup
Setup.
subroutine, public prc_mpistop
Abort MPI.
real(rp), dimension(:,:,:), allocatable, target, public rhot
real(rp), dimension(:,:,:), allocatable, public momy_tp
module Atmosphere / Physics Cloud Microphysics
module Atmosphere / Dynamics
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
real(rp), dimension(:,:,:), allocatable, target, public momx
real(rp), dimension(:,:,:), allocatable, public rhot_tp
real(rp), dimension(:,:,:), allocatable, target, public dens
subroutine, public atmos_phy_sf_vars_setup
Setup.
module Atmosphere / Physics Radiation
module ATMOSPHERIC Surface Variables
subroutine, public atmos_phy_cp_vars_setup
Setup.
real(rp), dimension(:,:,:), pointer, public momx_av
subroutine, public monit_reg(itemid, item, desc, unit, ndim, isflux)
Search existing item, or matching check between requested and registered item.
module MONITOR
real(rp), dimension(:,:,:,:), allocatable, public rhoq_tp
subroutine, public atmos_phy_tb_vars_setup
Setup.
module PROCESS
subroutine, public atmos_phy_rd_vars_setup
Setup.
module Atmosphere / Physics Turbulence
real(rp), dimension(:,:,:), pointer, public dens_av
subroutine, public atmos_dyn_vars_setup
Setup.
subroutine, public atmos_phy_ae_vars_setup
Setup.
real(rp), dimension(:,:,:), allocatable, public momx_tp
real(rp), dimension(:,:,:), allocatable, target, public momy
module Atmosphere / Physics Chemistry
real(rp), dimension(:,:,:), allocatable, public momz_tp
subroutine, public atmos_phy_mp_vars_setup
Setup.
real(rp), dimension(:,:,:), allocatable, public n2
module HISTORY
real(rp), dimension(:,:,:), pointer, public momz_av
real(rp), dimension(:,:,:), pointer, public rhot_av
subroutine, public hist_reg(itemid, item, desc, unit, ndim, xdim, ydim, zdim)
Register/Append variable to history file.
real(rp), dimension(:,:,:), pointer, public momy_av
module ATMOSPHERE / Physics Aerosol Microphysics
logical, public atmos_use_average
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_vars_fillhalo()

subroutine, public mod_atmos_vars::atmos_vars_fillhalo ( logical, intent(in), optional  FILL_BND)

HALO Communication.

Definition at line 760 of file mod_atmos_vars.f90.

References dens, scale_grid_index::ieb, scale_grid_index::isb, scale_grid_index::jeb, scale_grid_index::jsb, scale_grid_index::ka, scale_grid_index::ke, scale_grid_index::ks, momx, momy, momz, scale_tracer::qa, qtrc, and rhot.

Referenced by atmos_vars_restart_read(), and atmos_vars_restart_write().

760  use scale_comm, only: &
761  comm_vars8, &
762  comm_wait
763  implicit none
764 
765  logical, intent(in), optional :: FILL_BND
766 
767  logical :: FILL_BND_
768  integer :: i, j, iq
769  !---------------------------------------------------------------------------
770 
771  fill_bnd_ = .false.
772  if ( present(fill_bnd) ) fill_bnd_ = fill_bnd
773 
774  !$omp parallel do private(i,j) OMP_SCHEDULE_ collapse(2)
775  do j = jsb, jeb
776  do i = isb, ieb
777  dens( 1:ks-1,i,j) = dens(ks,i,j)
778  momz( 1:ks-1,i,j) = momz(ks,i,j)
779  momx( 1:ks-1,i,j) = momx(ks,i,j)
780  momy( 1:ks-1,i,j) = momy(ks,i,j)
781  rhot( 1:ks-1,i,j) = rhot(ks,i,j)
782  dens(ke+1:ka, i,j) = dens(ke,i,j)
783  momz(ke+1:ka, i,j) = momz(ke,i,j)
784  momx(ke+1:ka, i,j) = momx(ke,i,j)
785  momy(ke+1:ka, i,j) = momy(ke,i,j)
786  rhot(ke+1:ka, i,j) = rhot(ke,i,j)
787  enddo
788  enddo
789 
790  !$omp parallel do private(i,j,iq) OMP_SCHEDULE_ collapse(3)
791  do iq = 1, qa
792  do j = jsb, jeb
793  do i = isb, ieb
794  qtrc( 1:ks-1,i,j,iq) = qtrc(ks,i,j,iq)
795  qtrc(ke+1:ka, i,j,iq) = qtrc(ke,i,j,iq)
796  enddo
797  enddo
798  enddo
799 
800  call comm_vars8( dens(:,:,:), 1 )
801  call comm_vars8( momz(:,:,:), 2 )
802  call comm_vars8( momx(:,:,:), 3 )
803  call comm_vars8( momy(:,:,:), 4 )
804  call comm_vars8( rhot(:,:,:), 5 )
805  call comm_wait ( dens(:,:,:), 1, fill_bnd_ )
806  call comm_wait ( momz(:,:,:), 2, fill_bnd_ )
807  call comm_wait ( momx(:,:,:), 3, fill_bnd_ )
808  call comm_wait ( momy(:,:,:), 4, fill_bnd_ )
809  call comm_wait ( rhot(:,:,:), 5, fill_bnd_ )
810 
811  do iq = 1, qa
812  call comm_vars8( qtrc(:,:,:,iq), iq )
813  enddo
814  do iq = 1, qa
815  call comm_wait ( qtrc(:,:,:,iq), iq, fill_bnd_ )
816  enddo
817 
818  return
real(rp), dimension(:,:,:), allocatable, target, public momz
real(rp), dimension(:,:,:), allocatable, target, public rhot
real(rp), dimension(:,:,:), allocatable, target, public momx
real(rp), dimension(:,:,:), allocatable, target, public dens
module COMMUNICATION
Definition: scale_comm.F90:23
real(rp), dimension(:,:,:), allocatable, target, public momy
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
Here is the caller graph for this function:

◆ atmos_vars_restart_open()

subroutine, public mod_atmos_vars::atmos_vars_restart_open ( )

Open restart file for reading atmospheric variables.

Definition at line 824 of file mod_atmos_vars.f90.

References mod_atmos_dyn_vars::atmos_dyn_vars_restart_open(), mod_atmos_phy_ae_vars::atmos_phy_ae_vars_restart_open(), mod_atmos_phy_ch_vars::atmos_phy_ch_vars_restart_open(), mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_open(), mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_open(), mod_atmos_phy_rd_vars::atmos_phy_rd_vars_restart_open(), mod_atmos_phy_sf_vars::atmos_phy_sf_vars_restart_open(), mod_atmos_phy_tb_vars::atmos_phy_tb_vars_restart_open(), atmos_restart_in_basename, atmos_restart_in_postfix_timelabel, mod_atmos_admin::atmos_sw_dyn, mod_atmos_admin::atmos_sw_phy_ae, mod_atmos_admin::atmos_sw_phy_ch, mod_atmos_admin::atmos_sw_phy_cp, mod_atmos_admin::atmos_sw_phy_mp, mod_atmos_admin::atmos_sw_phy_rd, mod_atmos_admin::atmos_sw_phy_sf, mod_atmos_admin::atmos_sw_phy_tb, mod_atmos_admin::atmos_use_average, scale_const::const_grav, dens, dens_av, scale_fileio::fileio_open(), scale_stdio::io_fid_log, scale_stdio::io_l, momx, momx_av, momy, momy_av, momz, momz_av, scale_process::prc_mpistop(), qtrc, qtrc_av, rhot, rhot_av, and scale_time::time_gettimelabel().

Referenced by mod_admin_restart::admin_restart_read().

824  use scale_process, only: &
826  use scale_const, only: &
827  grav => const_grav
828  use scale_time, only: &
830  use scale_fileio, only: &
831  fileio_open, &
832  fileio_check_coordinates
833  use scale_atmos_thermodyn, only: &
834  thermodyn_qd => atmos_thermodyn_qd, &
835  thermodyn_temp_pres => atmos_thermodyn_temp_pres
836  use mod_atmos_admin, only: &
838  atmos_sw_dyn, &
839  atmos_sw_phy_mp, &
840  atmos_sw_phy_ae, &
841  atmos_sw_phy_ch, &
842  atmos_sw_phy_rd, &
843  atmos_sw_phy_sf, &
844  atmos_sw_phy_tb, &
846  use mod_atmos_dyn_vars, only: &
848  use mod_atmos_phy_mp_vars, only: &
850  use mod_atmos_phy_ae_vars, only: &
852  use mod_atmos_phy_ch_vars, only: &
854  use mod_atmos_phy_rd_vars, only: &
856  use mod_atmos_phy_sf_vars, only: &
858  use mod_atmos_phy_tb_vars, only: &
860  use mod_atmos_phy_cp_vars, only: &
862  implicit none
863 
864  character(len=19) :: timelabel
865  character(len=H_LONG) :: basename
866  !---------------------------------------------------------------------------
867 
868  if( io_l ) write(io_fid_log,*)
869  if( io_l ) write(io_fid_log,*) '*** Open restart file (ATMOS) ***'
870 
871  if ( atmos_restart_in_basename /= '' ) then
872 
873  if ( atmos_restart_in_postfix_timelabel ) then
874  call time_gettimelabel( timelabel )
875  basename = trim(atmos_restart_in_basename)//'_'//trim(timelabel)
876  else
877  basename = trim(atmos_restart_in_basename)
878  endif
879 
880  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
881 
882  call fileio_open( restart_fid, basename )
883 
884  if ( atmos_restart_in_check_coordinates ) then
885  call fileio_check_coordinates( restart_fid, atmos=.true. )
886  end if
887 
888  else
889  write(*,*) '*** restart file for atmosphere is not specified. STOP!'
890  call prc_mpistop
891  endif
892 
893  if ( atmos_use_average ) then
894  dens_av(:,:,:) = dens(:,:,:)
895  momz_av(:,:,:) = momz(:,:,:)
896  momx_av(:,:,:) = momx(:,:,:)
897  momy_av(:,:,:) = momy(:,:,:)
898  rhot_av(:,:,:) = rhot(:,:,:)
899  qtrc_av(:,:,:,:) = qtrc(:,:,:,:)
900  endif
901 
910 
911  return
module ATMOS admin
subroutine, public atmos_phy_sf_vars_restart_open
Open restart file for read.
logical, public atmos_sw_phy_cp
real(rp), dimension(:,:,:), allocatable, target, public momz
module Atmosphere / Physics Cumulus
subroutine, public atmos_dyn_vars_restart_open
Open restart file for read.
subroutine, public prc_mpistop
Abort MPI.
logical, public atmos_sw_phy_rd
real(rp), dimension(:,:,:), allocatable, target, public rhot
subroutine, public atmos_phy_cp_vars_restart_open
Open restart file for read.
module Atmosphere / Physics Cloud Microphysics
module Atmosphere / Dynamics
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
real(rp), dimension(:,:,:), allocatable, target, public momx
logical, public atmos_sw_phy_ae
real(rp), dimension(:,:,:), allocatable, target, public dens
module FILE I/O (netcdf)
module Atmosphere / Physics Radiation
subroutine, public atmos_phy_rd_vars_restart_open
Open restart file for read.
module ATMOSPHERIC Surface Variables
real(rp), dimension(:,:,:), pointer, public momx_av
logical, public atmos_sw_phy_tb
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:90
logical, public atmos_sw_dyn
real(rp), public const_grav
standard acceleration of gravity [m/s2]
Definition: scale_const.F90:48
module TIME
Definition: scale_time.F90:15
module PROCESS
logical, public atmos_sw_phy_sf
logical, public atmos_sw_phy_ch
module Atmosphere / Physics Turbulence
real(rp), dimension(:,:,:), pointer, public dens_av
module CONSTANT
Definition: scale_const.F90:14
logical, public atmos_sw_phy_mp
real(rp), dimension(:,:,:), allocatable, target, public momy
subroutine, public atmos_phy_mp_vars_restart_open
Open restart file for read.
module Atmosphere / Physics Chemistry
module ATMOSPHERE / Thermodynamics
subroutine, public fileio_open(fid, basename)
open a netCDF file for read
real(rp), dimension(:,:,:), pointer, public momz_av
real(rp), dimension(:,:,:), pointer, public rhot_av
subroutine, public atmos_phy_ch_vars_restart_open
Open restart file for read.
real(rp), dimension(:,:,:), pointer, public momy_av
module ATMOSPHERE / Physics Aerosol Microphysics
subroutine, public atmos_phy_tb_vars_restart_open
Open restart file for read.
subroutine, public atmos_phy_ae_vars_restart_open
Open restart file for read.
logical, public atmos_use_average
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_vars_restart_read()

subroutine, public mod_atmos_vars::atmos_vars_restart_read ( )

Read restart of atmospheric variables.

Definition at line 917 of file mod_atmos_vars.f90.

References mod_atmos_dyn_vars::atmos_dyn_vars_restart_read(), mod_atmos_phy_ae_vars::atmos_phy_ae_vars_restart_read(), mod_atmos_phy_ch_vars::atmos_phy_ch_vars_restart_read(), mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_read(), mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_read(), mod_atmos_phy_rd_vars::atmos_phy_rd_vars_restart_read(), mod_atmos_phy_sf_vars::atmos_phy_sf_vars_restart_read(), mod_atmos_phy_tb_vars::atmos_phy_tb_vars_restart_read(), mod_atmos_admin::atmos_sw_dyn, mod_atmos_admin::atmos_sw_phy_ae, mod_atmos_admin::atmos_sw_phy_ch, mod_atmos_admin::atmos_sw_phy_cp, mod_atmos_admin::atmos_sw_phy_mp, mod_atmos_admin::atmos_sw_phy_rd, mod_atmos_admin::atmos_sw_phy_sf, mod_atmos_admin::atmos_sw_phy_tb, mod_atmos_admin::atmos_use_average, atmos_vars_fillhalo(), atmos_vars_total(), dens, dens_av, scale_fileio::fileio_flush(), scale_grid_index::ia, scale_stdio::io_aggregate, scale_stdio::io_fid_log, scale_stdio::io_l, scale_grid_index::ja, scale_grid_index::ka, scale_grid_index::ke, scale_grid_index::ks, momx, momx_av, momy, momy_av, momz, momz_av, scale_process::prc_mpistop(), scale_tracer::qa, qtrc, qtrc_av, rhot, rhot_av, and scale_tracer::tracer_name.

Referenced by mod_admin_restart::admin_restart_read(), and mod_rm_driver::resume_state().

917  use scale_process, only: &
919  use scale_fileio, only: &
920  fileio_read, &
922  use scale_atmos_thermodyn, only: &
923  thermodyn_qd => atmos_thermodyn_qd, &
924  thermodyn_temp_pres => atmos_thermodyn_temp_pres
925  use mod_atmos_admin, only: &
927  atmos_sw_dyn, &
928  atmos_sw_phy_mp, &
929  atmos_sw_phy_ae, &
930  atmos_sw_phy_ch, &
931  atmos_sw_phy_rd, &
932  atmos_sw_phy_sf, &
933  atmos_sw_phy_tb, &
935  use mod_atmos_dyn_vars, only: &
937  use mod_atmos_phy_mp_vars, only: &
939  use mod_atmos_phy_ae_vars, only: &
941  use mod_atmos_phy_ch_vars, only: &
943  use mod_atmos_phy_rd_vars, only: &
945  use mod_atmos_phy_sf_vars, only: &
947  use mod_atmos_phy_tb_vars, only: &
949  use mod_atmos_phy_cp_vars, only: &
951  implicit none
952 
953  integer :: i, j, iq
954  !---------------------------------------------------------------------------
955 
956  if ( restart_fid /= -1 ) then
957  if( io_l ) write(io_fid_log,*)
958  if( io_l ) write(io_fid_log,*) '*** Read from restart file (ATMOS) ***'
959 
960  call fileio_read( dens(:,:,:), & ! [OUT]
961  restart_fid, var_name(1), 'ZXY', step=1 ) ! [IN]
962  call fileio_read( momz(:,:,:), & ! [OUT]
963  restart_fid, var_name(2), 'ZXY', step=1 ) ! [IN]
964  call fileio_read( momx(:,:,:), & ! [OUT]
965  restart_fid, var_name(3), 'ZXY', step=1 ) ! [IN]
966  call fileio_read( momy(:,:,:), & ! [OUT]
967  restart_fid, var_name(4), 'ZXY', step=1 ) ! [IN]
968  call fileio_read( rhot(:,:,:), & ! [OUT]
969  restart_fid, var_name(5), 'ZXY', step=1 ) ! [IN]
970 
971  do iq = 1, qa
972  call fileio_read( qtrc(:,:,:,iq), & ! [OUT]
973  restart_fid, tracer_name(iq), 'ZXY', step=1 ) ! [IN]
974  enddo
975 
976  if ( io_aggregate ) then
977  call fileio_flush( restart_fid ) ! X/Y halos have been read from file
978 
979  ! fill k halos
980  do j = 1, ja
981  do i = 1, ia
982  dens( 1:ks-1,i,j) = dens(ks,i,j)
983  momz( 1:ks-1,i,j) = momz(ks,i,j)
984  momx( 1:ks-1,i,j) = momx(ks,i,j)
985  momy( 1:ks-1,i,j) = momy(ks,i,j)
986  rhot( 1:ks-1,i,j) = rhot(ks,i,j)
987  dens(ke+1:ka, i,j) = dens(ke,i,j)
988  momz(ke+1:ka, i,j) = momz(ke,i,j)
989  momx(ke+1:ka, i,j) = momx(ke,i,j)
990  momy(ke+1:ka, i,j) = momy(ke,i,j)
991  rhot(ke+1:ka, i,j) = rhot(ke,i,j)
992  enddo
993  enddo
994  else
995  call atmos_vars_fillhalo
996  end if
997 
998  call atmos_vars_total
999  else
1000  write(*,*) '*** invalid restart file ID for atmosphere. STOP!'
1001  call prc_mpistop
1002  endif
1003 
1004  if ( atmos_use_average ) then
1005  dens_av(:,:,:) = dens(:,:,:)
1006  momz_av(:,:,:) = momz(:,:,:)
1007  momx_av(:,:,:) = momx(:,:,:)
1008  momy_av(:,:,:) = momy(:,:,:)
1009  rhot_av(:,:,:) = rhot(:,:,:)
1010  qtrc_av(:,:,:,:) = qtrc(:,:,:,:)
1011  endif
1012 
1021 
1022  return
module ATMOS admin
logical, public atmos_sw_phy_cp
real(rp), dimension(:,:,:), allocatable, target, public momz
module Atmosphere / Physics Cumulus
subroutine, public atmos_phy_sf_vars_restart_read
Read restart.
subroutine, public atmos_phy_tb_vars_restart_read
Read restart.
subroutine, public prc_mpistop
Abort MPI.
logical, public atmos_sw_phy_rd
real(rp), dimension(:,:,:), allocatable, target, public rhot
module Atmosphere / Physics Cloud Microphysics
module Atmosphere / Dynamics
subroutine, public fileio_flush(fid)
Flush all pending requests to a netCDF file (PnetCDF only)
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
real(rp), dimension(:,:,:), allocatable, target, public momx
logical, public atmos_sw_phy_ae
real(rp), dimension(:,:,:), allocatable, target, public dens
module FILE I/O (netcdf)
module Atmosphere / Physics Radiation
module ATMOSPHERIC Surface Variables
real(rp), dimension(:,:,:), pointer, public momx_av
logical, public atmos_sw_phy_tb
logical, public atmos_sw_dyn
subroutine, public atmos_dyn_vars_restart_read
Read restart.
module PROCESS
logical, public atmos_sw_phy_sf
logical, public atmos_sw_phy_ch
module Atmosphere / Physics Turbulence
real(rp), dimension(:,:,:), pointer, public dens_av
logical, public atmos_sw_phy_mp
subroutine, public atmos_phy_ae_vars_restart_read
Read restart.
real(rp), dimension(:,:,:), allocatable, target, public momy
module Atmosphere / Physics Chemistry
subroutine, public atmos_phy_mp_vars_restart_read
Read restart.
module ATMOSPHERE / Thermodynamics
subroutine, public atmos_phy_rd_vars_restart_read
Read restart.
real(rp), dimension(:,:,:), pointer, public momz_av
subroutine, public atmos_phy_cp_vars_restart_read
Read restart.
real(rp), dimension(:,:,:), pointer, public rhot_av
real(rp), dimension(:,:,:), pointer, public momy_av
subroutine, public atmos_phy_ch_vars_restart_read
Read restart.
module ATMOSPHERE / Physics Aerosol Microphysics
logical, public atmos_use_average
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_vars_history_setpres()

subroutine, public mod_atmos_vars::atmos_vars_history_setpres ( )

Set pressure for history output.

Definition at line 1028 of file mod_atmos_vars.f90.

References scale_atmos_bottom::atmos_bottom_estimate(), dens_av, scale_history::hist_setpres(), phyd, pres, scale_grid_real::real_cz, scale_grid_real::real_z1, and scale_topography::topo_zsfc.

Referenced by mod_atmos_driver::atmos_driver(), mod_atmos_driver::atmos_driver_resume1(), and mod_rm_driver::resume_state().

1028  use scale_grid_real, only: &
1029  real_cz, &
1030  real_z1
1031  use scale_topography, only: &
1032  topo_zsfc
1033  use scale_atmos_bottom, only: &
1034  bottom_estimate => atmos_bottom_estimate
1035  use scale_history, only: &
1036  hist_setpres
1037  implicit none
1038 
1039  real(RP) :: SFC_DENS(IA,JA)
1040  real(RP) :: SFC_PRES(IA,JA)
1041  !---------------------------------------------------------------------------
1042 
1043  call bottom_estimate( dens_av(:,:,:), & ! [IN]
1044  pres(:,:,:), & ! [IN]
1045  real_cz(:,:,:), & ! [IN]
1046  topo_zsfc(:,:), & ! [IN]
1047  real_z1(:,:), & ! [IN]
1048  sfc_dens(:,:), & ! [OUT]
1049  sfc_pres(:,:) ) ! [OUT]
1050 
1051  call hist_setpres( phyd(:,:,:), & ! [IN]
1052  sfc_pres(:,:) ) ! [IN]
1053 
1054  return
module ATMOSPHERE / Bottom boundary treatment
real(rp), dimension(:,:,:), allocatable, public real_cz
geopotential height [m] (cell center)
real(rp), dimension(:,:), allocatable, public real_z1
Height of the lowermost grid from surface (cell center) [m].
module GRID (real space)
subroutine, public hist_setpres(PRES, SFC_PRES)
set interpolation factor for pressure coordinate
real(rp), dimension(:,:,:), pointer, public dens_av
subroutine, public atmos_bottom_estimate(DENS, PRES, CZ, Zsfc, Z1, SFC_DENS, SFC_PRES)
Calc bottom boundary of atmosphere (just above surface)
real(rp), dimension(:,:), allocatable, public topo_zsfc
absolute ground height [m]
module HISTORY
module TOPOGRAPHY
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_vars_restart_check()

subroutine, public mod_atmos_vars::atmos_vars_restart_check ( )

Check and compare between last data and sample data.

Definition at line 1060 of file mod_atmos_vars.f90.

References atmos_restart_check_basename, atmos_restart_check_criterion, dens, scale_fileio::fileio_close(), scale_fileio::fileio_flush(), scale_fileio::fileio_open(), scale_grid_index::ie, scale_stdio::io_aggregate, scale_stdio::io_fid_log, scale_stdio::io_l, scale_grid_index::is, scale_grid_index::je, scale_grid_index::js, scale_grid_index::ke, scale_grid_index::ks, momx, momy, momz, scale_process::prc_myrank, scale_prof::prof_rapend(), scale_prof::prof_rapstart(), scale_tracer::qa, qtrc, rhot, and scale_tracer::tracer_name.

Referenced by mod_rm_driver::scalerm().

1060  use scale_process, only: &
1061  prc_myrank
1062  use scale_fileio, only: &
1063  fileio_open, &
1064  fileio_read, &
1065  fileio_flush, &
1066  fileio_close
1067  implicit none
1068 
1069  real(RP) :: DENS_check(KA,IA,JA) ! Density [kg/m3]
1070  real(RP) :: MOMZ_check(KA,IA,JA) ! momentum z [kg/s/m2]
1071  real(RP) :: MOMX_check(KA,IA,JA) ! momentum x [kg/s/m2]
1072  real(RP) :: MOMY_check(KA,IA,JA) ! momentum y [kg/s/m2]
1073  real(RP) :: RHOT_check(KA,IA,JA) ! DENS * POTT [K*kg/m3]
1074  real(RP) :: QTRC_check(KA,IA,JA,QA) ! tracer mixing ratio [kg/kg]
1075 
1076  character(len=H_LONG) :: basename
1077 
1078  logical :: datacheck
1079  integer :: k, i, j, iq
1080  integer :: fid
1081  !---------------------------------------------------------------------------
1082 
1083  call prof_rapstart('Debug')
1084 
1085  write(*,*) 'Compare last Data with ', trim(atmos_restart_check_basename), 'on PE=', prc_myrank
1086  write(*,*) '*** criterion = ', atmos_restart_check_criterion
1087  datacheck = .true.
1088 
1089  basename = atmos_restart_check_basename
1090 
1091  call fileio_open( fid, basename )
1092 
1093  call fileio_read( dens_check(:,:,:), fid, 'DENS', 'ZXY', step=1 )
1094  call fileio_read( momz_check(:,:,:), fid, 'MOMZ', 'ZXY', step=1 )
1095  call fileio_read( momx_check(:,:,:), fid, 'MOMX', 'ZXY', step=1 )
1096  call fileio_read( momy_check(:,:,:), fid, 'MOMY', 'ZXY', step=1 )
1097  call fileio_read( rhot_check(:,:,:), fid, 'RHOT', 'ZXY', step=1 )
1098  do iq = 1, qa
1099  call fileio_read( qtrc_check(:,:,:,iq), fid, tracer_name(iq), 'ZXY', step=1 )
1100  end do
1101  if ( io_aggregate ) call fileio_flush( fid )
1102 
1103  call fileio_close( fid ) ! [IN]
1104 
1105  do k = ks, ke
1106  do j = js, je
1107  do i = is, ie
1108  if ( abs( dens(k,i,j)-dens_check(k,i,j) ) > atmos_restart_check_criterion ) then
1109  write(*,*) 'xxx there is the difference : ', dens(k,i,j)-dens_check(k,i,j)
1110  write(*,*) 'xxx at (PE-id,k,i,j,varname) : ', prc_myrank, k, i, j, 'DENS'
1111  datacheck = .false.
1112  endif
1113  enddo
1114  enddo
1115  enddo
1116 
1117  do k = ks, ke
1118  do j = js, je
1119  do i = is, ie
1120  if ( abs( momz(k,i,j)-momz_check(k,i,j) ) > atmos_restart_check_criterion ) then
1121  write(*,*) 'xxx there is the difference : ', momz(k,i,j)-momz_check(k,i,j)
1122  write(*,*) 'xxx at (PE-id,k,i,j,varname) : ', prc_myrank, k, i, j, 'MOMZ'
1123  datacheck = .false.
1124  endif
1125  enddo
1126  enddo
1127  enddo
1128 
1129  do k = ks, ke
1130  do j = js, je
1131  do i = is, ie
1132  if ( abs( momx(k,i,j)-momx_check(k,i,j) ) > atmos_restart_check_criterion ) then
1133  write(*,*) 'xxx there is the difference : ', momx(k,i,j)-momx_check(k,i,j)
1134  write(*,*) 'xxx at (PE-id,k,i,j,varname) : ', prc_myrank, k, i, j, 'MOMX'
1135  datacheck = .false.
1136  endif
1137  enddo
1138  enddo
1139  enddo
1140 
1141  do k = ks, ke
1142  do j = js, je
1143  do i = is, ie
1144  if ( abs( momy(k,i,j)-momy_check(k,i,j) ) > atmos_restart_check_criterion ) then
1145  write(*,*) 'xxx there is the difference : ', momy(k,i,j)-momy_check(k,i,j)
1146  write(*,*) 'xxx at (PE-id,k,i,j,varname) : ', prc_myrank, k, i, j, 'MOMY'
1147  datacheck = .false.
1148  endif
1149  enddo
1150  enddo
1151  enddo
1152 
1153  do k = ks, ke
1154  do j = js, je
1155  do i = is, ie
1156  if ( abs( rhot(k,i,j)-rhot_check(k,i,j) ) > atmos_restart_check_criterion ) then
1157  write(*,*) 'xxx there is the difference : ', rhot(k,i,j)-rhot_check(k,i,j)
1158  write(*,*) 'xxx at (PE-id,k,i,j,varname) : ', prc_myrank, k, i, j, 'RHOT'
1159  datacheck = .false.
1160  endif
1161  enddo
1162  enddo
1163  enddo
1164 
1165  do iq = 1, qa
1166  do k = ks, ke
1167  do j = js, je
1168  do i = is, ie
1169  if ( abs( qtrc(k,i,j,iq)-qtrc_check(k,i,j,iq) ) > atmos_restart_check_criterion ) then
1170  write(*,*) 'xxx there is the difference : ', qtrc(k,i,j,iq)-qtrc_check(k,i,j,iq)
1171  write(*,*) 'xxx at (PE-id,k,i,j,varname) : ', prc_myrank, k, i, j, tracer_name(iq)
1172  datacheck = .false.
1173  endif
1174  enddo
1175  enddo
1176  enddo
1177  enddo
1178 
1179  if (datacheck) then
1180  if( io_l ) write(io_fid_log,*) 'Data Check Clear.'
1181  write(*,*) 'Data Check Clear.'
1182  else
1183  if( io_l ) write(io_fid_log,*) 'Data Check Failed. See std. output.'
1184  write(*,*) 'Data Check Failed.'
1185  endif
1186 
1187  call prof_rapend('Debug')
1188 
1189  return
real(rp), dimension(:,:,:), allocatable, target, public momz
real(rp), dimension(:,:,:), allocatable, target, public rhot
subroutine, public fileio_flush(fid)
Flush all pending requests to a netCDF file (PnetCDF only)
real(rp), dimension(:,:,:), allocatable, target, public momx
real(rp), dimension(:,:,:), allocatable, target, public dens
module FILE I/O (netcdf)
module PROCESS
integer, public prc_myrank
process num in local communicator
real(rp), dimension(:,:,:), allocatable, target, public momy
subroutine, public fileio_open(fid, basename)
open a netCDF file for read
subroutine, public fileio_close(fid)
Close a netCDF file.
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_vars_history()

subroutine, public mod_atmos_vars::atmos_vars_history ( )

History output set for atmospheric variables.

Definition at line 1195 of file mod_atmos_vars.f90.

References scale_atmos_adiabat::atmos_adiabat_cape(), mod_atmos_phy_cp_vars::atmos_phy_cp_sflx_rain, mod_atmos_phy_mp_vars::atmos_phy_mp_sflx_rain, mod_atmos_phy_mp_vars::atmos_phy_mp_sflx_snow, scale_comm::comm_horizontal_mean(), scale_const::const_cpdry, scale_const::const_cvdry, scale_const::const_grav, scale_const::const_pre00, scale_const::const_rdry, scale_const::const_rvap, dens, dens_av, scale_grid::grid_rcdx, scale_grid::grid_rcdy, scale_index::i_dens, scale_index::i_momx, scale_index::i_momy, scale_index::i_momz, scale_atmos_hydrometeor::i_qc, scale_atmos_hydrometeor::i_qv, scale_index::i_rhot, scale_grid_index::ia, scale_grid_index::ie, scale_grid_index::ieb, scale_grid_index::is, scale_grid_index::isb, scale_grid_index::ja, scale_grid_index::je, scale_grid_index::jeb, scale_grid_index::js, scale_grid_index::jsb, scale_grid_index::ka, scale_grid_index::ke, scale_grid_index::ks, scale_atmos_hydrometeor::lhf, scale_atmos_hydrometeor::lhv, momx, momx_av, momy, momy_av, momz, momz_av, n2, pott, pres, scale_tracer::qa, scale_atmos_hydrometeor::qhe, scale_atmos_hydrometeor::qhs, scale_atmos_hydrometeor::qie, scale_atmos_hydrometeor::qis, scale_atmos_hydrometeor::qle, scale_atmos_hydrometeor::qls, qtrc, qtrc_av, scale_grid_real::real_cz, scale_grid_real::real_fz, rhot, rhot_av, temp, scale_tracer::tracer_cp, scale_tracer::tracer_cv, scale_tracer::tracer_desc, scale_tracer::tracer_mass, scale_tracer::tracer_name, scale_tracer::tracer_r, scale_tracer::tracer_unit, u, v, and w.

Referenced by mod_atmos_driver::atmos_driver(), and mod_atmos_driver::atmos_driver_resume2().

1195  use scale_const, only: &
1196  grav => const_grav, &
1197  rdry => const_rdry, &
1198  rvap => const_rvap, &
1199  cpdry => const_cpdry, &
1200  cvdry => const_cvdry, &
1201  p00 => const_pre00
1202  use scale_grid, only: &
1203  rcdx => grid_rcdx, &
1204  rcdy => grid_rcdy
1205  use scale_grid_real, only: &
1206  real_cz, &
1207  real_fz
1208  use scale_comm, only: &
1210  use scale_history, only: &
1211  hist_in
1212  use scale_atmos_thermodyn, only: &
1213  thermodyn_qd => atmos_thermodyn_qd
1214  use scale_atmos_hydrometeor, only: &
1215  hydrometeor_lhv => atmos_hydrometeor_lhv, &
1216  i_qv, &
1217  i_qc, &
1218  qhs, &
1219  qhe, &
1220  qls, &
1221  qle, &
1222  qis, &
1223  qie, &
1224  lhv, &
1225  lhf
1226  use scale_atmos_saturation, only: &
1227  saturation_psat_all => atmos_saturation_psat_all, &
1228  saturation_psat_liq => atmos_saturation_psat_liq, &
1229  saturation_psat_ice => atmos_saturation_psat_ice
1230  use scale_atmos_adiabat, only: &
1231  adiabat_cape => atmos_adiabat_cape
1232  use mod_atmos_phy_cp_vars, only: &
1233  sflx_rain_cp => atmos_phy_cp_sflx_rain
1234  use mod_atmos_phy_mp_vars, only: &
1235  sflx_rain_mp => atmos_phy_mp_sflx_rain, &
1236  sflx_snow_mp => atmos_phy_mp_sflx_snow
1237  implicit none
1238 
1239  real(RP) :: QDRY (KA,IA,JA) ! dry air [kg/kg]
1240  real(RP) :: QTOT (KA,IA,JA) ! total water [kg/kg]
1241  real(RP) :: QHYD (KA,IA,JA) ! total hydrometeor [kg/kg]
1242  real(RP) :: QLIQ (KA,IA,JA) ! total liquid water [kg/kg]
1243  real(RP) :: QICE (KA,IA,JA) ! total ice water [kg/kg]
1244  real(RP) :: RHOQ (KA,IA,JA)
1245 
1246  real(RP) :: LWP (IA,JA) ! liquid water path [g/m2]
1247  real(RP) :: IWP (IA,JA) ! ice water path [g/m2]
1248  real(RP) :: PW (IA,JA) ! precipitable water [g/m2]
1249 
1250  real(RP) :: RTOT (KA,IA,JA) ! Total gas constant [J/kg/K]
1251  real(RP) :: CPTOT (KA,IA,JA) ! Total heat capacity [J/kg/K]
1252  real(RP) :: CVTOT (KA,IA,JA) ! Total heat capacity [J/kg/K]
1253  real(RP) :: CPovCV(KA,IA,JA) ! Cp/Cv
1254 
1255  real(RP) :: POTL (KA,IA,JA) ! liquid water potential temperature [K]
1256  real(RP) :: RHA (KA,IA,JA) ! relative humidity (liquid+ice) [%]
1257  real(RP) :: RHL (KA,IA,JA) ! relative humidity against to liquid [%]
1258  real(RP) :: RHI (KA,IA,JA) ! relative humidity against to ice [%]
1259 
1260  real(RP) :: VOR (KA,IA,JA) ! vertical vorticity [1/s]
1261  real(RP) :: DIV (KA,IA,JA) ! divergence [1/s]
1262  real(RP) :: HDIV (KA,IA,JA) ! horizontal divergence [1/s]
1263  real(RP) :: Uabs (KA,IA,JA) ! absolute velocity [m/s]
1264 
1265  real(RP) :: CAPE (IA,JA) ! CAPE [m2/s2]
1266  real(RP) :: CIN (IA,JA) ! CIN [m2/s2]
1267  real(RP) :: LCL (IA,JA) ! LCL height [m]
1268  real(RP) :: LFC (IA,JA) ! LFC height [m]
1269  real(RP) :: LNB (IA,JA) ! LNB height [m]
1270 
1271  real(RP) :: PBLH (IA,JA) ! PBL height [m]
1272  real(RP) :: POTTv (KA,IA,JA) ! vertual potential temperature [K]
1273  real(RP) :: fact
1274 
1275  real(RP) :: MSE (KA,IA,JA) ! MSE [m2/s2]
1276  real(RP) :: LHV_local(KA,IA,JA) ! latent heat for vaporization [m2/s2]
1277 
1278  real(RP) :: PREC (IA,JA) ! surface precipitation rate CP+MP(rain+snow) [kg/m2/s]
1279  real(RP) :: RAIN (IA,JA) ! surface rain rate CP+MP [kg/m2/s]
1280  real(RP) :: SNOW (IA,JA) ! surface snow rate CP+MP [kg/m2/s]
1281 
1282  real(RP) :: DENS_PRIM(KA,IA,JA) ! horiz. deviation of density [kg/m3]
1283  real(RP) :: W_PRIM (KA,IA,JA) ! horiz. deviation of w [m/s]
1284  real(RP) :: U_PRIM (KA,IA,JA) ! horiz. deviation of u [m/s]
1285  real(RP) :: V_PRIM (KA,IA,JA) ! horiz. deviation of v [m/s]
1286  real(RP) :: POTT_PRIM(KA,IA,JA) ! horiz. deviation of pot. temp. [K]
1287  real(RP) :: W_PRIM2 (KA,IA,JA) ! variance of w [m2/s2]
1288  real(RP) :: PT_W_PRIM(KA,IA,JA) ! resolved scale heat flux [W/s]
1289  real(RP) :: W_PRIM3 (KA,IA,JA) ! skewness of w [m3/s3]
1290  real(RP) :: TKE_RS (KA,IA,JA) ! resolved scale TKE [m2/s2]
1291  real(RP) :: DENS_MEAN(KA) ! horiz. mean of density [kg/m3]
1292  real(RP) :: W_MEAN (KA) ! horiz. mean of w [m/s]
1293  real(RP) :: U_MEAN (KA) ! horiz. mean of u [m/s]
1294  real(RP) :: V_MEAN (KA) ! horiz. mean of v [m/s]
1295  real(RP) :: PT_MEAN (KA) ! horiz. mean of pot. [K]
1296  real(RP) :: T_MEAN (KA) ! horiz. mean of t [K]
1297  real(RP) :: QV_MEAN (KA) ! horiz. mean of QV
1298  real(RP) :: QHYD_MEAN(KA) ! horiz. mean of QHYD
1299  real(RP) :: QLIQ_MEAN(KA) ! horiz. mean of QLIQ
1300  real(RP) :: QICE_MEAN(KA) ! horiz. mean of QICE
1301 
1302  real(RP) :: ENGT (KA,IA,JA) ! total energy [J/m3]
1303  real(RP) :: ENGP (KA,IA,JA) ! potential energy [J/m3]
1304  real(RP) :: ENGK (KA,IA,JA) ! kinetic energy [J/m3]
1305  real(RP) :: ENGI (KA,IA,JA) ! internal energy [J/m3]
1306 
1307  real(RP) :: PSAT (KA,IA,JA)
1308  real(RP) :: UH (KA,IA,JA)
1309  real(RP) :: VH (KA,IA,JA)
1310 
1311  integer :: k, i, j, iq
1312  !---------------------------------------------------------------------------
1313 
1314  ! value check for prognostic variables
1315  if ( atmos_vars_checkrange ) then
1316  call valcheck( dens(:,:,:), 0.0_rp, 2.0_rp, var_name(i_dens), __file__, __line__ )
1317  call valcheck( momz(:,:,:), -200.0_rp, 200.0_rp, var_name(i_momz), __file__, __line__ )
1318  call valcheck( momx(:,:,:), -200.0_rp, 200.0_rp, var_name(i_momx), __file__, __line__ )
1319  call valcheck( momy(:,:,:), -200.0_rp, 200.0_rp, var_name(i_momy), __file__, __line__ )
1320  call valcheck( rhot(:,:,:), 0.0_rp, 1000.0_rp, var_name(i_rhot), __file__, __line__ )
1321  endif
1322 
1323  ! history output of prognostic variables
1324  call hist_in( dens(:,:,:), var_name(i_dens), var_desc(i_dens), var_unit(i_dens) )
1325  call hist_in( momz(:,:,:), var_name(i_momz), var_desc(i_momz), var_unit(i_momz) )
1326  call hist_in( momx(:,:,:), var_name(i_momx), var_desc(i_momx), var_unit(i_momx) )
1327  call hist_in( momy(:,:,:), var_name(i_momy), var_desc(i_momy), var_unit(i_momy) )
1328  call hist_in( rhot(:,:,:), var_name(i_rhot), var_desc(i_rhot), var_unit(i_rhot) )
1329  do iq = 1, qa
1330  call hist_in( qtrc(:,:,:,iq), tracer_name(iq), tracer_desc(iq), tracer_unit(iq) )
1331  enddo
1332 
1333  ! prepare and history output of diagnostic variables
1334 
1335  if ( ad_prep_sw(i_qdry) > 0 ) then
1336  call thermodyn_qd( qdry(:,:,:), & ! [OUT]
1337  qtrc_av(:,:,:,:), & ! [IN]
1338  tracer_mass(:) ) ! [IN]
1339  endif
1340 
1341  if ( ad_prep_sw(i_qtot) > 0 ) then
1342 !OCL XFILL
1343  do j = jsb, jeb
1344  do i = isb, ieb
1345  do k = ks, ke
1346  qtot(k,i,j) = 1.0_rp - qdry(k,i,j)
1347  enddo
1348  enddo
1349  enddo
1350  endif
1351 
1352  if ( ad_prep_sw(i_qhyd) > 0 ) then
1353 !OCL XFILL
1354  qhyd(:,:,:) = 0.0_rp
1355  do iq = qhs, qhe
1356  qhyd(:,:,:) = qhyd(:,:,:) + qtrc_av(:,:,:,iq)
1357  enddo
1358  endif
1359 
1360  if ( ad_prep_sw(i_qliq) > 0 ) then
1361 !OCL XFILL
1362  qliq(:,:,:) = 0.0_rp
1363  do iq = qls, qle
1364  qliq(:,:,:) = qliq(:,:,:) + qtrc_av(:,:,:,iq)
1365  enddo
1366  endif
1367 
1368  if ( ad_prep_sw(i_qice) > 0 ) then
1369 !OCL XFILL
1370  qice(:,:,:) = 0.0_rp
1371  do iq = qis, qie
1372  qice(:,:,:) = qice(:,:,:) + qtrc_av(:,:,:,iq)
1373  enddo
1374  endif
1375 
1376  if ( ad_prep_sw(i_lwp) > 0 ) then
1377  do j = jsb, jeb
1378  do i = isb, ieb
1379  lwp(i,j) = 0.0_rp
1380  do k = ks, ke
1381  lwp(i,j) = lwp(i,j) &
1382  + qliq(k,i,j) * dens_av(k,i,j) * ( real_fz(k,i,j)-real_fz(k-1,i,j) ) * 1.e3_rp ! [kg/m2->g/m2]
1383  enddo
1384  enddo
1385  enddo
1386  endif
1387 
1388  if ( ad_prep_sw(i_iwp) > 0 ) then
1389  do j = jsb, jeb
1390  do i = isb, ieb
1391  iwp(i,j) = 0.0_rp
1392  do k = ks, ke
1393  iwp(i,j) = iwp(i,j) &
1394  + qice(k,i,j) * dens_av(k,i,j) * ( real_fz(k,i,j)-real_fz(k-1,i,j) ) * 1.e3_rp ! [kg/m2->g/m2]
1395  enddo
1396  enddo
1397  enddo
1398  endif
1399 
1400  if ( ad_prep_sw(i_pw) > 0 ) then
1401  do j = jsb, jeb
1402  do i = isb, ieb
1403  pw(i,j) = 0.0_rp
1404  do k = ks, ke
1405  pw(i,j) = pw(i,j) &
1406  + qtrc_av(k,i,j,i_qv) * dens_av(k,i,j) * ( real_fz(k,i,j)-real_fz(k-1,i,j) ) * 1.e3_rp ! [kg/m2->g/m2]
1407  enddo
1408  enddo
1409  enddo
1410  endif
1411 
1412  if ( ad_prep_sw(i_rtot) > 0 ) then
1413  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1414 !OCL XFILL
1415  do j = jsb, jeb
1416  do i = isb, ieb
1417  do k = ks, ke
1418  calc_r(rtot(k,i,j), qdry(k,i,j), qtrc_av, k, i, j, iq, rdry, tracer_r)
1419  enddo
1420  enddo
1421  enddo
1422  endif
1423 
1424  if ( ad_prep_sw(i_cptot) > 0 ) then
1425  !$omp parallel do default(none) private(i,j,k) OMP_SCHEDULE_ collapse(2) &
1426  !$omp private(iq) &
1427  !$omp shared(JSB,JEB,ISB,IEB,KS,KE,CPTOT,CPdry,QDRY,QA,CVTOT,CVdry,QTRC_av,TRACER_CP,TRACER_CV) &
1428  !$omp shared(I_QV,LHV,QIS,QIE,LHF)
1429 !OCL XFILL
1430  do j = jsb, jeb
1431  do i = isb, ieb
1432  do k = ks, ke
1433  cptot(k,i,j) = cpdry * qdry(k,i,j)
1434  cvtot(k,i,j) = cvdry * qdry(k,i,j)
1435  do iq = 1, qa
1436  cptot(k,i,j) = cptot(k,i,j) + qtrc_av(k,i,j,iq) * tracer_cp(iq)
1437  cvtot(k,i,j) = cvtot(k,i,j) + qtrc_av(k,i,j,iq) * tracer_cv(iq)
1438  end do
1439  enddo
1440  enddo
1441  enddo
1442 
1443  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1444 !OCL XFILL
1445  do j = jsb, jeb
1446  do i = isb, ieb
1447  do k = ks, ke
1448  cpovcv(k,i,j) = cptot(k,i,j) / cvtot(k,i,j)
1449  enddo
1450  enddo
1451  enddo
1452  endif
1453 
1454  if ( ad_prep_sw(i_potl) > 0 ) then
1455  call hydrometeor_lhv( lhv_local(:,:,:), temp(:,:,:) )
1456 
1457  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1458 !OCL XFILL
1459  do j = jsb, jeb
1460  do i = isb, ieb
1461  do k = ks, ke
1462  potl(k,i,j) = pott(k,i,j) &
1463  - lhv_local(k,i,j) / cpdry * qliq(k,i,j) * pott(k,i,j) / temp(k,i,j)
1464  enddo
1465  enddo
1466  enddo
1467  endif
1468 
1469  if ( ad_prep_sw(i_qsat) > 0 ) then
1470 ! call SATURATION_dens2qsat_all( QSAT (:,:,:), & ! [OUT]
1471 ! TEMP (:,:,:), & ! [IN]
1472 ! DENS_av(:,:,:) ) ! [IN]
1473  end if
1474 
1475  if ( ad_hist_id(i_rha) > 0 ) then
1476  call saturation_psat_all( psat(:,:,:), temp(:,:,:) )
1477 
1478  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1479 !OCL XFILL
1480  do j = jsb, jeb
1481  do i = isb, ieb
1482  do k = ks, ke
1483  rha(k,i,j) = dens_av(k,i,j) * qtrc_av(k,i,j,i_qv) &
1484  / psat(k,i,j) * rvap * temp(k,i,j) &
1485  * 100.0_rp
1486  enddo
1487  enddo
1488  enddo
1489  endif
1490 
1491  if ( ad_hist_id(i_rhl) > 0 ) then
1492  call saturation_psat_liq( psat(:,:,:), & ! [OUT]
1493  temp(:,:,:) ) ! [IN]
1494  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1495 !OCL XFILL
1496  do j = jsb, jeb
1497  do i = isb, ieb
1498  do k = ks, ke
1499  rhl(k,i,j) = dens_av(k,i,j) * qtrc_av(k,i,j,i_qv) &
1500  / psat(k,i,j) * rvap * temp(k,i,j) &
1501  * 100.0_rp
1502  enddo
1503  enddo
1504  enddo
1505  endif
1506 
1507  if ( ad_hist_id(i_rhi) > 0 ) then
1508  call saturation_psat_ice( psat(:,:,:), & ! [OUT]
1509  temp(:,:,:) ) ! [IN]
1510  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1511 !OCL XFILL
1512  do j = jsb, jeb
1513  do i = isb, ieb
1514  do k = ks, ke
1515  rhi(k,i,j) = dens_av(k,i,j) * qtrc_av(k,i,j,i_qv) &
1516  / psat(k,i,j) * rvap * temp(k,i,j) &
1517  * 100.0_rp
1518  enddo
1519  enddo
1520  enddo
1521  endif
1522 
1523  if ( ad_prep_sw(i_vor) > 0 ) then
1524  ! at x, v, layer
1525  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1526 !OCL XFILL
1527  do j = 1, ja-1
1528  do i = 2, ia
1529  do k = ks, ke
1530  uh(k,i,j) = 0.5_rp * ( momx_av(k,i,j)+momx_av(k,i,j+1)+momx_av(k,i-1,j)+momx_av(k,i-1,j+1) ) &
1531  / ( dens_av(k,i,j)+dens_av(k,i,j+1) )
1532  enddo
1533  enddo
1534  enddo
1535 
1536  ! at u, y, layer
1537  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1538 !OCL XFILL
1539  do j = 2, ja
1540  do i = 1, ia-1
1541  do k = ks, ke
1542  vh(k,i,j) = 0.5_rp * ( momy_av(k,i,j)+momy_av(k,i+1,j)+momy_av(k,i,j-1)+momy_av(k,i+1,j-1) ) &
1543  / ( dens_av(k,i,j)+dens_av(k,i+1,j) )
1544  enddo
1545  enddo
1546  enddo
1547 
1548  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1549 !OCL XFILL
1550  do j = 2, ja-1
1551  do i = 2, ia-1
1552  do k = ks, ke
1553  vor(k,i,j) = ( vh(k,i,j ) - vh(k,i-1,j ) ) * rcdx(i) &
1554  - ( uh(k,i ,j) - uh(k,i ,j-1) ) * rcdy(j)
1555  enddo
1556  enddo
1557  enddo
1558 
1559  !$omp parallel do private(j,k) OMP_SCHEDULE_
1560  do j = 1, ja
1561  do k = ks, ke
1562  vor(k,1 ,j) = vor(k,2 ,j)
1563  vor(k,ia,j) = vor(k,ia-1,j)
1564  enddo
1565  enddo
1566 
1567  !$omp parallel do private(i,k) OMP_SCHEDULE_
1568  do i = 1, ia
1569  do k = ks, ke
1570  vor(k,i,1 ) = vor(k,i,2 )
1571  vor(k,i,ja) = vor(k,i,ja-1)
1572  enddo
1573  enddo
1574  endif
1575 
1576  if ( ad_prep_sw(i_hdiv) > 0 ) then
1577  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1578 !OCL XFILL
1579  do j = 2, ja
1580  do i = 2, ia
1581  do k = ks, ke
1582  hdiv(k,i,j) = ( momx_av(k,i,j) - momx_av(k ,i-1,j ) ) * rcdx(i) &
1583  + ( momy_av(k,i,j) - momy_av(k ,i ,j-1) ) * rcdy(j)
1584  enddo
1585  enddo
1586  enddo
1587  !$omp parallel do private(i,k) OMP_SCHEDULE_
1588  do i = 1, ia
1589  do k = ks, ke
1590  hdiv(k,i,1) = hdiv(k,i,2)
1591  enddo
1592  enddo
1593  !$omp parallel do private(j,k) OMP_SCHEDULE_
1594  do j = 1, ja
1595  do k = ks, ke
1596  hdiv(k,1,j) = hdiv(k,2,j)
1597  enddo
1598  enddo
1599  endif
1600 
1601  if ( ad_prep_sw(i_div) > 0 ) then
1602  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1603 !OCL XFILL
1604  do j = 1, ja
1605  do i = 1, ia
1606  do k = ks, ke
1607  div(k,i,j) = ( momz_av(k,i,j) - momz_av(k-1,i ,j ) ) * ( real_fz(k,i,j)-real_fz(k-1,i,j) ) &
1608  + hdiv(k,i,j)
1609  enddo
1610  enddo
1611  enddo
1612  endif
1613 
1614  if ( ad_prep_sw(i_uabs) > 0 ) then
1615 !OCL XFILL
1616  do j = 1, ja
1617  do i = 1, ia
1618  do k = ks, ke
1619  uabs(k,i,j) = sqrt( u(k,i,j) * u(k,i,j) &
1620  + v(k,i,j) * v(k,i,j) )
1621  enddo
1622  enddo
1623  enddo
1624  endif
1625 
1626  if ( ad_prep_sw(i_dens_mean) > 0 ) then
1627  call comm_horizontal_mean( dens_mean(:), dens_av(:,:,:) )
1628  end if
1629 
1630  if ( ad_prep_sw(i_dens_prim) > 0 ) then
1631 !OCL XFILL
1632  do j = 1, ja
1633  do i = 1, ia
1634  do k = ks, ke
1635  dens_prim(k,i,j) = dens_av(k,i,j) - dens_mean(k)
1636  enddo
1637  enddo
1638  enddo
1639  endif
1640 
1641  if ( ad_prep_sw(i_w_mean) > 0 ) then
1642 !OCL XFILL
1643  do j = 1, ja
1644  do i = 1, ia
1645  do k = 1, ka
1646  w_prim(k,i,j) = w(k,i,j) * dens_av(k,i,j)
1647  enddo
1648  enddo
1649  enddo
1650  call comm_horizontal_mean( w_mean(:), w_prim(:,:,:) )
1651  do k = 1, ka
1652  w_mean(k) = w_mean(k) / dens_mean(k)
1653  enddo
1654  end if
1655  if ( ad_prep_sw(i_w_prim) > 0 ) then
1656 !OCL XFILL
1657  do j = 1, ja
1658  do i = 1, ia
1659  do k = 1, ka
1660  w_prim(k,i,j) = w(k,i,j) - w_mean(k)
1661  enddo
1662  enddo
1663  enddo
1664  endif
1665 
1666  if ( ad_prep_sw(i_u_mean) > 0 ) then
1667 !OCL XFILL
1668  do j = 1, ja
1669  do i = 1, ia
1670  do k = 1, ka
1671  u_prim(k,i,j) = u(k,i,j) * dens_av(k,i,j)
1672  enddo
1673  enddo
1674  enddo
1675  call comm_horizontal_mean( u_mean(:), u_prim(:,:,:) )
1676  do k = 1, ka
1677  u_mean(k) = u_mean(k) / dens_mean(k)
1678  enddo
1679  end if
1680  if ( ad_prep_sw(i_u_prim) > 0 ) then
1681 !OCL XFILL
1682  do j = 1, ja
1683  do i = 1, ia
1684  do k = 1, ka
1685  u_prim(k,i,j) = u(k,i,j) - u_mean(k)
1686  enddo
1687  enddo
1688  enddo
1689  endif
1690 
1691  if ( ad_prep_sw(i_v_mean) > 0 ) then
1692 !OCL XFILL
1693  do j = 1, ja
1694  do i = 1, ia
1695  do k = 1, ka
1696  v_prim(k,i,j) = v(k,i,j) * dens_av(k,i,j)
1697  enddo
1698  enddo
1699  enddo
1700  call comm_horizontal_mean( v_mean(:), v_prim(:,:,:) )
1701  do k = 1, ka
1702  v_mean(k) = v_mean(k) / dens_mean(k)
1703  enddo
1704  end if
1705  if ( ad_prep_sw(i_v_prim) > 0 ) then
1706 !OCL XFILL
1707  do j = 1, ja
1708  do i = 1, ia
1709  do k = 1, ka
1710  v_prim(k,i,j) = v(k,i,j) - v_mean(k)
1711  enddo
1712  enddo
1713  enddo
1714  endif
1715 
1716  if ( ad_prep_sw(i_t_mean) > 0 ) then
1717 !OCL XFILL
1718  do j = 1, ja
1719  do i = 1, ia
1720  do k = 1, ka
1721  pott_prim(k,i,j) = temp(k,i,j) * dens_av(k,i,j)
1722  enddo
1723  enddo
1724  enddo
1725  call comm_horizontal_mean( t_mean(:), pott_prim(:,:,:) )
1726  do k = 1, ka
1727  t_mean(k) = t_mean(k) / dens_mean(k)
1728  enddo
1729  end if
1730 
1731  if ( ad_prep_sw(i_pott_mean) > 0 ) then
1732  call comm_horizontal_mean( pt_mean(:), rhot_av(:,:,:) )
1733  do k = 1, ka
1734  pt_mean(k) = pt_mean(k) / dens_mean(k)
1735  enddo
1736  end if
1737  if ( ad_prep_sw(i_pott_prim) > 0 ) then
1738 !OCL XFILL
1739  do j = 1, ja
1740  do i = 1, ia
1741  do k = 1, ka
1742  pott_prim(k,i,j) = pott(k,i,j) - pt_mean(k)
1743  enddo
1744  enddo
1745  enddo
1746  endif
1747 
1748  if ( ad_prep_sw(i_qv_mean) > 0 ) then
1749 !OCL XFILL
1750  do j = 1, ja
1751  do i = 1, ia
1752  do k = 1, ka
1753  rhoq(k,i,j) = qtrc_av(k,i,j,i_qv) * dens_av(k,i,j)
1754  enddo
1755  enddo
1756  enddo
1757  call comm_horizontal_mean( qv_mean(:), rhoq(:,:,:) )
1758  do k = 1, ka
1759  qv_mean(k) = qv_mean(k) / dens_mean(k)
1760  enddo
1761  end if
1762 
1763  if ( ad_prep_sw(i_qhyd_mean) > 0 ) then
1764 !OCL XFILL
1765  do j = 1, ja
1766  do i = 1, ia
1767  do k = 1, ka
1768  rhoq(k,i,j) = qhyd(k,i,j) * dens_av(k,i,j)
1769  enddo
1770  enddo
1771  enddo
1772  call comm_horizontal_mean( qhyd_mean(:), rhoq(:,:,:) )
1773  do k = 1, ka
1774  qhyd_mean(k) = qhyd_mean(k) / dens_mean(k)
1775  enddo
1776  end if
1777 
1778  if ( ad_prep_sw(i_qliq_mean) > 0 ) then
1779 !OCL XFILL
1780  do j = 1, ja
1781  do i = 1, ia
1782  do k = 1, ka
1783  rhoq(k,i,j) = qliq(k,i,j) * dens_av(k,i,j)
1784  enddo
1785  enddo
1786  enddo
1787  call comm_horizontal_mean( qliq_mean(:), rhoq(:,:,:) )
1788  do k = 1, ka
1789  qliq_mean(k) = qliq_mean(k) / dens_mean(k)
1790  enddo
1791  end if
1792 
1793  if ( ad_prep_sw(i_qice_mean) > 0 ) then
1794 !OCL XFILL
1795  do j = 1, ja
1796  do i = 1, ia
1797  do k = 1, ka
1798  rhoq(k,i,j) = qice(k,i,j) * dens_av(k,i,j)
1799  enddo
1800  enddo
1801  enddo
1802  call comm_horizontal_mean( qice_mean(:), rhoq(:,:,:) )
1803  do k = 1, ka
1804  qice_mean(k) = qice_mean(k) / dens_mean(k)
1805  enddo
1806  end if
1807 
1808  if ( ad_prep_sw(i_w_prim2) > 0 ) then
1809 !OCL XFILL
1810  do j = 1, ja
1811  do i = 1, ia
1812  do k = ks, ke
1813  w_prim2(k,i,j) = w_prim(k,i,j) * w_prim(k,i,j)
1814  enddo
1815  enddo
1816  enddo
1817  endif
1818 
1819  if ( ad_prep_sw(i_pt_w_prim) > 0 ) then
1820 !OCL XFILL
1821  do j = 1, ja
1822  do i = 1, ia
1823  do k = ks, ke
1824  pt_w_prim(k,i,j) = w_prim(k,i,j) * pott_prim(k,i,j) * dens_av(k,i,j) * cpdry
1825  enddo
1826  enddo
1827  enddo
1828  endif
1829 
1830  if ( ad_prep_sw(i_w_prim3) > 0 ) then
1831 !OCL XFILL
1832  do j = 1, ja
1833  do i = 1, ia
1834  do k = ks, ke
1835  w_prim3(k,i,j) = w_prim(k,i,j) * w_prim(k,i,j) * w_prim(k,i,j)
1836  enddo
1837  enddo
1838  enddo
1839  endif
1840 
1841  if ( ad_prep_sw(i_tke_rs) > 0 ) then
1842 !OCL XFILL
1843  do j = 1, ja
1844  do i = 1, ia
1845  do k = ks, ke
1846  tke_rs(k,i,j) = 0.5_rp * ( w_prim(k,i,j) * w_prim(k,i,j) &
1847  + u_prim(k,i,j) * u_prim(k,i,j) &
1848  + v_prim(k,i,j) * v_prim(k,i,j) )
1849  enddo
1850  enddo
1851  enddo
1852  endif
1853 
1854  if ( ad_prep_sw(i_engp) > 0 ) then
1855  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1856 !OCL XFILL
1857  do j = 1, ja
1858  do i = 1, ia
1859  do k = ks, ke
1860  engp(k,i,j) = dens_av(k,i,j) * grav * real_cz(k,i,j)
1861  enddo
1862  enddo
1863  enddo
1864  endif
1865 
1866  if ( ad_prep_sw(i_engk) > 0 ) then
1867  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1868 !OCL XFILL
1869  do j = 1, ja
1870  do i = 1, ia
1871  do k = ks, ke
1872  engk(k,i,j) = 0.5_rp * dens_av(k,i,j) * ( w(k,i,j)**2 &
1873  + u(k,i,j)**2 &
1874  + v(k,i,j)**2 )
1875  enddo
1876  enddo
1877  enddo
1878  endif
1879 
1880  if ( ad_prep_sw(i_engi) > 0 ) then
1881  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1882 !OCL XFILL
1883  do j = jsb, jeb
1884  do i = isb, ieb
1885  do k = ks, ke
1886  engi(k,i,j) = dens_av(k,i,j) * qdry(k,i,j) * temp(k,i,j) * cvdry
1887  enddo
1888  enddo
1889  enddo
1890 
1891  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(3)
1892  do j = jsb, jeb
1893  do i = isb, ieb
1894  do k = ks, ke
1895  do iq = 1, qa
1896  engi(k,i,j) = engi(k,i,j) &
1897  + dens_av(k,i,j) * qtrc_av(k,i,j,iq) * temp(k,i,j) * tracer_cv(iq)
1898  enddo
1899  enddo
1900  enddo
1901  enddo
1902 
1903  if ( i_qv > 0 ) then
1904  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(3)
1905  do j = jsb, jeb
1906  do i = isb, ieb
1907  do k = ks, ke
1908  engi(k,i,j) = engi(k,i,j) &
1909  + dens_av(k,i,j) * qtrc_av(k,i,j,i_qv) * lhv ! Latent Heat [vapor->liquid]
1910  enddo
1911  enddo
1912  enddo
1913  end if
1914 
1915  do iq = qis, qie
1916  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(3)
1917  do j = jsb, jeb
1918  do i = isb, ieb
1919  do k = ks, ke
1920  engi(k,i,j) = engi(k,i,j) &
1921  - dens_av(k,i,j) * qtrc_av(k,i,j,iq) * lhf ! Latent Heat [ice->liquid]
1922  enddo
1923  enddo
1924  enddo
1925  enddo
1926  endif
1927 
1928  if ( ad_prep_sw(i_engt) > 0 ) then
1929  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
1930 !OCL XFILL
1931  do j = jsb, jeb
1932  do i = isb, ieb
1933  do k = ks, ke
1934  engt(k,i,j) = engp(k,i,j) + engk(k,i,j) + engi(k,i,j)
1935  enddo
1936  enddo
1937  enddo
1938  endif
1939 
1940  call hist_in( w(:,:,:), 'W', 'velocity w', 'm/s' )
1941  call hist_in( u(:,:,:), 'U', 'velocity u', 'm/s' )
1942  call hist_in( v(:,:,:), 'V', 'velocity v', 'm/s' )
1943  call hist_in( pott(:,:,:), 'PT', 'potential temp.', 'K' )
1944 
1945  call hist_in( qdry(:,:,:), 'QDRY', 'dry air', 'kg/kg' )
1946  call hist_in( qtot(:,:,:), 'QTOT', 'total water', 'kg/kg' )
1947  call hist_in( qhyd(:,:,:), 'QHYD', 'total hydrometeors', 'kg/kg' )
1948  call hist_in( qliq(:,:,:), 'QLIQ', 'total liquid water', 'kg/kg' )
1949  call hist_in( qice(:,:,:), 'QICE', 'total ice water', 'kg/kg' )
1950 
1951  call hist_in( lwp(:,:), 'LWP', 'liquid water path', 'g/m2' )
1952  call hist_in( iwp(:,:), 'IWP', 'ice water path', 'g/m2' )
1953  call hist_in( pw(:,:), 'PW', 'precipitable water', 'g/m2' )
1954 
1955  call hist_in( rtot(:,:,:), 'RTOT', 'Total gas constant', 'J/kg/K' )
1956  call hist_in( cptot(:,:,:), 'CPTOT', 'Total heat capacity', 'J/kg/K' )
1957  call hist_in( pres(:,:,:), 'PRES', 'pressure', 'Pa' )
1958  call hist_in( temp(:,:,:), 'T', 'temperature', 'K' )
1959 
1960  call hist_in( potl(:,:,:), 'LWPT', 'liq. potential temp.', 'K' )
1961  call hist_in( rha(:,:,:), 'RHA', 'relative humidity(liq+ice)','%' )
1962  call hist_in( rhl(:,:,:), 'RH' , 'relative humidity(liq)', '%' )
1963  call hist_in( rhi(:,:,:), 'RHI', 'relative humidity(ice)', '%' )
1964 
1965  call hist_in( vor(:,:,:), 'VOR', 'vertical vorticity', '1/s' )
1966  call hist_in( div(:,:,:), 'DIV', 'divergence', '1/s' )
1967  call hist_in( hdiv(:,:,:), 'HDIV', 'horizontal divergence', '1/s' )
1968  call hist_in( uabs(:,:,:), 'Uabs', 'absolute velocity', 'm/s' )
1969 
1970  call hist_in( n2(:,:,:), 'N2', 'squared Brunt-Vaisala frequency','1/s2' )
1971 
1972  call hist_in( dens_mean(:), 'DENS_MEAN', 'horiz. mean of density', 'kg/m3' )
1973  call hist_in( w_mean(:), 'W_MEAN', 'horiz. mean of w', 'm/s' )
1974  call hist_in( u_mean(:), 'U_MEAN', 'horiz. mean of u', 'm/s' )
1975  call hist_in( v_mean(:), 'V_MEAN', 'horiz. mean of v', 'm/s' )
1976  call hist_in( pt_mean(:), 'PT_MEAN', 'horiz. mean of pot.', 'K' )
1977  call hist_in( t_mean(:), 'T_MEAN', 'horiz. mean of t', 'K' )
1978  call hist_in( qv_mean(:), 'QV_MEAN', 'horiz. mean of QV', '1' )
1979  call hist_in( qhyd_mean(:), 'QHYD_MEAN', 'horiz. mean of QHYD', '1' )
1980  call hist_in( qliq_mean(:), 'QLIQ_MEAN', 'horiz. mean of QLIQ', '1' )
1981  call hist_in( qice_mean(:), 'QICE_MEAN', 'horiz. mean of QICE', '1' )
1982 
1983  call hist_in( dens_prim(:,:,:), 'DENS_PRIM', 'horiz. deviation of density', 'kg/m3' )
1984  call hist_in( w_prim(:,:,:), 'W_PRIM', 'horiz. deviation of w', 'm/s' )
1985  call hist_in( u_prim(:,:,:), 'U_PRIM', 'horiz. deviation of u', 'm/s' )
1986  call hist_in( v_prim(:,:,:), 'V_PRIM', 'horiz. deviation of v', 'm/s' )
1987  call hist_in( pott_prim(:,:,:), 'PT_PRIM', 'horiz. deviation of pot. temp.', 'K' )
1988  call hist_in( w_prim2(:,:,:), 'W_PRIM2', 'variance of w', 'm2/s2' )
1989  call hist_in( pt_w_prim(:,:,:), 'PT_W_PRIM', 'resolved scale heat flux', 'W/s' )
1990  call hist_in( w_prim3(:,:,:), 'W_PRIM3', 'skewness of w', 'm3/s3' )
1991  call hist_in( tke_rs(:,:,:), 'TKE_RS', 'resolved scale TKE', 'm2/s2' )
1992 
1993  call hist_in( engt(:,:,:), 'ENGT', 'total energy', 'J/m3' )
1994  call hist_in( engp(:,:,:), 'ENGP', 'potential energy', 'J/m3' )
1995  call hist_in( engk(:,:,:), 'ENGK', 'kinetic energy', 'J/m3' )
1996  call hist_in( engi(:,:,:), 'ENGI', 'internal energy', 'J/m3' )
1997 
1998  if ( ad_prep_sw(i_cape) > 0 &
1999  .OR. ad_prep_sw(i_cin) > 0 &
2000  .OR. ad_prep_sw(i_lcl) > 0 &
2001  .OR. ad_prep_sw(i_lfc) > 0 &
2002  .OR. ad_prep_sw(i_lnb) > 0 ) then
2003 
2004  call adiabat_cape( ks, & ! [IN]
2005  dens_av(:,:,:), & ! [IN]
2006  temp(:,:,:), & ! [IN]
2007  pres(:,:,:), & ! [IN]
2008  qtrc_av(:,:,:,:), & ! [IN]
2009  real_cz(:,:,:), & ! [IN]
2010  real_fz(:,:,:), & ! [IN]
2011  cape(:,:), & ! [OUT]
2012  cin(:,:), & ! [OUT]
2013  lcl(:,:), & ! [OUT]
2014  lfc(:,:), & ! [OUT]
2015  lnb(:,:) ) ! [OUT]
2016 
2017  endif
2018 
2019  call hist_in( cape(:,:), 'CAPE', 'convection avail. pot. energy', 'm2/s2' )
2020  call hist_in( cin(:,:), 'CIN', 'convection inhibition', 'm2/s2' )
2021  call hist_in( lcl(:,:), 'LCL', 'lifted condensation level', 'm' )
2022  call hist_in( lfc(:,:), 'LFC', 'level of free convection', 'm' )
2023  call hist_in( lnb(:,:), 'LNB', 'level of neutral buoyancy', 'm' )
2024 
2025  if ( ad_prep_sw(i_pblh) > 0 ) then
2026  do j = js, je
2027  do i = is, ie
2028  do k = ks, ke
2029  fact = 1.0_rp
2030  if ( i_qv > 0 ) fact = fact + 0.61_rp * qtrc_av(k,i,j,i_qv)
2031  if ( i_qc > 0 ) fact = fact - 1.61_rp * qtrc_av(k,i,j,i_qc)
2032  pottv(k,i,j) = pott(k,i,j) * fact
2033  enddo
2034  enddo
2035  enddo
2036 
2037  do j = js, je
2038  do i = is, ie
2039  pblh(i,j) = real_cz(ks,i,j) - real_fz(ks-1,i,j)
2040 
2041  do k = ks+1, ke
2042  if ( pottv(k,i,j) > pottv(ks,i,j) ) then
2043  fact = ( pottv(ks,i,j) - pottv(k-1,i,j) ) &
2044  / ( pottv(k,i,j) - pottv(k-1,i,j) )
2045 
2046  pblh(i,j) = real_cz(k-1,i,j) - real_fz(ks-1,i,j) &
2047  + fact * ( real_cz(k,i,j) - real_cz(k-1,i,j) )
2048 
2049  exit
2050  endif
2051  enddo
2052  enddo
2053  enddo
2054  endif
2055  call hist_in( pblh(:,:), 'PBLH', 'PBL height', 'm' )
2056 
2057  if ( ad_prep_sw(i_mse) > 0 ) then
2058  call hydrometeor_lhv( lhv_local(:,:,:), temp(:,:,:) )
2059 
2060  do j = js, je
2061  do i = is, ie
2062  do k = ks, ke
2063  mse(k,i,j) = cptot(k,i,j) * temp(k,i,j) &
2064  + grav * ( real_cz(k,i,j) - real_fz(ks-1,i,j) ) &
2065  + lhv_local(k,i,j) * qtrc_av(k,i,j,i_qv)
2066  enddo
2067  enddo
2068  enddo
2069  endif
2070  call hist_in( mse(:,:,:), 'MSE', 'moist static energy', 'm2/s2' )
2071 
2072  do j = js, je
2073  do i = is, ie
2074  prec(i,j) = sflx_rain_mp(i,j) + sflx_snow_mp(i,j) &
2075  + sflx_rain_cp(i,j)
2076  rain(i,j) = sflx_rain_mp(i,j) &
2077  + sflx_rain_cp(i,j)
2078  snow(i,j) = sflx_snow_mp(i,j)
2079  enddo
2080  enddo
2081  call hist_in( prec(:,:), 'PREC', 'surface precipitation rate (total)', 'kg/m2/s' )
2082  call hist_in( rain(:,:), 'RAIN', 'surface rain rate (total)', 'kg/m2/s' )
2083  call hist_in( snow(:,:), 'SNOW', 'surface snow rate (total)', 'kg/m2/s' )
2084 
2085  return
module ATMOSPHERE / Adiabatic process
real(rp), dimension(:,:,:), allocatable, target, public momz
real(rp), public const_cvdry
specific heat (dry air,constant volume) [J/kg/K]
Definition: scale_const.F90:59
module Atmosphere / Physics Cumulus
real(rp), dimension(:), allocatable, public grid_rcdy
reciprocal of center-dy
real(rp), public const_cpdry
specific heat (dry air,constant pressure) [J/kg/K]
Definition: scale_const.F90:58
module ATMOSPHERE / Saturation adjustment
real(rp), dimension(:,:,:), allocatable, target, public rhot
module Atmosphere / Physics Cloud Microphysics
real(rp), dimension(:), allocatable, public grid_rcdx
reciprocal of center-dx
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
real(rp), dimension(:,:,:), allocatable, target, public momx
real(rp), dimension(:,:,:), allocatable, public real_fz
geopotential height [m] (cell face )
real(rp), dimension(:,:,:), allocatable, public real_cz
geopotential height [m] (cell center)
real(rp), dimension(:,:,:), allocatable, target, public dens
real(rp), dimension(:,:), allocatable, public atmos_phy_mp_sflx_rain
real(rp), public const_rdry
specific gas constant (dry air) [J/kg/K]
Definition: scale_const.F90:57
subroutine, public atmos_adiabat_cape(Kstr, DENS, TEMP, PRES, QTRC, CZ, FZ, CAPE, CIN, LCL, LFC, LNB)
Calc CAPE and CIN Type of parcel method: Pseudo-adiabatic ascend from lowermost layer of the model Re...
real(rp), dimension(:,:,:), pointer, public momx_av
subroutine, public comm_horizontal_mean(varmean, var)
calculate horizontal mean (global total with communication)
Definition: scale_comm.F90:482
module GRID (real space)
real(rp), public const_pre00
pressure reference [Pa]
Definition: scale_const.F90:90
module COMMUNICATION
Definition: scale_comm.F90:23
real(rp), public const_grav
standard acceleration of gravity [m/s2]
Definition: scale_const.F90:48
real(rp), dimension(:,:,:), pointer, public dens_av
real(rp), public lhf
latent heat of fusion for use [J/kg]
real(rp), parameter, public const_rvap
specific gas constant (water vapor) [J/kg/K]
Definition: scale_const.F90:65
real(rp), public lhv
latent heat of vaporization for use [J/kg]
module CONSTANT
Definition: scale_const.F90:14
real(rp), dimension(:,:,:), allocatable, target, public momy
module GRID (cartesian)
real(rp), dimension(:,:), allocatable, public atmos_phy_mp_sflx_snow
real(rp), dimension(:,:,:), allocatable, public n2
module ATMOSPHERE / Thermodynamics
module HISTORY
real(rp), dimension(:,:,:), pointer, public momz_av
real(rp), dimension(:,:,:), pointer, public rhot_av
real(rp), dimension(:,:,:), pointer, public momy_av
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_rain
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_vars_total()

subroutine, public mod_atmos_vars::atmos_vars_total ( )

Budget monitor for atmosphere.

Definition at line 2091 of file mod_atmos_vars.f90.

References scale_const::const_cvdry, scale_const::const_grav, dens, dens_av, scale_index::i_dens, scale_index::i_momx, scale_index::i_momy, scale_index::i_momz, scale_atmos_hydrometeor::i_qv, scale_index::i_rhot, scale_grid_index::ie, scale_grid_index::is, scale_grid_index::je, scale_grid_index::js, scale_grid_index::ke, scale_grid_index::ks, scale_atmos_hydrometeor::lhf, scale_atmos_hydrometeor::lhv, momx, momx_av, momy, momy_av, momz, momz_av, pres, scale_tracer::qa, scale_atmos_hydrometeor::qie, scale_atmos_hydrometeor::qis, qtrc, qtrc_av, scale_grid_real::real_cz, rhot, rhot_av, scale_rm_statistics::statistics_checktotal, temp, scale_tracer::tracer_cv, scale_tracer::tracer_mass, scale_tracer::tracer_name, scale_tracer::tracer_r, u, v, and w.

Referenced by mod_atmos_dyn_driver::atmos_dyn_driver(), atmos_vars_restart_read(), and atmos_vars_restart_write().

2091  use scale_const, only: &
2092  grav => const_grav, &
2093  cvdry => const_cvdry
2094  use scale_grid_real, only: &
2095  real_cz
2096  use scale_rm_statistics, only: &
2098  stat_total
2099  use scale_atmos_thermodyn, only: &
2100  thermodyn_qd => atmos_thermodyn_qd, &
2101  thermodyn_temp_pres => atmos_thermodyn_temp_pres
2102  use scale_atmos_hydrometeor, only: &
2103  i_qv, &
2104  qis, &
2105  qie, &
2106  lhv, &
2107  lhf
2108  implicit none
2109 
2110  real(RP) :: W (KA,IA,JA) ! velocity w at cell center [m/s]
2111  real(RP) :: U (KA,IA,JA) ! velocity u at cell center [m/s]
2112  real(RP) :: V (KA,IA,JA) ! velocity v at cell center [m/s]
2113 
2114  real(RP) :: QDRY(KA,IA,JA) ! dry air [kg/kg]
2115  real(RP) :: PRES(KA,IA,JA) ! pressure [Pa]
2116  real(RP) :: TEMP(KA,IA,JA) ! temperature [K]
2117 
2118  real(RP) :: ENGT(KA,IA,JA) ! total energy [J/m3]
2119  real(RP) :: ENGP(KA,IA,JA) ! potential energy [J/m3]
2120  real(RP) :: ENGK(KA,IA,JA) ! kinetic energy [J/m3]
2121  real(RP) :: ENGI(KA,IA,JA) ! internal energy [J/m3]
2122 
2123  real(RP) :: RHOQ(KA,IA,JA)
2124 
2125  real(RP) :: total ! dummy
2126  integer :: i, j, k, iq
2127  !---------------------------------------------------------------------------
2128 
2129  if ( statistics_checktotal ) then
2130 
2131  call stat_total( total, dens(:,:,:), var_name(i_dens) )
2132  call stat_total( total, momz(:,:,:), var_name(i_momz) )
2133  call stat_total( total, momx(:,:,:), var_name(i_momx) )
2134  call stat_total( total, momy(:,:,:), var_name(i_momy) )
2135  call stat_total( total, rhot(:,:,:), var_name(i_rhot) )
2136 
2137  do iq = 1, qa
2138  rhoq(:,:,:) = dens_av(:,:,:) * qtrc_av(:,:,:,iq)
2139 
2140  call stat_total( total, rhoq(:,:,:), tracer_name(iq) )
2141  enddo
2142 
2143  call thermodyn_qd( qdry(:,:,:), & ! [OUT]
2144  qtrc_av(:,:,:,:), & ! [IN]
2145  tracer_mass(:) ) ! [IN]
2146 
2147  call thermodyn_temp_pres( temp(:,:,:), & ! [OUT]
2148  pres(:,:,:), & ! [OUT]
2149  dens_av(:,:,:), & ! [IN]
2150  rhot_av(:,:,:), & ! [IN]
2151  qtrc_av(:,:,:,:), & ! [IN]
2152  tracer_cv(:), & ! [IN]
2153  tracer_r(:), & ! [IN]
2154  tracer_mass(:) ) ! [IN]
2155 
2156  rhoq(ks:ke,is:ie,js:je) = dens_av(ks:ke,is:ie,js:je) * qdry(ks:ke,is:ie,js:je)
2157 
2158  call stat_total( total, rhoq(:,:,:), 'QDRY' )
2159 
2160  rhoq(ks:ke,is:ie,js:je) = dens_av(ks:ke,is:ie,js:je) * ( 1.0_rp - qdry(ks:ke,is:ie,js:je) ) ! Qtotal
2161 
2162  call stat_total( total, rhoq(:,:,:), 'QTOT' )
2163 
2164  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
2165  do j = js, je
2166  do i = is, ie
2167  do k = ks, ke
2168  w(k,i,j) = 0.5_rp * ( momz_av(k-1,i,j)+momz_av(k,i,j) ) / dens_av(k,i,j)
2169  u(k,i,j) = 0.5_rp * ( momx_av(k,i-1,j)+momx_av(k,i,j) ) / dens_av(k,i,j)
2170  v(k,i,j) = 0.5_rp * ( momy_av(k,i,j-1)+momy_av(k,i,j) ) / dens_av(k,i,j)
2171 
2172  engp(k,i,j) = dens_av(k,i,j) * grav * real_cz(k,i,j)
2173 
2174  engk(k,i,j) = 0.5_rp * dens_av(k,i,j) * ( w(k,i,j)**2 &
2175  + u(k,i,j)**2 &
2176  + v(k,i,j)**2 )
2177 
2178  engi(k,i,j) = dens_av(k,i,j) * qdry(k,i,j) * temp(k,i,j) * cvdry
2179  do iq = 1, qa
2180  engi(k,i,j) = engi(k,i,j) &
2181  + dens_av(k,i,j) * qtrc_av(k,i,j,iq) * temp(k,i,j) * tracer_cv(iq)
2182  enddo
2183 
2184  if ( i_qv > 0 ) then
2185  engi(k,i,j) = engi(k,i,j) + dens(k,i,j) * qtrc(k,i,j,i_qv) * lhv ! Latent Heat [vapor->liquid]
2186  end if
2187 
2188  do iq = qis, qie
2189  engi(k,i,j) = engi(k,i,j) - dens_av(k,i,j) * qtrc_av(k,i,j,iq) * lhf ! Latent Heat [ice->liquid]
2190  enddo
2191 
2192  engt(k,i,j) = engp(k,i,j) + engk(k,i,j) + engi(k,i,j)
2193  enddo
2194  enddo
2195  enddo
2196 
2197  call stat_total( total, engp(:,:,:), 'ENGP' )
2198  call stat_total( total, engk(:,:,:), 'ENGK' )
2199  call stat_total( total, engi(:,:,:), 'ENGI' )
2200  call stat_total( total, engt(:,:,:), 'ENGT' )
2201 
2202  endif
2203 
2204  return
logical, public statistics_checktotal
calc&report variable totals to logfile?
real(rp), dimension(:,:,:), allocatable, target, public momz
real(rp), public const_cvdry
specific heat (dry air,constant volume) [J/kg/K]
Definition: scale_const.F90:59
real(rp), dimension(:,:,:), allocatable, target, public rhot
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
real(rp), dimension(:,:,:), allocatable, target, public momx
real(rp), dimension(:,:,:), allocatable, public real_cz
geopotential height [m] (cell center)
real(rp), dimension(:,:,:), allocatable, target, public dens
module Statistics
real(rp), dimension(:,:,:), pointer, public momx_av
module GRID (real space)
real(rp), public const_grav
standard acceleration of gravity [m/s2]
Definition: scale_const.F90:48
real(rp), dimension(:,:,:), pointer, public dens_av
real(rp), public lhf
latent heat of fusion for use [J/kg]
real(rp), public lhv
latent heat of vaporization for use [J/kg]
module CONSTANT
Definition: scale_const.F90:14
real(rp), dimension(:,:,:), allocatable, target, public momy
module ATMOSPHERE / Thermodynamics
real(rp), dimension(:,:,:), pointer, public momz_av
real(rp), dimension(:,:,:), pointer, public rhot_av
real(rp), dimension(:,:,:), pointer, public momy_av
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
Here is the caller graph for this function:

◆ atmos_vars_diagnostics()

subroutine, public mod_atmos_vars::atmos_vars_diagnostics ( )

Calc diagnostic variables.

Definition at line 2210 of file mod_atmos_vars.f90.

References scale_atmos_diagnostic::atmos_diagnostic_get(), dens_av, momx_av, momy_av, momz_av, n2, phyd, pott, pres, qtrc_av, rhot_av, temp, u, v, and w.

Referenced by mod_atmos_driver::atmos_driver(), mod_atmos_driver::atmos_driver_resume1(), and mod_rm_driver::resume_state().

2210  use scale_atmos_diagnostic, only: &
2212  implicit none
2213 
2214  call atmos_diagnostic_get( pott, temp, pres, phyd, w, u, v, n2, & ! (out)
2216 
2217  return
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
real(rp), dimension(:,:,:), pointer, public momx_av
module ATMOSPHERE / Diagnostic
subroutine, public atmos_diagnostic_get(POTT, TEMP, PRES, PHYD, W, U, V, N2, DENS, MOMZ, MOMX, MOMY, RHOT, QTRC)
real(rp), dimension(:,:,:), pointer, public dens_av
real(rp), dimension(:,:,:), allocatable, public n2
real(rp), dimension(:,:,:), pointer, public momz_av
real(rp), dimension(:,:,:), pointer, public rhot_av
real(rp), dimension(:,:,:), pointer, public momy_av
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_vars_monitor()

subroutine, public mod_atmos_vars::atmos_vars_monitor ( )

monitor output

Definition at line 2223 of file mod_atmos_vars.f90.

References mod_atmos_phy_cp_vars::atmos_phy_cp_sflx_rain, mod_atmos_phy_mp_vars::atmos_phy_mp_sflx_rain, mod_atmos_phy_mp_vars::atmos_phy_mp_sflx_snow, mod_atmos_phy_rd_vars::atmos_phy_rd_sflx_lw_dn, mod_atmos_phy_rd_vars::atmos_phy_rd_sflx_lw_up, mod_atmos_phy_rd_vars::atmos_phy_rd_sflx_sw_dn, mod_atmos_phy_rd_vars::atmos_phy_rd_sflx_sw_up, mod_atmos_phy_rd_vars::atmos_phy_rd_toaflx_lw_dn, mod_atmos_phy_rd_vars::atmos_phy_rd_toaflx_lw_up, mod_atmos_phy_rd_vars::atmos_phy_rd_toaflx_sw_dn, mod_atmos_phy_rd_vars::atmos_phy_rd_toaflx_sw_up, mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_lh, mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_qtrc, mod_atmos_phy_sf_vars::atmos_phy_sf_sflx_sh, scale_const::const_cvdry, scale_const::const_grav, dens_av, scale_grid::grid_rfdx, scale_grid::grid_rfdy, scale_gridtrans::gtrans_mapf, scale_index::i_dens, scale_index::i_momx, scale_index::i_momy, scale_index::i_momz, scale_atmos_hydrometeor::i_qv, scale_index::i_rhot, scale_gridtrans::i_uy, scale_gridtrans::i_xv, scale_grid_index::ie, scale_stdio::io_fid_log, scale_stdio::io_l, scale_grid_index::is, scale_grid_index::je, scale_grid_index::js, scale_grid_index::ke, scale_grid_index::ks, scale_atmos_hydrometeor::lhf, scale_atmos_hydrometeor::lhv, momx_av, momy_av, momz_av, scale_process::prc_myrank, scale_tracer::qa, scale_atmos_hydrometeor::qie, scale_atmos_hydrometeor::qis, qtrc_av, scale_grid_real::real_cz, rhot_av, scale_rm_statistics::stat_detail(), scale_rm_statistics::statistics_checktotal, temp, scale_time::time_dtsec_atmos_dyn, scale_tracer::tracer_cv, scale_tracer::tracer_desc, scale_tracer::tracer_mass, scale_tracer::tracer_name, scale_tracer::tracer_unit, u, v, and w.

Referenced by mod_atmos_driver::atmos_driver(), and mod_atmos_driver::atmos_driver_resume2().

2223  use scale_process, only: &
2224  prc_myrank
2225  use scale_const, only: &
2226  grav => const_grav, &
2227  cvdry => const_cvdry
2228  use scale_grid, only: &
2229  rfdx => grid_rfdx, &
2230  rfdy => grid_rfdy
2231  use scale_grid_real, only: &
2232  real_cz
2233  use scale_gridtrans, only: &
2234  mapf => gtrans_mapf, &
2235  i_uy, &
2236  i_xv
2237  use scale_comm, only: &
2238  comm_vars8, &
2239  comm_wait
2240  use scale_rm_statistics, only: &
2242  stat_total, &
2243  stat_detail
2244  use scale_monitor, only: &
2245  monit_put, &
2246  monit_in
2247  use scale_time, only: &
2249  use scale_atmos_thermodyn, only: &
2250  thermodyn_qd => atmos_thermodyn_qd, &
2251  thermodyn_temp_pres => atmos_thermodyn_temp_pres
2252  use scale_atmos_hydrometeor, only: &
2253  i_qv, &
2254  qis, &
2255  qie, &
2256  lhv, &
2257  lhf
2258  use mod_atmos_phy_cp_vars, only: &
2259  sflx_rain_cp => atmos_phy_cp_sflx_rain
2260  use mod_atmos_phy_mp_vars, only: &
2261  sflx_rain_mp => atmos_phy_mp_sflx_rain, &
2262  sflx_snow_mp => atmos_phy_mp_sflx_snow
2263  use mod_atmos_phy_rd_vars, only: &
2264  sflx_lw_up => atmos_phy_rd_sflx_lw_up, &
2265  sflx_lw_dn => atmos_phy_rd_sflx_lw_dn, &
2266  sflx_sw_up => atmos_phy_rd_sflx_sw_up, &
2267  sflx_sw_dn => atmos_phy_rd_sflx_sw_dn, &
2268  toaflx_lw_up => atmos_phy_rd_toaflx_lw_up, &
2269  toaflx_lw_dn => atmos_phy_rd_toaflx_lw_dn, &
2270  toaflx_sw_up => atmos_phy_rd_toaflx_sw_up, &
2271  toaflx_sw_dn => atmos_phy_rd_toaflx_sw_dn
2272  use mod_atmos_phy_sf_vars, only: &
2273  sflx_sh => atmos_phy_sf_sflx_sh, &
2274  sflx_lh => atmos_phy_sf_sflx_lh, &
2275  sflx_qtrc => atmos_phy_sf_sflx_qtrc
2276  implicit none
2277 
2278  real(RP) :: QDRY(KA,IA,JA) ! dry air [kg/kg]
2279  real(RP) :: RHOQ(KA,IA,JA) ! DENS * tracer [kg/m3]
2280  real(RP) :: PRCP(IA,JA) ! rain + snow [kg/m2/s]
2281 
2282  real(RP) :: ENGT(KA,IA,JA) ! total energy [J/m3]
2283  real(RP) :: ENGP(KA,IA,JA) ! potential energy [J/m3]
2284  real(RP) :: ENGK(KA,IA,JA) ! kinetic energy [J/m3]
2285  real(RP) :: ENGI(KA,IA,JA) ! internal energy [J/m3]
2286 
2287  real(RP) :: ENGFLXT (IA,JA) ! total flux [J/m2/s]
2288  real(RP) :: SFLX_RD_net (IA,JA) ! net SFC radiation flux [J/m2/s]
2289  real(RP) :: TOAFLX_RD_net(IA,JA) ! net TOA radiation flux [J/m2/s]
2290 
2291  real(RP) :: WORK (KA,IA,JA,3)
2292  character(len=H_SHORT) :: WNAME(3)
2293  real(RP) :: CFLMAX
2294 
2295  integer :: k, i, j, iq
2296  !---------------------------------------------------------------------------
2297 
2298  call monit_in( dens_av(:,:,:), var_name(i_dens), var_desc(i_dens), var_unit(i_dens), ndim=3, isflux=.false. )
2299  call monit_in( momz_av(:,:,:), var_name(i_momz), var_desc(i_momz), var_unit(i_momz), ndim=3, isflux=.false. )
2300  call monit_in( momx_av(:,:,:), var_name(i_momx), var_desc(i_momx), var_unit(i_momx), ndim=3, isflux=.false. )
2301  call monit_in( momy_av(:,:,:), var_name(i_momy), var_desc(i_momy), var_unit(i_momy), ndim=3, isflux=.false. )
2302  call monit_in( rhot_av(:,:,:), var_name(i_rhot), var_desc(i_rhot), var_unit(i_rhot), ndim=3, isflux=.false. )
2303 
2304  !##### Mass Budget #####
2305 
2306  do iq = 1, qa
2307  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
2308 !OCL XFILL
2309  do j = js, je
2310  do i = is, ie
2311  do k = ks, ke
2312  rhoq(k,i,j) = dens_av(k,i,j) * qtrc_av(k,i,j,iq)
2313  enddo
2314  enddo
2315  enddo
2316 
2317  call monit_in( rhoq(:,:,:), tracer_name(iq), tracer_desc(iq), tracer_unit(iq), ndim=3, isflux=.false. )
2318  enddo
2319 
2320  ! total dry airmass
2321 
2322  call thermodyn_qd( qdry(:,:,:), & ! [OUT]
2323  qtrc_av(:,:,:,:), & ! [IN]
2324  tracer_mass(:) ) ! [IN]
2325 
2326  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
2327 !OCL XFILL
2328  do j = js, je
2329  do i = is, ie
2330  do k = ks, ke
2331  rhoq(k,i,j) = dens_av(k,i,j) * qdry(k,i,j)
2332  enddo
2333  enddo
2334  enddo
2335  call monit_put( ad_monit_id(i_qdry), rhoq(:,:,:) )
2336 
2337  ! total vapor,liquid,solid tracers
2338  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
2339 !OCL XFILL
2340  do j = js, je
2341  do i = is, ie
2342  do k = ks, ke
2343  rhoq(k,i,j) = dens_av(k,i,j) * ( 1.0_rp - qdry(k,i,j) )
2344  enddo
2345  enddo
2346  enddo
2347  call monit_put( ad_monit_id(i_qtot), rhoq(:,:,:) )
2348 
2349  ! total evapolation
2350  if ( i_qv > 0 ) then
2351  call monit_put( ad_monit_id(i_evap), sflx_qtrc(:,:,i_qv) )
2352  endif
2353 
2354  ! total precipitation
2355 !OCL XFILL
2356  do j = js, je
2357  do i = is, ie
2358  prcp(i,j) = sflx_rain_cp(i,j) &
2359  + sflx_rain_mp(i,j) + sflx_snow_mp(i,j)
2360  enddo
2361  enddo
2362  call monit_put( ad_monit_id(i_prcp), prcp(:,:) )
2363 
2364  !##### Energy Budget #####
2365 
2366 
2367  !$omp parallel do default(none) private(i,j,k) OMP_SCHEDULE_ collapse(2) &
2368  !$omp private(iq) &
2369  !$omp shared(JS,JE,IS,IE,KS,KE,ENGP,DENS_av,GRAV,REAL_CZ,W,U,V,ENGI,ENGK,QDRY,TEMP,CVdry,QA) &
2370  !$omp shared(TRACER_CV,QTRC_av,I_QV,LHV,QIS,QIE,LHF)
2371  do j = js, je
2372  do i = is, ie
2373  do k = ks, ke
2374  engp(k,i,j) = dens_av(k,i,j) * grav * real_cz(k,i,j)
2375 
2376  engk(k,i,j) = 0.5_rp * dens_av(k,i,j) * ( w(k,i,j)**2 &
2377  + u(k,i,j)**2 &
2378  + v(k,i,j)**2 )
2379 
2380  engi(k,i,j) = dens_av(k,i,j) * qdry(k,i,j) * temp(k,i,j) * cvdry
2381  do iq = 1, qa
2382  engi(k,i,j) = engi(k,i,j) &
2383  + dens_av(k,i,j) * qtrc_av(k,i,j,iq) * temp(k,i,j) * tracer_cv(iq)
2384  enddo
2385 
2386  if ( i_qv > 0 ) then
2387  engi(k,i,j) = engi(k,i,j) + dens_av(k,i,j) * qtrc_av(k,i,j,i_qv) * lhv ! Latent Heat [vapor->liquid]
2388  end if
2389 
2390  do iq = qis, qie
2391  engi(k,i,j) = engi(k,i,j) - dens_av(k,i,j) * qtrc_av(k,i,j,iq) * lhf ! Latent Heat [ice->liquid]
2392  enddo
2393  enddo
2394  enddo
2395  enddo
2396 
2397  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
2398 !OCL XFILL
2399  do j = js, je
2400  do i = is, ie
2401  do k = ks, ke
2402  engt(k,i,j) = engp(k,i,j) + engk(k,i,j) + engi(k,i,j)
2403  enddo
2404  enddo
2405  enddo
2406 
2407 !OCL XFILL
2408  do j = js, je
2409  do i = is, ie
2410  sflx_rd_net(i,j) = ( sflx_lw_up(i,j) - sflx_lw_dn(i,j) ) &
2411  + ( sflx_sw_up(i,j) - sflx_sw_dn(i,j) )
2412 
2413  toaflx_rd_net(i,j) = ( toaflx_lw_up(i,j) - toaflx_lw_dn(i,j) ) &
2414  + ( toaflx_sw_up(i,j) - toaflx_sw_dn(i,j) )
2415  enddo
2416  enddo
2417 
2418  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
2419 !OCL XFILL
2420  do j = js, je
2421  do i = is, ie
2422  engflxt(i,j) = sflx_sh(i,j) + sflx_lh(i,j) &
2423  + sflx_rd_net(i,j) - toaflx_rd_net(i,j)
2424  enddo
2425  enddo
2426 
2427  call monit_put( ad_monit_id(i_engp), engp(:,:,:) )
2428  call monit_put( ad_monit_id(i_engk), engk(:,:,:) )
2429  call monit_put( ad_monit_id(i_engi), engi(:,:,:) )
2430  call monit_put( ad_monit_id(i_engt), engt(:,:,:) )
2431 
2432  call monit_put( ad_monit_id(i_engflxt), engflxt(:,:) )
2433 
2434 
2435  call monit_put( ad_monit_id(i_engsfc_sh), sflx_sh(:,:) )
2436  call monit_put( ad_monit_id(i_engsfc_lh), sflx_lh(:,:) )
2437  call monit_put( ad_monit_id(i_engsfc_rd), sflx_rd_net(:,:) )
2438  call monit_put( ad_monit_id(i_engtoa_rd), toaflx_rd_net(:,:) )
2439 
2440  call monit_put( ad_monit_id(i_engsfc_lw_up), sflx_lw_up(:,:) )
2441  call monit_put( ad_monit_id(i_engsfc_lw_dn), sflx_lw_dn(:,:) )
2442  call monit_put( ad_monit_id(i_engsfc_sw_up), sflx_sw_up(:,:) )
2443  call monit_put( ad_monit_id(i_engsfc_sw_dn), sflx_sw_dn(:,:) )
2444 
2445  call monit_put( ad_monit_id(i_engtoa_lw_up), toaflx_lw_up(:,:) )
2446  call monit_put( ad_monit_id(i_engtoa_lw_dn), toaflx_lw_dn(:,:) )
2447  call monit_put( ad_monit_id(i_engtoa_sw_up), toaflx_sw_up(:,:) )
2448  call monit_put( ad_monit_id(i_engtoa_sw_dn), toaflx_sw_dn(:,:) )
2449 
2450  if ( atmos_vars_checkrange ) then
2451 !OCL XFILL
2452  work(:,:,:,1) = w(:,:,:)
2453 !OCL XFILL
2454  work(:,:,:,2) = u(:,:,:)
2455 !OCL XFILL
2456  work(:,:,:,3) = v(:,:,:)
2457 
2458  wname(1) = "W"
2459  wname(2) = "U"
2460  wname(3) = "V"
2461 
2462  call stat_detail( work(:,:,:,:), wname(:) )
2463  endif
2464 
2465  if ( atmos_vars_checkcfl > 0.0_rp ) then
2466 !OCL XFILL
2467  work(:,:,:,:) = 0.0_rp
2468 
2469  do j = js, je
2470  do i = is, ie
2471  do k = ks, ke
2472  work(k,i,j,1) = 0.5_rp * abs(momz_av(k,i,j)) / ( dens_av(k+1,i,j) + dens_av(k,i,j) ) &
2473  * time_dtsec_atmos_dyn / ( real_cz(k+1,i,j) - real_cz(k,i,j) )
2474  work(k,i,j,2) = 0.5_rp * abs(momx_av(k,i,j)) / ( dens_av(k,i+1,j) + dens_av(k,i,j) ) &
2475  * time_dtsec_atmos_dyn * rfdx(i) * mapf(i,j,1,i_uy)
2476  work(k,i,j,3) = 0.5_rp * abs(momy_av(k,i,j)) / ( dens_av(k,i,j+1) + dens_av(k,i,j) ) &
2477  * time_dtsec_atmos_dyn * rfdy(j) * mapf(i,j,2,i_xv)
2478  enddo
2479  enddo
2480  enddo
2481 
2482  cflmax = maxval( work(:,:,:,:) )
2483  if ( cflmax > atmos_vars_checkcfl ) then
2484  if( io_l ) write(io_fid_log,*) "*** [ATMOS_vars_monitor] Courant number exceeded the upper limit. : ", cflmax
2485  write(*,*) "*** [ATMOS_vars_monitor] Courant number exceeded the upper limit. : ", cflmax, &
2486  ", rank = ", prc_myrank
2487 
2488  wname(1) = "Courant num. Z"
2489  wname(2) = "Courant num. X"
2490  wname(3) = "Courant num. Y"
2491 
2492  call stat_detail( work(:,:,:,:), wname(:), supress_globalcomm=.true. )
2493  endif
2494  endif
2495 
2496  return
logical, public statistics_checktotal
calc&report variable totals to logfile?
real(rp), public const_cvdry
specific heat (dry air,constant volume) [J/kg/K]
Definition: scale_const.F90:59
module Atmosphere / Physics Cumulus
real(rp), dimension(:,:,:), allocatable, public atmos_phy_sf_sflx_qtrc
module Atmosphere / Physics Cloud Microphysics
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
real(rp), dimension(:,:,:), allocatable, public real_cz
geopotential height [m] (cell center)
real(rp), dimension(:), allocatable, public grid_rfdy
reciprocal of face-dy
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_lw_up
real(rp), dimension(:,:), allocatable, public atmos_phy_mp_sflx_rain
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_sw_up
module Statistics
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_lw_dn
module Atmosphere / Physics Radiation
module ATMOSPHERIC Surface Variables
real(rp), dimension(:,:,:), pointer, public momx_av
real(rp), dimension(:,:,:,:), allocatable, public gtrans_mapf
map factor
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_sw_up
module GRIDTRANS
module GRID (real space)
integer, public i_uy
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_sw_dn
module MONITOR
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_lh
module COMMUNICATION
Definition: scale_comm.F90:23
real(rp), public const_grav
standard acceleration of gravity [m/s2]
Definition: scale_const.F90:48
module TIME
Definition: scale_time.F90:15
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_lw_dn
real(dp), public time_dtsec_atmos_dyn
time interval of dynamics [sec]
Definition: scale_time.F90:38
module PROCESS
subroutine, public stat_detail(var, varname, supress_globalcomm)
Search global maximum & minimum value.
real(rp), dimension(:,:,:), pointer, public dens_av
real(rp), public lhf
latent heat of fusion for use [J/kg]
real(rp), public lhv
latent heat of vaporization for use [J/kg]
module CONSTANT
Definition: scale_const.F90:14
integer, public prc_myrank
process num in local communicator
module GRID (cartesian)
real(rp), dimension(:,:), allocatable, public atmos_phy_mp_sflx_snow
integer, public i_xv
real(rp), dimension(:,:), allocatable, public atmos_phy_sf_sflx_sh
module ATMOSPHERE / Thermodynamics
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_sw_dn
real(rp), dimension(:,:,:), pointer, public momz_av
real(rp), dimension(:), allocatable, public grid_rfdx
reciprocal of face-dx
real(rp), dimension(:,:,:), pointer, public rhot_av
real(rp), dimension(:,:,:), pointer, public momy_av
real(rp), dimension(:,:), allocatable, public atmos_phy_cp_sflx_rain
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_lw_up
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_vars_restart_create()

subroutine, public mod_atmos_vars::atmos_vars_restart_create ( )

Create atmospheric restart file.

Definition at line 2502 of file mod_atmos_vars.f90.

References mod_atmos_dyn_vars::atmos_dyn_vars_restart_create(), mod_atmos_phy_ae_vars::atmos_phy_ae_vars_restart_create(), mod_atmos_phy_ch_vars::atmos_phy_ch_vars_restart_create(), mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_create(), mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_create(), mod_atmos_phy_rd_vars::atmos_phy_rd_vars_restart_create(), mod_atmos_phy_sf_vars::atmos_phy_sf_vars_restart_create(), mod_atmos_phy_tb_vars::atmos_phy_tb_vars_restart_create(), atmos_restart_out_basename, atmos_restart_out_dtype, atmos_restart_out_postfix_timelabel, atmos_restart_out_title, mod_atmos_admin::atmos_sw_dyn, mod_atmos_admin::atmos_sw_phy_ae, mod_atmos_admin::atmos_sw_phy_ch, mod_atmos_admin::atmos_sw_phy_cp, mod_atmos_admin::atmos_sw_phy_mp, mod_atmos_admin::atmos_sw_phy_rd, mod_atmos_admin::atmos_sw_phy_sf, mod_atmos_admin::atmos_sw_phy_tb, scale_fileio::fileio_create(), scale_stdio::io_fid_log, scale_stdio::io_l, scale_tracer::qa, scale_time::time_gettimelabel(), and scale_time::time_nowsec.

Referenced by mod_admin_restart::admin_restart_write().

2502  use scale_time, only: &
2504  use scale_fileio, only: &
2506  use mod_atmos_admin, only: &
2507  atmos_sw_dyn, &
2508  atmos_sw_phy_mp, &
2509  atmos_sw_phy_ae, &
2510  atmos_sw_phy_ch, &
2511  atmos_sw_phy_rd, &
2512  atmos_sw_phy_sf, &
2513  atmos_sw_phy_tb, &
2515  use mod_atmos_dyn_vars, only: &
2517  use mod_atmos_phy_mp_vars, only: &
2519  use mod_atmos_phy_ae_vars, only: &
2521  use mod_atmos_phy_ch_vars, only: &
2523  use mod_atmos_phy_rd_vars, only: &
2525  use mod_atmos_phy_sf_vars, only: &
2527  use mod_atmos_phy_tb_vars, only: &
2529  use mod_atmos_phy_cp_vars, only: &
2531 #ifdef SDM
2532  use scale_atmos_phy_mp_sdm, only: &
2533  sd_rest_flg_out, &
2534  atmos_phy_mp_sdm_restart_create
2535  use scale_time, only: &
2536  nowsec => time_nowsec
2537 #endif
2538  implicit none
2539 
2540  character(len=19) :: timelabel
2541  character(len=H_LONG) :: basename
2542  !---------------------------------------------------------------------------
2543 
2544 #ifdef SDM
2545  if( sd_rest_flg_out ) then
2546  if( io_l ) write(io_fid_log,*) '*** Output random number for SDM ***'
2547  call atmos_phy_mp_sdm_restart_create(nowsec)
2548  endif
2549 #endif
2550 
2551  if ( atmos_restart_out_basename /= '' ) then
2552 
2553  if( io_l ) write(io_fid_log,*)
2554  if( io_l ) write(io_fid_log,*) '*** Create restart file (ATMOS) ***'
2555 
2556  if ( atmos_restart_out_postfix_timelabel ) then
2557  call time_gettimelabel( timelabel )
2558  basename = trim(atmos_restart_out_basename)//'_'//trim(timelabel)
2559  else
2560  basename = trim(atmos_restart_out_basename)
2561  endif
2562 
2563  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
2564 
2565  call fileio_create( restart_fid, & ! [OUT]
2566  basename, atmos_restart_out_title, atmos_restart_out_dtype ) ! [IN]
2567 
2568  allocate( var_id(vmax+qa) )
2569  endif
2570 
2579 
2580  return
module ATMOS admin
subroutine, public atmos_phy_ae_vars_restart_create
Create restart file.
logical, public atmos_sw_phy_cp
module Atmosphere / Physics Cumulus
subroutine, public atmos_phy_rd_vars_restart_create
Create restart file.
logical, public atmos_sw_phy_rd
real(dp), public time_nowsec
subday part of current time [sec]
Definition: scale_time.F90:68
module Atmosphere / Physics Cloud Microphysics
module Atmosphere / Dynamics
subroutine, public atmos_phy_cp_vars_restart_create
Create restart file.
logical, public atmos_sw_phy_ae
module FILE I/O (netcdf)
subroutine, public atmos_phy_tb_vars_restart_create
Create restart file.
module Atmosphere / Physics Radiation
module ATMOSPHERIC Surface Variables
logical, public atmos_sw_phy_tb
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:90
subroutine, public atmos_phy_mp_vars_restart_create
Create restart file.
logical, public atmos_sw_dyn
subroutine, public fileio_create(fid, basename, title, datatype, date, subsec, append, nozcoord)
Create/open a netCDF file.
module TIME
Definition: scale_time.F90:15
logical, public atmos_sw_phy_sf
logical, public atmos_sw_phy_ch
module Atmosphere / Physics Turbulence
logical, public atmos_sw_phy_mp
module Atmosphere / Physics Chemistry
subroutine, public atmos_phy_sf_vars_restart_create
Create restart file.
module ATMOSPHERE / Physics Cloud Microphysics
subroutine, public atmos_phy_ch_vars_restart_create
Create restart file.
module ATMOSPHERE / Physics Aerosol Microphysics
subroutine, public atmos_dyn_vars_restart_create
Create restart file.
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_vars_restart_enddef()

subroutine, public mod_atmos_vars::atmos_vars_restart_enddef ( )

Exit netCDF define mode.

Definition at line 2586 of file mod_atmos_vars.f90.

References mod_atmos_dyn_vars::atmos_dyn_vars_restart_enddef(), mod_atmos_phy_ae_vars::atmos_phy_ae_vars_restart_enddef(), mod_atmos_phy_ch_vars::atmos_phy_ch_vars_restart_enddef(), mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_enddef(), mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_enddef(), mod_atmos_phy_rd_vars::atmos_phy_rd_vars_restart_enddef(), mod_atmos_phy_sf_vars::atmos_phy_sf_vars_restart_enddef(), mod_atmos_phy_tb_vars::atmos_phy_tb_vars_restart_enddef(), mod_atmos_admin::atmos_sw_dyn, mod_atmos_admin::atmos_sw_phy_ae, mod_atmos_admin::atmos_sw_phy_ch, mod_atmos_admin::atmos_sw_phy_cp, mod_atmos_admin::atmos_sw_phy_mp, mod_atmos_admin::atmos_sw_phy_rd, mod_atmos_admin::atmos_sw_phy_sf, mod_atmos_admin::atmos_sw_phy_tb, and scale_fileio::fileio_enddef().

Referenced by mod_admin_restart::admin_restart_write().

2586  use scale_fileio, only: &
2588  use mod_atmos_admin, only: &
2589  atmos_sw_dyn, &
2590  atmos_sw_phy_mp, &
2591  atmos_sw_phy_ae, &
2592  atmos_sw_phy_ch, &
2593  atmos_sw_phy_rd, &
2594  atmos_sw_phy_sf, &
2595  atmos_sw_phy_tb, &
2597  use mod_atmos_dyn_vars, only: &
2599  use mod_atmos_phy_mp_vars, only: &
2601  use mod_atmos_phy_ae_vars, only: &
2603  use mod_atmos_phy_ch_vars, only: &
2605  use mod_atmos_phy_rd_vars, only: &
2607  use mod_atmos_phy_sf_vars, only: &
2609  use mod_atmos_phy_tb_vars, only: &
2611  use mod_atmos_phy_cp_vars, only: &
2613 #ifdef SDM
2614  use scale_atmos_phy_mp_sdm, only: &
2615  sd_rest_flg_out, &
2616  atmos_phy_mp_sdm_restart_enddef
2617 #endif
2618  implicit none
2619 
2620  !---------------------------------------------------------------------------
2621 
2622 #ifdef SDM
2623  if( sd_rest_flg_out ) then
2624  call atmos_phy_mp_sdm_restart_enddef
2625  endif
2626 #endif
2627 
2628  if ( restart_fid /= -1 ) then
2629  call fileio_enddef( restart_fid ) ! [IN]
2630  endif
2631 
2640 
2641  return
module ATMOS admin
logical, public atmos_sw_phy_cp
subroutine, public atmos_phy_tb_vars_restart_enddef
Exit netCDF define mode.
module Atmosphere / Physics Cumulus
subroutine, public atmos_phy_cp_vars_restart_enddef
Exit netCDF define mode.
logical, public atmos_sw_phy_rd
subroutine, public atmos_phy_mp_vars_restart_enddef
Exit netCDF define mode.
module Atmosphere / Physics Cloud Microphysics
subroutine, public atmos_dyn_vars_restart_enddef
Exit netCDF define mode.
module Atmosphere / Dynamics
subroutine, public atmos_phy_ch_vars_restart_enddef
Exit netCDF define mode.
logical, public atmos_sw_phy_ae
subroutine, public atmos_phy_sf_vars_restart_enddef
Exit netCDF define mode.
module FILE I/O (netcdf)
module Atmosphere / Physics Radiation
module ATMOSPHERIC Surface Variables
logical, public atmos_sw_phy_tb
logical, public atmos_sw_dyn
logical, public atmos_sw_phy_sf
logical, public atmos_sw_phy_ch
subroutine, public atmos_phy_ae_vars_restart_enddef
Exit netCDF define mode.
module Atmosphere / Physics Turbulence
logical, public atmos_sw_phy_mp
module Atmosphere / Physics Chemistry
subroutine, public fileio_enddef(fid)
Exit netCDF file define mode.
module ATMOSPHERE / Physics Cloud Microphysics
subroutine, public atmos_phy_rd_vars_restart_enddef
Exit netCDF define mode.
module ATMOSPHERE / Physics Aerosol Microphysics
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_vars_restart_close()

subroutine, public mod_atmos_vars::atmos_vars_restart_close ( )

Close restart file.

Definition at line 2647 of file mod_atmos_vars.f90.

References mod_atmos_dyn_vars::atmos_dyn_vars_restart_close(), mod_atmos_phy_ae_vars::atmos_phy_ae_vars_restart_close(), mod_atmos_phy_ch_vars::atmos_phy_ch_vars_restart_close(), mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_close(), mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_close(), mod_atmos_phy_rd_vars::atmos_phy_rd_vars_restart_close(), mod_atmos_phy_sf_vars::atmos_phy_sf_vars_restart_close(), mod_atmos_phy_tb_vars::atmos_phy_tb_vars_restart_close(), mod_atmos_admin::atmos_sw_dyn, mod_atmos_admin::atmos_sw_phy_ae, mod_atmos_admin::atmos_sw_phy_ch, mod_atmos_admin::atmos_sw_phy_cp, mod_atmos_admin::atmos_sw_phy_mp, mod_atmos_admin::atmos_sw_phy_rd, mod_atmos_admin::atmos_sw_phy_sf, mod_atmos_admin::atmos_sw_phy_tb, scale_fileio::fileio_close(), scale_stdio::io_fid_log, and scale_stdio::io_l.

Referenced by mod_admin_restart::admin_restart_read(), and mod_admin_restart::admin_restart_write().

2647  use scale_fileio, only: &
2648  fileio_close
2649  use mod_atmos_admin, only: &
2650  atmos_sw_dyn, &
2651  atmos_sw_phy_mp, &
2652  atmos_sw_phy_ae, &
2653  atmos_sw_phy_ch, &
2654  atmos_sw_phy_rd, &
2655  atmos_sw_phy_sf, &
2656  atmos_sw_phy_tb, &
2658  use mod_atmos_dyn_vars, only: &
2660  use mod_atmos_phy_mp_vars, only: &
2662  use mod_atmos_phy_ae_vars, only: &
2664  use mod_atmos_phy_ch_vars, only: &
2666  use mod_atmos_phy_rd_vars, only: &
2668  use mod_atmos_phy_sf_vars, only: &
2670  use mod_atmos_phy_tb_vars, only: &
2672  use mod_atmos_phy_cp_vars, only: &
2674 #ifdef SDM
2675  use scale_atmos_phy_mp_sdm, only: &
2676  sd_rest_flg_out, &
2677  atmos_phy_mp_sdm_restart_close
2678 #endif
2679  implicit none
2680  !---------------------------------------------------------------------------
2681 
2682 #ifdef SDM
2683  if( sd_rest_flg_out ) then
2684  call atmos_phy_mp_sdm_restart_close
2685  endif
2686 #endif
2687 
2688  if ( restart_fid /= -1 ) then
2689  if( io_l ) write(io_fid_log,*)
2690  if( io_l ) write(io_fid_log,*) '*** Close restart file (ATMOS) ***'
2691 
2692  call fileio_close( restart_fid ) ! [IN]
2693 
2694  restart_fid = -1
2695 
2696  if ( allocated(var_id) ) deallocate( var_id )
2697  endif
2698 
2707 
2708  return
module ATMOS admin
logical, public atmos_sw_phy_cp
subroutine, public atmos_phy_rd_vars_restart_close
Close restart file.
module Atmosphere / Physics Cumulus
subroutine, public atmos_phy_ch_vars_restart_close
Close restart file.
logical, public atmos_sw_phy_rd
module Atmosphere / Physics Cloud Microphysics
module Atmosphere / Dynamics
subroutine, public atmos_dyn_vars_restart_close
Close restart file.
logical, public atmos_sw_phy_ae
module FILE I/O (netcdf)
subroutine, public atmos_phy_cp_vars_restart_close
Close restart file.
module Atmosphere / Physics Radiation
module ATMOSPHERIC Surface Variables
subroutine, public atmos_phy_sf_vars_restart_close
Close restart file.
logical, public atmos_sw_phy_tb
logical, public atmos_sw_dyn
logical, public atmos_sw_phy_sf
logical, public atmos_sw_phy_ch
module Atmosphere / Physics Turbulence
logical, public atmos_sw_phy_mp
module Atmosphere / Physics Chemistry
module ATMOSPHERE / Physics Cloud Microphysics
subroutine, public atmos_phy_mp_vars_restart_close
Close restart file.
subroutine, public fileio_close(fid)
Close a netCDF file.
subroutine, public atmos_phy_ae_vars_restart_close
Close restart file.
module ATMOSPHERE / Physics Aerosol Microphysics
subroutine, public atmos_phy_tb_vars_restart_close
Close restart file.
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_vars_restart_def_var()

subroutine, public mod_atmos_vars::atmos_vars_restart_def_var ( )

Define atmospheric variables in restart file.

Definition at line 2714 of file mod_atmos_vars.f90.

References mod_atmos_dyn_vars::atmos_dyn_vars_restart_def_var(), mod_atmos_phy_ae_vars::atmos_phy_ae_vars_restart_def_var(), mod_atmos_phy_ch_vars::atmos_phy_ch_vars_restart_def_var(), mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_def_var(), mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_def_var(), mod_atmos_phy_rd_vars::atmos_phy_rd_vars_restart_def_var(), mod_atmos_phy_sf_vars::atmos_phy_sf_vars_restart_def_var(), mod_atmos_phy_tb_vars::atmos_phy_tb_vars_restart_def_var(), atmos_restart_out_dtype, mod_atmos_admin::atmos_sw_dyn, mod_atmos_admin::atmos_sw_phy_ae, mod_atmos_admin::atmos_sw_phy_ch, mod_atmos_admin::atmos_sw_phy_cp, mod_atmos_admin::atmos_sw_phy_mp, mod_atmos_admin::atmos_sw_phy_rd, mod_atmos_admin::atmos_sw_phy_sf, mod_atmos_admin::atmos_sw_phy_tb, scale_fileio::fileio_def_var(), scale_index::i_dens, scale_index::i_momx, scale_index::i_momy, scale_index::i_momz, scale_index::i_rhot, scale_tracer::qa, scale_tracer::tracer_desc, scale_tracer::tracer_name, and scale_tracer::tracer_unit.

Referenced by mod_admin_restart::admin_restart_write().

2714  use scale_fileio, only: &
2716  use mod_atmos_admin, only: &
2717  atmos_sw_dyn, &
2718  atmos_sw_phy_mp, &
2719  atmos_sw_phy_ae, &
2720  atmos_sw_phy_ch, &
2721  atmos_sw_phy_rd, &
2722  atmos_sw_phy_sf, &
2723  atmos_sw_phy_tb, &
2725  use mod_atmos_dyn_vars, only: &
2727  use mod_atmos_phy_mp_vars, only: &
2729  use mod_atmos_phy_ae_vars, only: &
2731  use mod_atmos_phy_ch_vars, only: &
2733  use mod_atmos_phy_rd_vars, only: &
2735  use mod_atmos_phy_sf_vars, only: &
2737  use mod_atmos_phy_tb_vars, only: &
2739  use mod_atmos_phy_cp_vars, only: &
2741 #ifdef SDM
2742  use scale_atmos_phy_mp_sdm, only: &
2743  sd_rest_flg_out, &
2744  atmos_phy_mp_sdm_restart_def_var
2745 #endif
2746  implicit none
2747 
2748  integer iq
2749  !---------------------------------------------------------------------------
2750 
2751 #ifdef SDM
2752  if( sd_rest_flg_out ) then
2753  call atmos_phy_mp_sdm_restart_def_var
2754  endif
2755 #endif
2756 
2757  if ( restart_fid /= -1 ) then
2758 
2759  call fileio_def_var( restart_fid, var_id(i_dens), var_name(i_dens), var_desc(i_dens), & ! [IN]
2760  var_unit(i_dens), 'ZXY', atmos_restart_out_dtype ) ! [IN]
2761  call fileio_def_var( restart_fid, var_id(i_momz), var_name(i_momz), var_desc(i_momz), & ! [IN]
2762  var_unit(i_momz), 'ZHXY', atmos_restart_out_dtype ) ! [IN]
2763  call fileio_def_var( restart_fid, var_id(i_momx), var_name(i_momx), var_desc(i_momx), & ! [IN]
2764  var_unit(i_momx), 'ZXHY', atmos_restart_out_dtype ) ! [IN]
2765  call fileio_def_var( restart_fid, var_id(i_momy), var_name(i_momy), var_desc(i_momy), & ! [IN]
2766  var_unit(i_momy), 'ZXYH', atmos_restart_out_dtype ) ! [IN]
2767  call fileio_def_var( restart_fid, var_id(i_rhot), var_name(i_rhot), var_desc(i_rhot), & ! [IN]
2768  var_unit(i_rhot), 'ZXY', atmos_restart_out_dtype ) ! [IN]
2769 
2770  do iq = 1, qa
2771  call fileio_def_var( restart_fid, var_id(vmax+iq), tracer_name(iq), tracer_desc(iq), & ! [IN]
2772  tracer_unit(iq), 'ZXY', atmos_restart_out_dtype ) ! [IN]
2773  enddo
2774 
2775  endif
2776 
2785 
2786  return
module ATMOS admin
subroutine, public atmos_phy_sf_vars_restart_def_var
Write restart.
subroutine, public atmos_dyn_vars_restart_def_var
Define variables in restart file.
subroutine, public atmos_phy_cp_vars_restart_def_var
Write restart.
logical, public atmos_sw_phy_cp
module Atmosphere / Physics Cumulus
logical, public atmos_sw_phy_rd
module Atmosphere / Physics Cloud Microphysics
module Atmosphere / Dynamics
subroutine, public atmos_phy_ch_vars_restart_def_var
Write restart.
subroutine, public atmos_phy_mp_vars_restart_def_var
Define variables in restart file.
logical, public atmos_sw_phy_ae
module FILE I/O (netcdf)
module Atmosphere / Physics Radiation
module ATMOSPHERIC Surface Variables
logical, public atmos_sw_phy_tb
subroutine, public atmos_phy_rd_vars_restart_def_var
Define variables in restart file.
logical, public atmos_sw_dyn
logical, public atmos_sw_phy_sf
logical, public atmos_sw_phy_ch
module Atmosphere / Physics Turbulence
logical, public atmos_sw_phy_mp
module Atmosphere / Physics Chemistry
module ATMOSPHERE / Physics Cloud Microphysics
subroutine, public atmos_phy_tb_vars_restart_def_var
Write restart.
subroutine, public fileio_def_var(fid, vid, varname, desc, unit, axistype, datatype, timeintv, nsteps)
Define a variable to file.
subroutine, public atmos_phy_ae_vars_restart_def_var
Write restart.
module ATMOSPHERE / Physics Aerosol Microphysics
Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_vars_restart_write()

subroutine, public mod_atmos_vars::atmos_vars_restart_write ( )

Write restart of atmospheric variables.

Definition at line 2792 of file mod_atmos_vars.f90.

References mod_atmos_dyn_vars::atmos_dyn_vars_restart_write(), mod_atmos_phy_ae_vars::atmos_phy_ae_vars_restart_write(), mod_atmos_phy_ch_vars::atmos_phy_ch_vars_restart_write(), mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_write(), mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_write(), mod_atmos_phy_rd_vars::atmos_phy_rd_vars_restart_write(), mod_atmos_phy_sf_vars::atmos_phy_sf_vars_restart_write(), mod_atmos_phy_tb_vars::atmos_phy_tb_vars_restart_write(), mod_atmos_admin::atmos_sw_dyn, mod_atmos_admin::atmos_sw_phy_ae, mod_atmos_admin::atmos_sw_phy_ch, mod_atmos_admin::atmos_sw_phy_cp, mod_atmos_admin::atmos_sw_phy_mp, mod_atmos_admin::atmos_sw_phy_rd, mod_atmos_admin::atmos_sw_phy_sf, mod_atmos_admin::atmos_sw_phy_tb, atmos_vars_fillhalo(), atmos_vars_total(), dens, scale_index::i_dens, scale_index::i_momx, scale_index::i_momy, scale_index::i_momz, scale_index::i_rhot, momx, momy, momz, scale_tracer::qa, qtrc, rhot, and scale_tracer::tracer_name.

Referenced by mod_admin_restart::admin_restart_write().

2792  use scale_fileio, only: &
2793  fileio_write_var
2794  use mod_atmos_admin, only: &
2795  atmos_sw_dyn, &
2796  atmos_sw_phy_mp, &
2797  atmos_sw_phy_ae, &
2798  atmos_sw_phy_ch, &
2799  atmos_sw_phy_rd, &
2800  atmos_sw_phy_sf, &
2801  atmos_sw_phy_tb, &
2803  use mod_atmos_dyn_vars, only: &
2805  use mod_atmos_phy_mp_vars, only: &
2807  use mod_atmos_phy_ae_vars, only: &
2809  use mod_atmos_phy_ch_vars, only: &
2811  use mod_atmos_phy_rd_vars, only: &
2813  use mod_atmos_phy_sf_vars, only: &
2815  use mod_atmos_phy_tb_vars, only: &
2817  use mod_atmos_phy_cp_vars, only: &
2819 #ifdef SDM
2820  use scale_atmos_phy_mp_sdm, only: &
2821  sd_rest_flg_out, &
2822  atmos_phy_mp_sdm_restart_write
2823 #endif
2824  implicit none
2825 
2826  integer iq
2827  !---------------------------------------------------------------------------
2828 
2829 #ifdef SDM
2830  if( sd_rest_flg_out ) then
2831  call atmos_phy_mp_sdm_restart_write
2832  endif
2833 #endif
2834 
2835  if ( restart_fid /= -1 ) then
2836 
2837  call atmos_vars_fillhalo
2838 
2839  call atmos_vars_total
2840 
2841  call fileio_write_var( restart_fid, var_id(i_dens), dens(:,:,:), var_name(i_dens), 'ZXY' ) ! [IN]
2842  call fileio_write_var( restart_fid, var_id(i_momz), momz(:,:,:), var_name(i_momz), 'ZHXY' ) ! [IN]
2843  call fileio_write_var( restart_fid, var_id(i_momx), momx(:,:,:), var_name(i_momx), 'ZXHY' ) ! [IN]
2844  call fileio_write_var( restart_fid, var_id(i_momy), momy(:,:,:), var_name(i_momy), 'ZXYH' ) ! [IN]
2845  call fileio_write_var( restart_fid, var_id(i_rhot), rhot(:,:,:), var_name(i_rhot), 'ZXY' ) ! [IN]
2846 
2847  do iq = 1, qa
2848  call fileio_write_var( restart_fid, var_id(vmax+iq), qtrc(:,:,:,iq), tracer_name(iq), 'ZXY' ) ! [IN]
2849  enddo
2850 
2851  endif
2852 
2861 
2862  return
module ATMOS admin
logical, public atmos_sw_phy_cp
real(rp), dimension(:,:,:), allocatable, target, public momz
module Atmosphere / Physics Cumulus
logical, public atmos_sw_phy_rd
real(rp), dimension(:,:,:), allocatable, target, public rhot
module Atmosphere / Physics Cloud Microphysics
subroutine, public atmos_phy_cp_vars_restart_write
Write restart.
module Atmosphere / Dynamics
subroutine, public atmos_phy_tb_vars_restart_write
Write restart.
real(rp), dimension(:,:,:), allocatable, target, public momx
logical, public atmos_sw_phy_ae
real(rp), dimension(:,:,:), allocatable, target, public dens
subroutine, public atmos_dyn_vars_restart_write
Write variables to restart file.
module FILE I/O (netcdf)
module Atmosphere / Physics Radiation
module ATMOSPHERIC Surface Variables
subroutine, public atmos_phy_sf_vars_restart_write
Write variables to restart file.
logical, public atmos_sw_phy_tb
logical, public atmos_sw_dyn
logical, public atmos_sw_phy_sf
logical, public atmos_sw_phy_ch
module Atmosphere / Physics Turbulence
logical, public atmos_sw_phy_mp
subroutine, public atmos_phy_rd_vars_restart_write
Write variables to restart file.
real(rp), dimension(:,:,:), allocatable, target, public momy
module Atmosphere / Physics Chemistry
subroutine, public atmos_phy_mp_vars_restart_write
Write restart.
module ATMOSPHERE / Physics Cloud Microphysics
subroutine, public atmos_phy_ae_vars_restart_write
Write restart.
subroutine, public atmos_phy_ch_vars_restart_write
Write restart.
module ATMOSPHERE / Physics Aerosol Microphysics
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ atmos_restart_output

logical, public mod_atmos_vars::atmos_restart_output = .false.

Output restart file?

Definition at line 58 of file mod_atmos_vars.f90.

Referenced by mod_admin_restart::admin_restart_setup(), mod_admin_restart::admin_restart_write(), and atmos_vars_setup().

58  logical, public :: ATMOS_RESTART_OUTPUT = .false.

◆ atmos_restart_in_basename

character(len=h_long), public mod_atmos_vars::atmos_restart_in_basename = ''

Basename of the input file.

Definition at line 60 of file mod_atmos_vars.f90.

Referenced by mod_admin_restart::admin_restart_setup(), mod_admin_time::admin_time_setup(), atmos_vars_restart_open(), and atmos_vars_setup().

60  character(len=H_LONG), public :: ATMOS_RESTART_IN_BASENAME = ''

◆ atmos_restart_in_postfix_timelabel

logical, public mod_atmos_vars::atmos_restart_in_postfix_timelabel = .false.

Add timelabel to the basename of input file?

Definition at line 61 of file mod_atmos_vars.f90.

Referenced by mod_admin_restart::admin_restart_setup(), atmos_vars_restart_open(), and atmos_vars_setup().

61  logical, public :: ATMOS_RESTART_IN_POSTFIX_TIMELABEL = .false.

◆ atmos_restart_out_basename

character(len=h_long), public mod_atmos_vars::atmos_restart_out_basename = ''

Basename of the output file.

Definition at line 62 of file mod_atmos_vars.f90.

Referenced by mod_admin_restart::admin_restart_setup(), atmos_vars_restart_create(), and atmos_vars_setup().

62  character(len=H_LONG), public :: ATMOS_RESTART_OUT_BASENAME = ''

◆ atmos_restart_out_postfix_timelabel

logical, public mod_atmos_vars::atmos_restart_out_postfix_timelabel = .true.

Add timelabel to the basename of output file?

Definition at line 63 of file mod_atmos_vars.f90.

Referenced by mod_admin_restart::admin_restart_setup(), atmos_vars_restart_create(), and atmos_vars_setup().

63  logical, public :: ATMOS_RESTART_OUT_POSTFIX_TIMELABEL = .true.

◆ atmos_restart_out_title

character(len=h_mid), public mod_atmos_vars::atmos_restart_out_title = 'ATMOS restart'

Title of the output file.

Definition at line 64 of file mod_atmos_vars.f90.

Referenced by mod_admin_restart::admin_restart_setup(), atmos_vars_restart_create(), and atmos_vars_setup().

64  character(len=H_MID), public :: ATMOS_RESTART_OUT_TITLE = 'ATMOS restart'

◆ atmos_restart_out_dtype

character(len=h_short), public mod_atmos_vars::atmos_restart_out_dtype = 'DEFAULT'

REAL4 or REAL8.

Definition at line 65 of file mod_atmos_vars.f90.

Referenced by mod_admin_restart::admin_restart_setup(), atmos_vars_restart_create(), atmos_vars_restart_def_var(), and atmos_vars_setup().

65  character(len=H_SHORT), public :: ATMOS_RESTART_OUT_DTYPE = 'DEFAULT'

◆ atmos_restart_check

logical, public mod_atmos_vars::atmos_restart_check = .false.

Check value consistency?

Definition at line 67 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup(), and mod_rm_driver::scalerm().

67  logical, public :: ATMOS_RESTART_CHECK = .false.

◆ atmos_restart_check_basename

character(len=h_long), public mod_atmos_vars::atmos_restart_check_basename = 'restart_check'

Definition at line 68 of file mod_atmos_vars.f90.

Referenced by atmos_vars_restart_check(), and atmos_vars_setup().

68  character(len=H_LONG), public :: ATMOS_RESTART_CHECK_BASENAME = 'restart_check'

◆ atmos_restart_check_criterion

real(rp), public mod_atmos_vars::atmos_restart_check_criterion = 1.E-6_RP

Definition at line 69 of file mod_atmos_vars.f90.

Referenced by atmos_vars_restart_check(), and atmos_vars_setup().

69  real(RP), public :: ATMOS_RESTART_CHECK_CRITERION = 1.e-6_rp

◆ dens

real(rp), dimension(:,:,:), allocatable, target, public mod_atmos_vars::dens

◆ momz

real(rp), dimension(:,:,:), allocatable, target, public mod_atmos_vars::momz

◆ momx

real(rp), dimension(:,:,:), allocatable, target, public mod_atmos_vars::momx

◆ momy

real(rp), dimension(:,:,:), allocatable, target, public mod_atmos_vars::momy

◆ rhot

real(rp), dimension(:,:,:), allocatable, target, public mod_atmos_vars::rhot

◆ qtrc

real(rp), dimension(:,:,:,:), allocatable, target, public mod_atmos_vars::qtrc

◆ dens_avw

real(rp), dimension(:,:,:), allocatable, target, public mod_atmos_vars::dens_avw

Definition at line 79 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup().

79  real(RP), public, target, allocatable :: DENS_avw(:,:,:)

◆ momz_avw

real(rp), dimension(:,:,:), allocatable, target, public mod_atmos_vars::momz_avw

Definition at line 80 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup().

80  real(RP), public, target, allocatable :: MOMZ_avw(:,:,:)

◆ momx_avw

real(rp), dimension(:,:,:), allocatable, target, public mod_atmos_vars::momx_avw

Definition at line 81 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup().

81  real(RP), public, target, allocatable :: MOMX_avw(:,:,:)

◆ momy_avw

real(rp), dimension(:,:,:), allocatable, target, public mod_atmos_vars::momy_avw

Definition at line 82 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup().

82  real(RP), public, target, allocatable :: MOMY_avw(:,:,:)

◆ rhot_avw

real(rp), dimension(:,:,:), allocatable, target, public mod_atmos_vars::rhot_avw

Definition at line 83 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup().

83  real(RP), public, target, allocatable :: RHOT_avw(:,:,:)

◆ qtrc_avw

real(rp), dimension(:,:,:,:), allocatable, target, public mod_atmos_vars::qtrc_avw

Definition at line 84 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup().

84  real(RP), public, target, allocatable :: QTRC_avw(:,:,:,:)

◆ dens_av

real(rp), dimension(:,:,:), pointer, public mod_atmos_vars::dens_av

◆ momz_av

real(rp), dimension(:,:,:), pointer, public mod_atmos_vars::momz_av

◆ momx_av

real(rp), dimension(:,:,:), pointer, public mod_atmos_vars::momx_av

◆ momy_av

real(rp), dimension(:,:,:), pointer, public mod_atmos_vars::momy_av

◆ rhot_av

real(rp), dimension(:,:,:), pointer, public mod_atmos_vars::rhot_av

◆ qtrc_av

real(rp), dimension(:,:,:,:), pointer, public mod_atmos_vars::qtrc_av

◆ dens_tp

real(rp), dimension(:,:,:), allocatable, public mod_atmos_vars::dens_tp

◆ momz_tp

real(rp), dimension(:,:,:), allocatable, public mod_atmos_vars::momz_tp

◆ momx_tp

real(rp), dimension(:,:,:), allocatable, public mod_atmos_vars::momx_tp

◆ momy_tp

real(rp), dimension(:,:,:), allocatable, public mod_atmos_vars::momy_tp

◆ rhot_tp

real(rp), dimension(:,:,:), allocatable, public mod_atmos_vars::rhot_tp

◆ rhoq_tp

real(rp), dimension(:,:,:,:), allocatable, public mod_atmos_vars::rhoq_tp

◆ pott

real(rp), dimension(:,:,:), allocatable, public mod_atmos_vars::pott

Definition at line 102 of file mod_atmos_vars.f90.

Referenced by atmos_vars_diagnostics(), atmos_vars_history(), and atmos_vars_setup().

102  real(RP), public, allocatable :: POTT(:,:,:) ! potential temperature [K]

◆ temp

real(rp), dimension(:,:,:), allocatable, public mod_atmos_vars::temp

◆ pres

real(rp), dimension(:,:,:), allocatable, public mod_atmos_vars::pres

◆ phyd

real(rp), dimension(:,:,:), allocatable, public mod_atmos_vars::phyd

Definition at line 105 of file mod_atmos_vars.f90.

Referenced by atmos_vars_diagnostics(), atmos_vars_history_setpres(), and atmos_vars_setup().

105  real(RP), public, allocatable :: PHYD(:,:,:) ! hydrostatic pressure [Pa=J/m3]

◆ w

real(rp), dimension (:,:,:), allocatable, public mod_atmos_vars::w

◆ u

real(rp), dimension (:,:,:), allocatable, public mod_atmos_vars::u

◆ v

real(rp), dimension (:,:,:), allocatable, public mod_atmos_vars::v

◆ n2

real(rp), dimension (:,:,:), allocatable, public mod_atmos_vars::n2

Definition at line 109 of file mod_atmos_vars.f90.

Referenced by mod_atmos_phy_tb_driver::atmos_phy_tb_driver(), atmos_vars_diagnostics(), atmos_vars_history(), and atmos_vars_setup().

109  real(RP), public, allocatable :: N2 (:,:,:) ! squared Brunt-Vaisala frequency [/s2]