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_read
 Read restart of atmospheric variables. More...
 
subroutine, public atmos_vars_restart_write
 Write restart of atmospheric variables. 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_var
 Write restart of atmospheric variables. More...
 

Variables

logical, public atmos_restart_output = .false.
 output restart file? More...
 
logical, public atmos_restart_check = .false.
 check value consistency? More...
 
character(len=h_long), public atmos_restart_in_basename = ''
 basename of the restart file More...
 
character(len=h_long), public atmos_restart_out_basename = ''
 basename of the output file More...
 
character(len=h_mid), public atmos_restart_out_title = 'ATMOS restart'
 title of the output file More...
 
character(len=h_mid), public atmos_restart_out_dtype = 'DEFAULT'
 REAL4 or REAL8. More...
 
logical, public atmos_restart_in_allowmissingq = .false.
 
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 temp
 
real(rp), dimension(:,:,:), allocatable, public pres
 
real(rp), dimension(:,:,:), allocatable, public w
 
real(rp), dimension(:,:,:), allocatable, public u
 
real(rp), dimension(:,:,:), allocatable, public v
 
real(rp), dimension(:,:,:), allocatable, public pott
 

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 restart file
    ATMOS_RESTART_IN_ALLOWMISSINGQ logical .false.
    ATMOS_RESTART_OUTPUT logical .false. output restart file?
    ATMOS_RESTART_OUT_BASENAME character(len=H_LONG) '' basename of the output file
    ATMOS_RESTART_OUT_TITLE character(len=H_MID) 'ATMOS restart' title of the output file
    ATMOS_RESTART_OUT_DTYPE character(len=H_MID) '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
AQ_NAME(iq) AQ_DESC(iq) AQ_UNIT(iq) QTRC
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
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
RH relative humidity(liq) % RHL
RHA relative humidity(liq+ice) % RHA
RHI relative humidity(ice) % RHI
RTOT Total gas constant J/kg/K RTOT
T temperature K TEMP
TKE_RS resolved scale TKE m2/s2 TKE_RS
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 247 of file mod_atmos_vars.f90.

References scale_tracer::aq_desc, scale_tracer::aq_name, scale_tracer::aq_unit, 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_allowmissingq, atmos_restart_in_basename, atmos_restart_out_basename, atmos_restart_out_dtype, 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_l, scale_stdio::io_lnml, 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(), pott, scale_process::prc_mpistop(), pres, scale_tracer::qa, qtrc, qtrc_av, qtrc_avw, rhoq_tp, rhot, rhot_av, rhot_avw, rhot_tp, temp, u, v, and w.

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

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

801  use scale_comm, only: &
802  comm_vars8, &
803  comm_wait
804  implicit none
805 
806  logical, intent(in), optional :: fill_bnd
807 
808  logical :: fill_bnd_
809  integer :: i, j, iq
810  !---------------------------------------------------------------------------
811 
812  fill_bnd_ = .false.
813  if ( present(fill_bnd) ) fill_bnd_ = fill_bnd
814 
815  !$omp parallel do private(i,j) OMP_SCHEDULE_ collapse(2)
816  do j = jsb, jeb
817  do i = isb, ieb
818  dens( 1:ks-1,i,j) = dens(ks,i,j)
819  momz( 1:ks-1,i,j) = momz(ks,i,j)
820  momx( 1:ks-1,i,j) = momx(ks,i,j)
821  momy( 1:ks-1,i,j) = momy(ks,i,j)
822  rhot( 1:ks-1,i,j) = rhot(ks,i,j)
823  dens(ke+1:ka, i,j) = dens(ke,i,j)
824  momz(ke+1:ka, i,j) = momz(ke,i,j)
825  momx(ke+1:ka, i,j) = momx(ke,i,j)
826  momy(ke+1:ka, i,j) = momy(ke,i,j)
827  rhot(ke+1:ka, i,j) = rhot(ke,i,j)
828  enddo
829  enddo
830 
831  !$omp parallel do private(i,j,iq) OMP_SCHEDULE_ collapse(3)
832  do iq = 1, qa
833  do j = jsb, jeb
834  do i = isb, ieb
835  qtrc( 1:ks-1,i,j,iq) = qtrc(ks,i,j,iq)
836  qtrc(ke+1:ka, i,j,iq) = qtrc(ke,i,j,iq)
837  enddo
838  enddo
839  enddo
840 
841  call comm_vars8( dens(:,:,:), 1 )
842  call comm_vars8( momz(:,:,:), 2 )
843  call comm_vars8( momx(:,:,:), 3 )
844  call comm_vars8( momy(:,:,:), 4 )
845  call comm_vars8( rhot(:,:,:), 5 )
846  call comm_wait ( dens(:,:,:), 1, fill_bnd_ )
847  call comm_wait ( momz(:,:,:), 2, fill_bnd_ )
848  call comm_wait ( momx(:,:,:), 3, fill_bnd_ )
849  call comm_wait ( momy(:,:,:), 4, fill_bnd_ )
850  call comm_wait ( rhot(:,:,:), 5, fill_bnd_ )
851 
852  do iq = 1, qa
853  call comm_vars8( qtrc(:,:,:,iq), iq )
854  enddo
855  do iq = 1, qa
856  call comm_wait ( qtrc(:,:,:,iq), iq, fill_bnd_ )
857  enddo
858 
859  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_read()

subroutine, public mod_atmos_vars::atmos_vars_restart_read ( )

Read restart of atmospheric variables.

Definition at line 865 of file mod_atmos_vars.f90.

References scale_tracer::aq_name, 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(), atmos_restart_in_basename, 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(), scale_const::const_grav, dens, dens_av, scale_stdio::io_fid_log, scale_stdio::io_l, momx, momx_av, momy, momy_av, momz, momz_av, scale_process::prc_mpistop(), scale_tracer::qa, qtrc, qtrc_av, rhot, and rhot_av.

Referenced by mod_rm_driver::resume_state().

865  use scale_process, only: &
867  use scale_const, only: &
868  grav => const_grav
869  use scale_fileio, only: &
870  fileio_read
871  use scale_atmos_thermodyn, only: &
872  thermodyn_qd => atmos_thermodyn_qd, &
873  thermodyn_temp_pres => atmos_thermodyn_temp_pres
874  use mod_atmos_admin, only: &
876  atmos_sw_dyn, &
877  atmos_sw_phy_mp, &
878  atmos_sw_phy_ae, &
879  atmos_sw_phy_ch, &
880  atmos_sw_phy_rd, &
881  atmos_sw_phy_sf, &
882  atmos_sw_phy_tb, &
884  use mod_atmos_dyn_vars, only: &
886  use mod_atmos_phy_mp_vars, only: &
888  use mod_atmos_phy_ae_vars, only: &
890  use mod_atmos_phy_ch_vars, only: &
892  use mod_atmos_phy_rd_vars, only: &
894  use mod_atmos_phy_sf_vars, only: &
896  use mod_atmos_phy_tb_vars, only: &
898  use mod_atmos_phy_cp_vars, only: &
900  implicit none
901 
902  integer :: iq
903  !---------------------------------------------------------------------------
904 
905  if( io_l ) write(io_fid_log,*)
906  if( io_l ) write(io_fid_log,*) '*** Input restart file (ATMOS) ***'
907 
908  if ( atmos_restart_in_basename /= '' ) then
909  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(atmos_restart_in_basename)
910 
911  call fileio_read( dens(:,:,:), & ! [OUT]
912  atmos_restart_in_basename, var_name(1), 'ZXY', step=1 ) ! [IN]
913  call fileio_read( momz(:,:,:), & ! [OUT]
914  atmos_restart_in_basename, var_name(2), 'ZXY', step=1 ) ! [IN]
915  call fileio_read( momx(:,:,:), & ! [OUT]
916  atmos_restart_in_basename, var_name(3), 'ZXY', step=1 ) ! [IN]
917  call fileio_read( momy(:,:,:), & ! [OUT]
918  atmos_restart_in_basename, var_name(4), 'ZXY', step=1 ) ! [IN]
919  call fileio_read( rhot(:,:,:), & ! [OUT]
920  atmos_restart_in_basename, var_name(5), 'ZXY', step=1 ) ! [IN]
921 
922  do iq = 1, qa
923  call fileio_read( qtrc(:,:,:,iq), & ! [OUT]
924  atmos_restart_in_basename, aq_name(iq), 'ZXY', step=1 ) ! [IN]
925  enddo
926 
927  call atmos_vars_fillhalo
928 
929  call atmos_vars_total
930  else
931  write(*,*) '*** restart file for atmosphere is not specified. STOP!'
932  call prc_mpistop
933  endif
934 
935  if ( atmos_use_average ) then
936  dens_av(:,:,:) = dens(:,:,:)
937  momz_av(:,:,:) = momz(:,:,:)
938  momx_av(:,:,:) = momx(:,:,:)
939  momy_av(:,:,:) = momy(:,:,:)
940  rhot_av(:,:,:) = rhot(:,:,:)
941  qtrc_av(:,:,:,:) = qtrc(:,:,:,:)
942  endif
943 
952 
953  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
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
real(rp), public const_grav
standard acceleration of gravity [m/s2]
Definition: scale_const.F90:48
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
module CONSTANT
Definition: scale_const.F90:14
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_restart_write()

subroutine, public mod_atmos_vars::atmos_vars_restart_write ( )

Write restart of atmospheric variables.

Definition at line 959 of file mod_atmos_vars.f90.

References scale_tracer::aq_desc, scale_tracer::aq_name, scale_tracer::aq_unit, 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(), atmos_restart_out_basename, atmos_restart_out_dtype, 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, 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, scale_stdio::io_fid_log, scale_stdio::io_l, momx, momy, momz, scale_tracer::qa, qtrc, rhot, scale_time::time_gettimelabel(), and scale_time::time_nowsec.

Referenced by mod_mkinit::mkinit(), and mod_rm_driver::scalerm().

959  use scale_time, only: &
961  use scale_fileio, only: &
962  fileio_write
963  use mod_atmos_admin, only: &
964  atmos_sw_dyn, &
965  atmos_sw_phy_mp, &
966  atmos_sw_phy_ae, &
967  atmos_sw_phy_ch, &
968  atmos_sw_phy_rd, &
969  atmos_sw_phy_sf, &
970  atmos_sw_phy_tb, &
972  use mod_atmos_dyn_vars, only: &
974  use mod_atmos_phy_mp_vars, only: &
976  use mod_atmos_phy_ae_vars, only: &
978  use mod_atmos_phy_ch_vars, only: &
980  use mod_atmos_phy_rd_vars, only: &
982  use mod_atmos_phy_sf_vars, only: &
984  use mod_atmos_phy_tb_vars, only: &
986  use mod_atmos_phy_cp_vars, only: &
988 #ifdef _SDM
989  use scale_atmos_phy_mp_sdm, only: &
990  sd_rest_flg_out, &
991  atmos_phy_mp_sdm_restart_out
992  use scale_time, only: &
993  nowsec => time_nowsec
994 #endif
995  implicit none
996 
997  character(len=20) :: timelabel
998  character(len=H_LONG) :: basename
999 
1000  integer :: iq
1001  !---------------------------------------------------------------------------
1002 
1003 #ifdef _SDM
1004  if( sd_rest_flg_out ) then
1005  if( io_l ) write(io_fid_log,*) '*** Output random number for SDM ***'
1006  call atmos_phy_mp_sdm_restart_out(nowsec)
1007  endif
1008 #endif
1009 
1010  if ( atmos_restart_out_basename /= '' ) then
1011 
1012  call time_gettimelabel( timelabel )
1013  write(basename,'(A,A,A)') trim(atmos_restart_out_basename), '_', trim(timelabel)
1014 
1015  if( io_l ) write(io_fid_log,*)
1016  if( io_l ) write(io_fid_log,*) '*** Output restart file (ATMOS) ***'
1017  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
1018 
1019  call atmos_vars_fillhalo
1020 
1021  call atmos_vars_total
1022 
1023  call fileio_write( dens(:,:,:), basename, atmos_restart_out_title, & ! [IN]
1024  var_name(i_dens), var_desc(i_dens), var_unit(i_dens), 'ZXY', atmos_restart_out_dtype ) ! [IN]
1025  call fileio_write( momz(:,:,:), basename, atmos_restart_out_title, & ! [IN]
1026  var_name(i_momz), var_desc(i_momz), var_unit(i_momz), 'ZHXY', atmos_restart_out_dtype ) ! [IN]
1027  call fileio_write( momx(:,:,:), basename, atmos_restart_out_title, & ! [IN]
1028  var_name(i_momx), var_desc(i_momx), var_unit(i_momx), 'ZXHY', atmos_restart_out_dtype ) ! [IN]
1029  call fileio_write( momy(:,:,:), basename, atmos_restart_out_title, & ! [IN]
1030  var_name(i_momy), var_desc(i_momy), var_unit(i_momy), 'ZXYH', atmos_restart_out_dtype ) ! [IN]
1031  call fileio_write( rhot(:,:,:), basename, atmos_restart_out_title, & ! [IN]
1032  var_name(i_rhot), var_desc(i_rhot), var_unit(i_rhot), 'ZXY', atmos_restart_out_dtype ) ! [IN]
1033 
1034  do iq = 1, qa
1035  call fileio_write( qtrc(:,:,:,iq), basename, atmos_restart_out_title, & ! [IN]
1036  aq_name(iq), aq_desc(iq), aq_unit(iq), 'ZXY', atmos_restart_out_dtype ) ! [IN]
1037  enddo
1038 
1039  endif
1040 
1049 
1050  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
real(dp), public time_nowsec
subday part of current time [sec]
Definition: scale_time.F90:68
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 restart.
module FILE I/O (netcdf)
module Atmosphere / Physics Radiation
module ATMOSPHERIC Surface Variables
subroutine, public atmos_phy_sf_vars_restart_write
Write restart.
logical, public atmos_sw_phy_tb
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:90
logical, public atmos_sw_dyn
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
subroutine, public atmos_phy_rd_vars_restart_write
Write restart.
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:

◆ 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 1056 of file mod_atmos_vars.f90.

References scale_tracer::aq_name, atmos_restart_check_basename, atmos_restart_check_criterion, dens, scale_grid_index::ie, scale_grid_index::imax, scale_stdio::io_fid_log, scale_stdio::io_l, scale_grid_index::is, scale_grid_index::je, scale_grid_index::jmax, scale_grid_index::js, scale_grid_index::ke, scale_grid_index::kmax, scale_grid_index::ks, momx, momy, momz, scale_process::prc_myrank, scale_prof::prof_rapend(), scale_prof::prof_rapstart(), scale_tracer::qa, qtrc, and rhot.

Referenced by mod_rm_driver::scalerm().

1056  use scale_process, only: &
1057  prc_myrank
1058  use gtool_file, only: &
1059  fileread
1060  implicit none
1061 
1062  real(RP) :: dens_check(ka,ia,ja) ! Density [kg/m3]
1063  real(RP) :: momz_check(ka,ia,ja) ! momentum z [kg/s/m2]
1064  real(RP) :: momx_check(ka,ia,ja) ! momentum x [kg/s/m2]
1065  real(RP) :: momy_check(ka,ia,ja) ! momentum y [kg/s/m2]
1066  real(RP) :: rhot_check(ka,ia,ja) ! DENS * POTT [K*kg/m3]
1067  real(RP) :: qtrc_check(ka,ia,ja,qa) ! tracer mixing ratio [kg/kg]
1068 
1069  real(RP) :: restart_atmos(kmax,imax,jmax)
1070 
1071  character(len=H_LONG) :: basename
1072 
1073  logical :: datacheck
1074  integer :: k, i, j, iq
1075  !---------------------------------------------------------------------------
1076 
1077  call prof_rapstart('Debug')
1078 
1079  write(*,*) 'Compare last Data with ', trim(atmos_restart_check_basename), 'on PE=', prc_myrank
1080  write(*,*) '*** criterion = ', atmos_restart_check_criterion
1081  datacheck = .true.
1082 
1083  basename = atmos_restart_check_basename
1084 
1085  call fileread( restart_atmos(:,:,:), basename, 'DENS', 1, prc_myrank )
1086  dens_check(ks:ke,is:ie,js:je) = restart_atmos(1:kmax,1:imax,1:jmax)
1087  do k = ks, ke
1088  do j = js, je
1089  do i = is, ie
1090  if ( abs( dens(k,i,j)-dens_check(k,i,j) ) > atmos_restart_check_criterion ) then
1091  write(*,*) 'xxx there is the difference : ', dens(k,i,j)-dens_check(k,i,j)
1092  write(*,*) 'xxx at (PE-id,k,i,j,varname) : ', prc_myrank, k, i, j, 'DENS'
1093  datacheck = .false.
1094  endif
1095  enddo
1096  enddo
1097  enddo
1098 
1099  call fileread( restart_atmos(:,:,:), basename, 'MOMZ', 1, prc_myrank )
1100  momz_check(ks:ke,is:ie,js:je) = restart_atmos(1:kmax,1:imax,1:jmax)
1101  do k = ks, ke
1102  do j = js, je
1103  do i = is, ie
1104  if ( abs( momz(k,i,j)-momz_check(k,i,j) ) > atmos_restart_check_criterion ) then
1105  write(*,*) 'xxx there is the difference : ', momz(k,i,j)-momz_check(k,i,j)
1106  write(*,*) 'xxx at (PE-id,k,i,j,varname) : ', prc_myrank, k, i, j, 'MOMZ'
1107  datacheck = .false.
1108  endif
1109  enddo
1110  enddo
1111  enddo
1112 
1113  call fileread( restart_atmos(:,:,:), basename, 'MOMX', 1, prc_myrank )
1114  momx_check(ks:ke,is:ie,js:je) = restart_atmos(1:kmax,1:imax,1:jmax)
1115  do k = ks, ke
1116  do j = js, je
1117  do i = is, ie
1118  if ( abs( momx(k,i,j)-momx_check(k,i,j) ) > atmos_restart_check_criterion ) then
1119  write(*,*) 'xxx there is the difference : ', momx(k,i,j)-momx_check(k,i,j)
1120  write(*,*) 'xxx at (PE-id,k,i,j,varname) : ', prc_myrank, k, i, j, 'MOMX'
1121  datacheck = .false.
1122  endif
1123  enddo
1124  enddo
1125  enddo
1126 
1127  call fileread( restart_atmos(:,:,:), basename, 'MOMY', 1, prc_myrank )
1128  momy_check(ks:ke,is:ie,js:je) = restart_atmos(1:kmax,1:imax,1:jmax)
1129  do k = ks, ke
1130  do j = js, je
1131  do i = is, ie
1132  if ( abs( momy(k,i,j)-momy_check(k,i,j) ) > atmos_restart_check_criterion ) then
1133  write(*,*) 'xxx there is the difference : ', momy(k,i,j)-momy_check(k,i,j)
1134  write(*,*) 'xxx at (PE-id,k,i,j,varname) : ', prc_myrank, k, i, j, 'MOMY'
1135  datacheck = .false.
1136  endif
1137  enddo
1138  enddo
1139  enddo
1140 
1141  call fileread( restart_atmos(:,:,:), basename, 'RHOT', 1, prc_myrank )
1142  rhot_check(ks:ke,is:ie,js:je) = restart_atmos(1:kmax,1:imax,1:jmax)
1143  do k = ks, ke
1144  do j = js, je
1145  do i = is, ie
1146  if ( abs( rhot(k,i,j)-rhot_check(k,i,j) ) > atmos_restart_check_criterion ) then
1147  write(*,*) 'xxx there is the difference : ', rhot(k,i,j)-rhot_check(k,i,j)
1148  write(*,*) 'xxx at (PE-id,k,i,j,varname) : ', prc_myrank, k, i, j, 'RHOT'
1149  datacheck = .false.
1150  endif
1151  enddo
1152  enddo
1153  enddo
1154 
1155  do iq = 1, qa
1156  call fileread( restart_atmos(:,:,:), basename, aq_name(iq), 1, prc_myrank )
1157  qtrc_check(ks:ke,is:ie,js:je,iq) = restart_atmos(1:kmax,1:imax,1:jmax)
1158  do k = ks, ke
1159  do j = js, je
1160  do i = is, ie
1161  if ( abs( qtrc(k,i,j,iq)-qtrc_check(k,i,j,iq) ) > atmos_restart_check_criterion ) then
1162  write(*,*) 'xxx there is the difference : ', qtrc(k,i,j,iq)-qtrc_check(k,i,j,iq)
1163  write(*,*) 'xxx at (PE-id,k,i,j,varname) : ', prc_myrank, k, i, j, aq_name(iq)
1164  datacheck = .false.
1165  endif
1166  enddo
1167  enddo
1168  enddo
1169  enddo
1170 
1171  if (datacheck) then
1172  if( io_l ) write(io_fid_log,*) 'Data Check Clear.'
1173  write(*,*) 'Data Check Clear.'
1174  else
1175  if( io_l ) write(io_fid_log,*) 'Data Check Failed. See std. output.'
1176  write(*,*) 'Data Check Failed.'
1177  endif
1178 
1179  call prof_rapend('Debug')
1180 
1181  return
module GTOOL_FILE
Definition: gtool_file.f90:17
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 PROCESS
integer, public prc_myrank
process num in local communicator
real(rp), dimension(:,:,:), allocatable, target, public momy
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 1187 of file mod_atmos_vars.f90.

References scale_atmos_thermodyn::aq_cp, scale_atmos_thermodyn::aq_cv, scale_tracer::aq_desc, scale_tracer::aq_name, scale_tracer::aq_unit, 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_lhf, scale_const::const_lhv, scale_const::const_pre00, scale_const::const_rdry, scale_const::const_rvap, dens, 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_tracer::i_qc, scale_tracer::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::ke, scale_grid_index::ks, momx, momy, momz, pott, pres, scale_tracer::qa, scale_tracer::qie, scale_tracer::qis, scale_tracer::qqe, scale_tracer::qqs, qtrc, scale_tracer::qwe, scale_tracer::qws, scale_grid_real::real_cz, scale_grid_real::real_fz, rhot, temp, u, v, and w.

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

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

References scale_atmos_thermodyn::aq_cv, scale_tracer::aq_name, scale_const::const_cvdry, scale_const::const_grav, scale_const::const_lhf, scale_const::const_lhv, dens, scale_index::i_dens, scale_index::i_momx, scale_index::i_momy, scale_index::i_momz, scale_tracer::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, momx, momy, momz, scale_tracer::qa, scale_tracer::qie, scale_tracer::qis, scale_tracer::qqe, scale_tracer::qqs, qtrc, scale_grid_real::real_cz, rhot, and scale_rm_statistics::statistics_checktotal.

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

2134  use scale_const, only: &
2135  grav => const_grav, &
2136  cvdry => const_cvdry, &
2137  lhv => const_lhv, &
2138  lhf => const_lhf
2139  use scale_grid_real, only: &
2140  real_cz
2141  use scale_rm_statistics, only: &
2143  stat_total
2144  use scale_atmos_thermodyn, only: &
2145  thermodyn_qd => atmos_thermodyn_qd, &
2146  thermodyn_temp_pres => atmos_thermodyn_temp_pres, &
2147  cvw => aq_cv
2148  implicit none
2149 
2150  real(RP) :: w (ka,ia,ja) ! velocity w at cell center [m/s]
2151  real(RP) :: u (ka,ia,ja) ! velocity u at cell center [m/s]
2152  real(RP) :: v (ka,ia,ja) ! velocity v at cell center [m/s]
2153 
2154  real(RP) :: qdry(ka,ia,ja) ! dry air [kg/kg]
2155  real(RP) :: pres(ka,ia,ja) ! pressure [Pa]
2156  real(RP) :: temp(ka,ia,ja) ! temperature [K]
2157 
2158  real(RP) :: engt(ka,ia,ja) ! total energy [J/m3]
2159  real(RP) :: engp(ka,ia,ja) ! potential energy [J/m3]
2160  real(RP) :: engk(ka,ia,ja) ! kinetic energy [J/m3]
2161  real(RP) :: engi(ka,ia,ja) ! internal energy [J/m3]
2162 
2163  real(RP) :: rhoq(ka,ia,ja)
2164 
2165  real(RP) :: total ! dummy
2166  integer :: i, j, k, iq
2167  !---------------------------------------------------------------------------
2168 
2169  if ( statistics_checktotal ) then
2170 
2171  call stat_total( total, dens(:,:,:), var_name(i_dens) )
2172  call stat_total( total, momz(:,:,:), var_name(i_momz) )
2173  call stat_total( total, momx(:,:,:), var_name(i_momx) )
2174  call stat_total( total, momy(:,:,:), var_name(i_momy) )
2175  call stat_total( total, rhot(:,:,:), var_name(i_rhot) )
2176 
2177  do iq = 1, qa
2178  rhoq(:,:,:) = dens(:,:,:) * qtrc(:,:,:,iq)
2179 
2180  call stat_total( total, rhoq(:,:,:), aq_name(iq) )
2181  enddo
2182 
2183  call thermodyn_qd( qdry(:,:,:), & ! [OUT]
2184  qtrc(:,:,:,:) ) ! [IN]
2185 
2186  call thermodyn_temp_pres( temp(:,:,:), & ! [OUT]
2187  pres(:,:,:), & ! [OUT]
2188  dens(:,:,:), & ! [IN]
2189  rhot(:,:,:), & ! [IN]
2190  qtrc(:,:,:,:) ) ! [IN]
2191 
2192  rhoq(ks:ke,is:ie,js:je) = dens(ks:ke,is:ie,js:je) * qdry(ks:ke,is:ie,js:je)
2193 
2194  call stat_total( total, rhoq(:,:,:), 'QDRY' )
2195 
2196  rhoq(ks:ke,is:ie,js:je) = dens(ks:ke,is:ie,js:je) * ( 1.0_rp - qdry(ks:ke,is:ie,js:je) ) ! Qtotal
2197 
2198  call stat_total( total, rhoq(:,:,:), 'QTOT' )
2199 
2200  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
2201  do j = js, je
2202  do i = is, ie
2203  do k = ks, ke
2204  w(k,i,j) = 0.5_rp * ( momz(k-1,i,j)+momz(k,i,j) ) / dens(k,i,j)
2205  u(k,i,j) = 0.5_rp * ( momx(k,i-1,j)+momx(k,i,j) ) / dens(k,i,j)
2206  v(k,i,j) = 0.5_rp * ( momy(k,i,j-1)+momy(k,i,j) ) / dens(k,i,j)
2207 
2208  engp(k,i,j) = dens(k,i,j) * grav * real_cz(k,i,j)
2209 
2210  engk(k,i,j) = 0.5_rp * dens(k,i,j) * ( w(k,i,j)**2 &
2211  + u(k,i,j)**2 &
2212  + v(k,i,j)**2 )
2213 
2214  engi(k,i,j) = dens(k,i,j) * qdry(k,i,j) * temp(k,i,j) * cvdry
2215  do iq = qqs, qqe
2216  engi(k,i,j) = engi(k,i,j) &
2217  + dens(k,i,j) * qtrc(k,i,j,iq) * temp(k,i,j) * cvw(iq)
2218  enddo
2219 
2220  engi(k,i,j) = engi(k,i,j) + dens(k,i,j) * qtrc(k,i,j,i_qv) * lhv ! Latent Heat [vapor->liquid]
2221 
2222  do iq = qis, qie
2223  engi(k,i,j) = engi(k,i,j) - dens(k,i,j) * qtrc(k,i,j,iq) * lhf ! Latent Heat [ice->liquid]
2224  enddo
2225 
2226  engt(k,i,j) = engp(k,i,j) + engk(k,i,j) + engi(k,i,j)
2227  enddo
2228  enddo
2229  enddo
2230 
2231  call stat_total( total, engp(:,:,:), 'ENGP' )
2232  call stat_total( total, engk(:,:,:), 'ENGK' )
2233  call stat_total( total, engi(:,:,:), 'ENGI' )
2234  call stat_total( total, engt(:,:,:), 'ENGT' )
2235 
2236  endif
2237 
2238  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(:,:,:), 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
module GRID (real space)
real(rp), public const_grav
standard acceleration of gravity [m/s2]
Definition: scale_const.F90:48
real(rp), public const_lhv
latent heat of vaporizaion for use
Definition: scale_const.F90:77
module CONSTANT
Definition: scale_const.F90:14
real(rp), dimension(:), allocatable, public aq_cv
CV for each hydrometeors [J/kg/K].
real(rp), dimension(:,:,:), allocatable, target, public momy
real(rp), public const_lhf
latent heat of fusion for use
Definition: scale_const.F90:79
module ATMOSPHERE / Thermodynamics
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 2244 of file mod_atmos_vars.f90.

References dens, scale_grid_index::ia, 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, momy, momz, pott, pres, qtrc, rhot, temp, u, v, and w.

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

2244  use scale_comm, only: &
2245  comm_vars8, &
2246  comm_wait
2247  use scale_atmos_thermodyn, only: &
2248  thermodyn_temp_pres => atmos_thermodyn_temp_pres
2249  implicit none
2250 
2251  integer :: k, i, j
2252  !---------------------------------------------------------------------------
2253 
2254  if( io_l ) write(io_fid_log,*) '*** Calc diagnostics'
2255 
2256  call thermodyn_temp_pres( temp(:,:,:), & ! [OUT]
2257  pres(:,:,:), & ! [OUT]
2258  dens(:,:,:), & ! [IN]
2259  rhot(:,:,:), & ! [IN]
2260  qtrc(:,:,:,:) ) ! [IN]
2261 
2262 !OCL XFILL
2263  do j = 1, ja
2264  do i = 1, ia
2265  do k = ks+1, ke-1
2266  w(k,i,j) = 0.5_rp * ( momz(k-1,i,j)+momz(k,i,j) ) / dens(k,i,j)
2267  enddo
2268  enddo
2269  enddo
2270 !OCL XFILL
2271  do j = 1, ja
2272  do i = 1, ia
2273  w(ks,i,j) = 0.5_rp * ( momz(ks,i,j) ) / dens(ks,i,j)
2274  enddo
2275  enddo
2276 !OCL XFILL
2277  do j = 1, ja
2278  do i = 1, ia
2279  w(ke,i,j) = 0.5_rp * ( momz(ke-1,i,j) ) / dens(ke,i,j)
2280  enddo
2281  enddo
2282 
2283 !OCL XFILL
2284  do j = 1, ja
2285  do i = 2, ia
2286  do k = ks, ke
2287  u(k,i,j) = 0.5_rp * ( momx(k,i-1,j)+momx(k,i,j) ) / dens(k,i,j)
2288  enddo
2289  enddo
2290  enddo
2291 !OCL XFILL
2292  do j = 1, ja
2293  do k = ks, ke
2294  u(k,1,j) = momx(k,1,j) / dens(k,1,j)
2295  enddo
2296  enddo
2297 
2298 !OCL XFILL
2299  do j = 2, ja
2300  do i = 1, ia
2301  do k = ks, ke
2302  v(k,i,j) = 0.5_rp * ( momy(k,i,j-1)+momy(k,i,j) ) / dens(k,i,j)
2303  enddo
2304  enddo
2305  enddo
2306 !OCL XFILL
2307  do i = 1, ia
2308  do k = ks, ke
2309  v(k,i,1) = momy(k,i,1) / dens(k,i,1)
2310  enddo
2311  enddo
2312 
2313  !$omp parallel do private(i,j) OMP_SCHEDULE_ collapse(2)
2314  do j = 1, ja
2315  do i = 1, ia
2316  w( 1:ks-1,i,j) = w(ks,i,j)
2317  u( 1:ks-1,i,j) = u(ks,i,j)
2318  v( 1:ks-1,i,j) = v(ks,i,j)
2319  w(ke+1:ka, i,j) = w(ke,i,j)
2320  u(ke+1:ka, i,j) = u(ke,i,j)
2321  v(ke+1:ka, i,j) = v(ke,i,j)
2322  enddo
2323  enddo
2324 
2325  call comm_vars8( u(:,:,:), 1 )
2326  call comm_vars8( v(:,:,:), 2 )
2327  call comm_wait ( u(:,:,:), 1, .false. )
2328  call comm_wait ( v(:,:,:), 2, .false. )
2329 
2330 !OCL XFILL
2331  do j = 1, ja
2332  do i = 1, ia
2333  do k = ks, ke
2334  pott(k,i,j) = rhot(k,i,j) / dens(k,i,j)
2335  enddo
2336  enddo
2337  enddo
2338 
2339  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
module ATMOSPHERE / Thermodynamics
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
Here is the caller graph for this function:

◆ atmos_vars_monitor()

subroutine, public mod_atmos_vars::atmos_vars_monitor ( )

monitor output

Definition at line 2345 of file mod_atmos_vars.f90.

References scale_atmos_thermodyn::aq_cv, scale_tracer::aq_desc, scale_tracer::aq_name, scale_tracer::aq_unit, 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, scale_const::const_lhf, scale_const::const_lhv, dens, 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_tracer::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, momx, momy, momz, scale_process::prc_myrank, pres, scale_tracer::qa, scale_tracer::qie, scale_tracer::qis, scale_tracer::qqe, scale_tracer::qqs, qtrc, scale_grid_real::real_cz, scale_grid_real::real_fz, rhot, scale_rm_statistics::stat_detail(), scale_rm_statistics::statistics_checktotal, temp, scale_time::time_dtsec_atmos_dyn, u, v, and w.

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

2345  use scale_process, only: &
2346  prc_myrank
2347  use scale_const, only: &
2348  grav => const_grav, &
2349  cvdry => const_cvdry, &
2350  lhv => const_lhv, &
2351  lhf => const_lhf
2352  use scale_grid, only: &
2353  rfdx => grid_rfdx, &
2354  rfdy => grid_rfdy
2355  use scale_grid_real, only: &
2356  real_cz, &
2357  real_fz
2358  use scale_gridtrans, only: &
2359  mapf => gtrans_mapf, &
2360  i_uy, &
2361  i_xv
2362  use scale_comm, only: &
2363  comm_vars8, &
2364  comm_wait
2365  use scale_rm_statistics, only: &
2367  stat_total, &
2368  stat_detail
2369  use scale_monitor, only: &
2370  monit_put, &
2371  monit_in
2372  use scale_time, only: &
2374  use scale_atmos_thermodyn, only: &
2375  thermodyn_qd => atmos_thermodyn_qd, &
2376  thermodyn_temp_pres => atmos_thermodyn_temp_pres, &
2377  cvw => aq_cv
2378  use mod_atmos_phy_mp_vars, only: &
2379  sflx_rain => atmos_phy_mp_sflx_rain, &
2380  sflx_snow => atmos_phy_mp_sflx_snow
2381  use mod_atmos_phy_rd_vars, only: &
2382  sflx_lw_up => atmos_phy_rd_sflx_lw_up, &
2383  sflx_lw_dn => atmos_phy_rd_sflx_lw_dn, &
2384  sflx_sw_up => atmos_phy_rd_sflx_sw_up, &
2385  sflx_sw_dn => atmos_phy_rd_sflx_sw_dn, &
2386  toaflx_lw_up => atmos_phy_rd_toaflx_lw_up, &
2387  toaflx_lw_dn => atmos_phy_rd_toaflx_lw_dn, &
2388  toaflx_sw_up => atmos_phy_rd_toaflx_sw_up, &
2389  toaflx_sw_dn => atmos_phy_rd_toaflx_sw_dn
2390  use mod_atmos_phy_sf_vars, only: &
2391  sflx_sh => atmos_phy_sf_sflx_sh, &
2392  sflx_lh => atmos_phy_sf_sflx_lh, &
2393  sflx_qtrc => atmos_phy_sf_sflx_qtrc
2394  implicit none
2395 
2396  real(RP) :: qdry(ka,ia,ja) ! dry air [kg/kg]
2397  real(RP) :: rhoq(ka,ia,ja) ! DENS * tracer [kg/m3]
2398  real(RP) :: prcp(ia,ja) ! rain + snow [kg/m2/s]
2399 
2400  real(RP) :: engt(ka,ia,ja) ! total energy [J/m3]
2401  real(RP) :: engp(ka,ia,ja) ! potential energy [J/m3]
2402  real(RP) :: engk(ka,ia,ja) ! kinetic energy [J/m3]
2403  real(RP) :: engi(ka,ia,ja) ! internal energy [J/m3]
2404 
2405  real(RP) :: engflxt (ia,ja) ! total flux [J/m2/s]
2406  real(RP) :: sflx_rd_net (ia,ja) ! net SFC radiation flux [J/m2/s]
2407  real(RP) :: toaflx_rd_net(ia,ja) ! net TOA radiation flux [J/m2/s]
2408 
2409  real(RP) :: work (ka,ia,ja,3)
2410  character(len=H_SHORT) :: wname(3)
2411  real(RP) :: cflmax
2412 
2413  integer :: k, i, j, iq
2414  !---------------------------------------------------------------------------
2415 
2416  if( io_l ) write(io_fid_log,*) '*** Monitor'
2417 
2418  call monit_in( dens(:,:,:), var_name(i_dens), var_desc(i_dens), var_unit(i_dens), ndim=3, isflux=.false. )
2419  call monit_in( momz(:,:,:), var_name(i_momz), var_desc(i_momz), var_unit(i_momz), ndim=3, isflux=.false. )
2420  call monit_in( momx(:,:,:), var_name(i_momx), var_desc(i_momx), var_unit(i_momx), ndim=3, isflux=.false. )
2421  call monit_in( momy(:,:,:), var_name(i_momy), var_desc(i_momy), var_unit(i_momy), ndim=3, isflux=.false. )
2422  call monit_in( rhot(:,:,:), var_name(i_rhot), var_desc(i_rhot), var_unit(i_rhot), ndim=3, isflux=.false. )
2423 
2424  !##### Mass Budget #####
2425  do iq = 1, qa
2426  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
2427 !OCL XFILL
2428  do j = js, je
2429  do i = is, ie
2430  do k = ks, ke
2431  rhoq(k,i,j) = dens(k,i,j) * qtrc(k,i,j,iq)
2432  enddo
2433  enddo
2434  enddo
2435 
2436  call monit_in( rhoq(:,:,:), aq_name(iq), aq_desc(iq), aq_unit(iq), ndim=3, isflux=.false. )
2437  enddo
2438 
2439  ! total dry airmass
2440 
2441  call thermodyn_qd( qdry(:,:,:), & ! [OUT]
2442  qtrc(:,:,:,:) ) ! [IN]
2443 
2444  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
2445 !OCL XFILL
2446  do j = js, je
2447  do i = is, ie
2448  do k = ks, ke
2449  rhoq(k,i,j) = dens(k,i,j) * qdry(k,i,j)
2450  enddo
2451  enddo
2452  enddo
2453  call monit_put( ad_monit_id(i_qdry), rhoq(:,:,:) )
2454 
2455  ! total vapor,liquid,solid tracers
2456  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
2457 !OCL XFILL
2458  do j = js, je
2459  do i = is, ie
2460  do k = ks, ke
2461  rhoq(k,i,j) = dens(k,i,j) * ( 1.0_rp - qdry(k,i,j) )
2462  enddo
2463  enddo
2464  enddo
2465  call monit_put( ad_monit_id(i_qtot), rhoq(:,:,:) )
2466 
2467  ! total evapolation
2468  call monit_put( ad_monit_id(i_evap), sflx_qtrc(:,:,i_qv) )
2469 
2470  ! total precipitation
2471 !OCL XFILL
2472  do j = js, je
2473  do i = is, ie
2474  prcp(i,j) = sflx_rain(i,j) + sflx_snow(i,j)
2475  enddo
2476  enddo
2477  call monit_put( ad_monit_id(i_prcp), prcp(:,:) )
2478 
2479  !##### Energy Budget #####
2480 
2481  call thermodyn_temp_pres( temp(:,:,:), & ! [OUT]
2482  pres(:,:,:), & ! [OUT]
2483  dens(:,:,:), & ! [IN]
2484  rhot(:,:,:), & ! [IN]
2485  qtrc(:,:,:,:) ) ! [IN]
2486 
2487  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
2488  do j = js, je
2489  do i = is, ie
2490  do k = ks, ke
2491  engp(k,i,j) = dens(k,i,j) * grav * real_cz(k,i,j)
2492 
2493  engk(k,i,j) = 0.5_rp * dens(k,i,j) * ( w(k,i,j)**2 &
2494  + u(k,i,j)**2 &
2495  + v(k,i,j)**2 )
2496 
2497  engi(k,i,j) = dens(k,i,j) * qdry(k,i,j) * temp(k,i,j) * cvdry
2498  do iq = qqs, qqe
2499  engi(k,i,j) = engi(k,i,j) &
2500  + dens(k,i,j) * qtrc(k,i,j,iq) * temp(k,i,j) * cvw(iq)
2501  enddo
2502 
2503  engi(k,i,j) = engi(k,i,j) + dens(k,i,j) * qtrc(k,i,j,i_qv) * lhv ! Latent Heat [vapor->liquid]
2504 
2505  do iq = qis, qie
2506  engi(k,i,j) = engi(k,i,j) - dens(k,i,j) * qtrc(k,i,j,iq) * lhf ! Latent Heat [ice->liquid]
2507  enddo
2508  enddo
2509  enddo
2510  enddo
2511 
2512  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
2513 !OCL XFILL
2514  do j = js, je
2515  do i = is, ie
2516  do k = ks, ke
2517  engt(k,i,j) = engp(k,i,j) + engk(k,i,j) + engi(k,i,j)
2518  enddo
2519  enddo
2520  enddo
2521 
2522 !OCL XFILL
2523  do j = js, je
2524  do i = is, ie
2525  sflx_rd_net(i,j) = ( sflx_lw_up(i,j) - sflx_lw_dn(i,j) ) &
2526  + ( sflx_sw_up(i,j) - sflx_sw_dn(i,j) )
2527 
2528  toaflx_rd_net(i,j) = ( toaflx_lw_up(i,j) - toaflx_lw_dn(i,j) ) &
2529  + ( toaflx_sw_up(i,j) - toaflx_sw_dn(i,j) )
2530  enddo
2531  enddo
2532 
2533  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
2534 !OCL XFILL
2535  do j = js, je
2536  do i = is, ie
2537  engflxt(i,j) = sflx_sh(i,j) + sflx_lh(i,j) &
2538  + sflx_rd_net(i,j) - toaflx_rd_net(i,j)
2539  enddo
2540  enddo
2541 
2542  call monit_put( ad_monit_id(i_engt), engt(:,:,:) )
2543  call monit_put( ad_monit_id(i_engp), engp(:,:,:) )
2544  call monit_put( ad_monit_id(i_engk), engk(:,:,:) )
2545  call monit_put( ad_monit_id(i_engi), engi(:,:,:) )
2546 
2547  call monit_put( ad_monit_id(i_engflxt), engflxt(:,:) )
2548 
2549 
2550  call monit_put( ad_monit_id(i_engsfc_sh), sflx_sh(:,:) )
2551  call monit_put( ad_monit_id(i_engsfc_lh), sflx_lh(:,:) )
2552  call monit_put( ad_monit_id(i_engsfc_rd), sflx_rd_net(:,:) )
2553  call monit_put( ad_monit_id(i_engtoa_rd), toaflx_rd_net(:,:) )
2554 
2555  call monit_put( ad_monit_id(i_engsfc_lw_up), sflx_lw_up(:,:) )
2556  call monit_put( ad_monit_id(i_engsfc_lw_dn), sflx_lw_dn(:,:) )
2557  call monit_put( ad_monit_id(i_engsfc_sw_up), sflx_sw_up(:,:) )
2558  call monit_put( ad_monit_id(i_engsfc_sw_dn), sflx_sw_dn(:,:) )
2559 
2560  call monit_put( ad_monit_id(i_engtoa_lw_up), toaflx_lw_up(:,:) )
2561  call monit_put( ad_monit_id(i_engtoa_lw_dn), toaflx_lw_dn(:,:) )
2562  call monit_put( ad_monit_id(i_engtoa_sw_up), toaflx_sw_up(:,:) )
2563  call monit_put( ad_monit_id(i_engtoa_sw_dn), toaflx_sw_dn(:,:) )
2564 
2565  if ( atmos_vars_checkrange ) then
2566 !OCL XFILL
2567  work(:,:,:,1) = w(:,:,:)
2568 !OCL XFILL
2569  work(:,:,:,2) = u(:,:,:)
2570 !OCL XFILL
2571  work(:,:,:,3) = v(:,:,:)
2572 
2573  wname(1) = "W"
2574  wname(2) = "U"
2575  wname(3) = "V"
2576 
2577  call stat_detail( work(:,:,:,:), wname(:) )
2578  endif
2579 
2580  if ( atmos_vars_checkcfl > 0.0_rp ) then
2581 !OCL XFILL
2582  work(:,:,:,:) = 0.0_rp
2583 
2584  do j = js, je
2585  do i = is, ie
2586  do k = ks, ke
2587  work(k,i,j,1) = 0.5_rp * abs(momz(k,i,j)) / ( dens(k+1,i,j) + dens(k,i,j) ) &
2588  * time_dtsec_atmos_dyn / ( real_cz(k+1,i,j) - real_cz(k,i,j) )
2589  work(k,i,j,2) = 0.5_rp * abs(momx(k,i,j)) / ( dens(k,i+1,j) + dens(k,i,j) ) &
2590  * time_dtsec_atmos_dyn * rfdx(i) * mapf(i,j,1,i_uy)
2591  work(k,i,j,3) = 0.5_rp * abs(momy(k,i,j)) / ( dens(k,i,j+1) + dens(k,i,j) ) &
2592  * time_dtsec_atmos_dyn * rfdy(j) * mapf(i,j,2,i_xv)
2593  enddo
2594  enddo
2595  enddo
2596 
2597  cflmax = maxval( work(:,:,:,:) )
2598  if ( cflmax > atmos_vars_checkcfl ) then
2599  if( io_l ) write(io_fid_log,*) "*** [ATMOS_vars_monitor] Courant number exceeded the upper limit. : ", cflmax
2600  write(*,*) "*** [ATMOS_vars_monitor] Courant number exceeded the upper limit. : ", cflmax, &
2601  ", rank = ", prc_myrank
2602 
2603  wname(1) = "Courant num. Z"
2604  wname(2) = "Courant num. X"
2605  wname(3) = "Courant num. Y"
2606 
2607  call stat_detail( work(:,:,:,:), wname(:), supress_globalcomm=.true. )
2608  endif
2609  endif
2610 
2611  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, public atmos_phy_sf_sflx_qtrc
real(rp), dimension(:,:,:), allocatable, target, public rhot
module Atmosphere / Physics Cloud Microphysics
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, public grid_rfdy
reciprocal of face-dy
real(rp), dimension(:,:,:), allocatable, target, public dens
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(:,:,:,:), 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), public const_lhv
latent heat of vaporizaion for use
Definition: scale_const.F90:77
module CONSTANT
Definition: scale_const.F90:14
real(rp), dimension(:), allocatable, public aq_cv
CV for each hydrometeors [J/kg/K].
integer, public prc_myrank
process num in local communicator
real(rp), dimension(:,:,:), allocatable, target, public momy
module GRID (cartesian)
real(rp), public const_lhf
latent heat of fusion for use
Definition: scale_const.F90:79
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(:), allocatable, public grid_rfdx
reciprocal of face-dx
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_lw_up
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_create()

subroutine, public mod_atmos_vars::atmos_vars_restart_create ( )

Create atmospheric restart file.

Definition at line 2617 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_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().

2617  use scale_time, only: &
2619  use scale_fileio, only: &
2621  use mod_atmos_admin, only: &
2622  atmos_sw_dyn, &
2623  atmos_sw_phy_mp, &
2624  atmos_sw_phy_ae, &
2625  atmos_sw_phy_ch, &
2626  atmos_sw_phy_rd, &
2627  atmos_sw_phy_sf, &
2628  atmos_sw_phy_tb, &
2630  use mod_atmos_dyn_vars, only: &
2632  use mod_atmos_phy_mp_vars, only: &
2634  use mod_atmos_phy_ae_vars, only: &
2636  use mod_atmos_phy_ch_vars, only: &
2638  use mod_atmos_phy_rd_vars, only: &
2640  use mod_atmos_phy_sf_vars, only: &
2642  use mod_atmos_phy_tb_vars, only: &
2644  use mod_atmos_phy_cp_vars, only: &
2646 #ifdef _SDM
2647  use scale_atmos_phy_mp_sdm, only: &
2648  sd_rest_flg_out, &
2649  atmos_phy_mp_sdm_restart_create
2650  use scale_time, only: &
2651  nowsec => time_nowsec
2652 #endif
2653  implicit none
2654 
2655  character(len=20) :: timelabel
2656  character(len=H_LONG) :: basename
2657 
2658  integer :: iq
2659  !---------------------------------------------------------------------------
2660 
2661 #ifdef _SDM
2662  if( sd_rest_flg_out ) then
2663  if( io_l ) write(io_fid_log,*) '*** Output random number for SDM ***'
2664  call atmos_phy_mp_sdm_restart_create(nowsec)
2665  endif
2666 #endif
2667 
2668  if ( atmos_restart_out_basename /= '' ) then
2669 
2670  call time_gettimelabel( timelabel )
2671  write(basename,'(A,A,A)') trim(atmos_restart_out_basename), '_', trim(timelabel)
2672 
2673  if( io_l ) write(io_fid_log,*)
2674  if( io_l ) write(io_fid_log,*) '*** Output restart file (ATMOS) ***'
2675  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
2676 
2677  call fileio_create(restart_fid, basename, atmos_restart_out_title, atmos_restart_out_dtype)
2678 
2679  allocate( var_id(vmax+qa) )
2680  endif
2681 
2690 
2691  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 2697 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().

2697  use scale_fileio, only: &
2699  use mod_atmos_admin, only: &
2700  atmos_sw_dyn, &
2701  atmos_sw_phy_mp, &
2702  atmos_sw_phy_ae, &
2703  atmos_sw_phy_ch, &
2704  atmos_sw_phy_rd, &
2705  atmos_sw_phy_sf, &
2706  atmos_sw_phy_tb, &
2708  use mod_atmos_dyn_vars, only: &
2710  use mod_atmos_phy_mp_vars, only: &
2712  use mod_atmos_phy_ae_vars, only: &
2714  use mod_atmos_phy_ch_vars, only: &
2716  use mod_atmos_phy_rd_vars, only: &
2718  use mod_atmos_phy_sf_vars, only: &
2720  use mod_atmos_phy_tb_vars, only: &
2722  use mod_atmos_phy_cp_vars, only: &
2724 #ifdef _SDM
2725  use scale_atmos_phy_mp_sdm, only: &
2726  sd_rest_flg_out, &
2727  atmos_phy_mp_sdm_restart_enddef
2728 #endif
2729  implicit none
2730 
2731  !---------------------------------------------------------------------------
2732 
2733 #ifdef _SDM
2734  if( sd_rest_flg_out ) then
2735  call atmos_phy_mp_sdm_restart_enddef
2736  endif
2737 #endif
2738 
2739  if ( restart_fid .NE. -1 ) then
2740  call fileio_enddef( restart_fid ) ! [IN]
2741  endif
2742 
2751 
2752  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 2758 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, and scale_fileio::fileio_close().

Referenced by mod_admin_restart::admin_restart().

2758  use scale_fileio, only: &
2759  fileio_close
2760  use mod_atmos_admin, only: &
2761  atmos_sw_dyn, &
2762  atmos_sw_phy_mp, &
2763  atmos_sw_phy_ae, &
2764  atmos_sw_phy_ch, &
2765  atmos_sw_phy_rd, &
2766  atmos_sw_phy_sf, &
2767  atmos_sw_phy_tb, &
2769  use mod_atmos_dyn_vars, only: &
2771  use mod_atmos_phy_mp_vars, only: &
2773  use mod_atmos_phy_ae_vars, only: &
2775  use mod_atmos_phy_ch_vars, only: &
2777  use mod_atmos_phy_rd_vars, only: &
2779  use mod_atmos_phy_sf_vars, only: &
2781  use mod_atmos_phy_tb_vars, only: &
2783  use mod_atmos_phy_cp_vars, only: &
2785 #ifdef _SDM
2786  use scale_atmos_phy_mp_sdm, only: &
2787  sd_rest_flg_out, &
2788  atmos_phy_mp_sdm_restart_close
2789 #endif
2790  implicit none
2791 
2792  !---------------------------------------------------------------------------
2793 
2794 #ifdef _SDM
2795  if( sd_rest_flg_out ) then
2796  call atmos_phy_mp_sdm_restart_close
2797  endif
2798 #endif
2799 
2800  if ( restart_fid .NE. -1 ) then
2801  call fileio_close( restart_fid ) ! [IN]
2802  restart_fid = -1
2803 
2804  deallocate( var_id )
2805  endif
2806 
2815 
2816  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 2822 of file mod_atmos_vars.f90.

References scale_tracer::aq_desc, scale_tracer::aq_name, scale_tracer::aq_unit, 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, and scale_tracer::qa.

Referenced by mod_admin_restart::admin_restart().

2822  use scale_fileio, only: &
2824  use mod_atmos_admin, only: &
2825  atmos_sw_dyn, &
2826  atmos_sw_phy_mp, &
2827  atmos_sw_phy_ae, &
2828  atmos_sw_phy_ch, &
2829  atmos_sw_phy_rd, &
2830  atmos_sw_phy_sf, &
2831  atmos_sw_phy_tb, &
2833  use mod_atmos_dyn_vars, only: &
2835  use mod_atmos_phy_mp_vars, only: &
2837  use mod_atmos_phy_ae_vars, only: &
2839  use mod_atmos_phy_ch_vars, only: &
2841  use mod_atmos_phy_rd_vars, only: &
2843  use mod_atmos_phy_sf_vars, only: &
2845  use mod_atmos_phy_tb_vars, only: &
2847  use mod_atmos_phy_cp_vars, only: &
2849 #ifdef _SDM
2850  use scale_atmos_phy_mp_sdm, only: &
2851  sd_rest_flg_out, &
2852  atmos_phy_mp_sdm_restart_def_var
2853 #endif
2854  implicit none
2855 
2856  integer iq
2857  !---------------------------------------------------------------------------
2858 
2859 #ifdef _SDM
2860  if( sd_rest_flg_out ) then
2861  call atmos_phy_mp_sdm_restart_def_var
2862  endif
2863 #endif
2864 
2865  if ( restart_fid .NE. -1 ) then
2866 
2867  call fileio_def_var( restart_fid, var_id(i_dens), var_name(i_dens), var_desc(i_dens), & ! [IN]
2868  var_unit(i_dens), 'ZXY', atmos_restart_out_dtype ) ! [IN]
2869  call fileio_def_var( restart_fid, var_id(i_momz), var_name(i_momz), var_desc(i_momz), & ! [IN]
2870  var_unit(i_momz), 'ZHXY', atmos_restart_out_dtype ) ! [IN]
2871  call fileio_def_var( restart_fid, var_id(i_momx), var_name(i_momx), var_desc(i_momx), & ! [IN]
2872  var_unit(i_momx), 'ZXHY', atmos_restart_out_dtype ) ! [IN]
2873  call fileio_def_var( restart_fid, var_id(i_momy), var_name(i_momy), var_desc(i_momy), & ! [IN]
2874  var_unit(i_momy), 'ZXYH', atmos_restart_out_dtype ) ! [IN]
2875  call fileio_def_var( restart_fid, var_id(i_rhot), var_name(i_rhot), var_desc(i_rhot), & ! [IN]
2876  var_unit(i_rhot), 'ZXY', atmos_restart_out_dtype ) ! [IN]
2877 
2878  do iq = 1, qa
2879  call fileio_def_var( restart_fid, var_id(vmax+iq), aq_name(iq), aq_desc(iq), & ! [IN]
2880  aq_unit(iq), 'ZXY', atmos_restart_out_dtype ) ! [IN]
2881  enddo
2882 
2883  endif
2884 
2893 
2894  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 fileio_def_var(fid, vid, varname, desc, unit, axistype, datatype, timeintv)
Define a variable to file.
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 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_var()

subroutine, public mod_atmos_vars::atmos_vars_restart_write_var ( )

Write restart of atmospheric variables.

Definition at line 2900 of file mod_atmos_vars.f90.

References scale_tracer::aq_name, mod_atmos_dyn_vars::atmos_dyn_vars_restart_write_var(), mod_atmos_phy_ae_vars::atmos_phy_ae_vars_restart_write_var(), mod_atmos_phy_ch_vars::atmos_phy_ch_vars_restart_write_var(), mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_write_var(), mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_write_var(), mod_atmos_phy_rd_vars::atmos_phy_rd_vars_restart_write_var(), mod_atmos_phy_sf_vars::atmos_phy_sf_vars_restart_write_var(), mod_atmos_phy_tb_vars::atmos_phy_tb_vars_restart_write_var(), 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, and rhot.

Referenced by mod_admin_restart::admin_restart().

2900  use scale_fileio, only: &
2901  fileio_write_var
2902  use mod_atmos_admin, only: &
2903  atmos_sw_dyn, &
2904  atmos_sw_phy_mp, &
2905  atmos_sw_phy_ae, &
2906  atmos_sw_phy_ch, &
2907  atmos_sw_phy_rd, &
2908  atmos_sw_phy_sf, &
2909  atmos_sw_phy_tb, &
2911  use mod_atmos_dyn_vars, only: &
2913  use mod_atmos_phy_mp_vars, only: &
2915  use mod_atmos_phy_ae_vars, only: &
2917  use mod_atmos_phy_ch_vars, only: &
2919  use mod_atmos_phy_rd_vars, only: &
2921  use mod_atmos_phy_sf_vars, only: &
2923  use mod_atmos_phy_tb_vars, only: &
2925  use mod_atmos_phy_cp_vars, only: &
2927 #ifdef _SDM
2928  use scale_atmos_phy_mp_sdm, only: &
2929  sd_rest_flg_out, &
2930  atmos_phy_mp_sdm_restart_write_var
2931 #endif
2932  implicit none
2933 
2934  integer iq
2935  !---------------------------------------------------------------------------
2936 
2937 #ifdef _SDM
2938  if( sd_rest_flg_out ) then
2939  call atmos_phy_mp_sdm_restart_write_var
2940  endif
2941 #endif
2942 
2943  if ( restart_fid .NE. -1 ) then
2944 
2945  call atmos_vars_fillhalo
2946 
2947  call atmos_vars_total
2948 
2949  call fileio_write_var( restart_fid, var_id(i_dens), dens(:,:,:), var_name(i_dens), 'ZXY' ) ! [IN]
2950  call fileio_write_var( restart_fid, var_id(i_momz), momz(:,:,:), var_name(i_momz), 'ZHXY' ) ! [IN]
2951  call fileio_write_var( restart_fid, var_id(i_momx), momx(:,:,:), var_name(i_momx), 'ZXHY' ) ! [IN]
2952  call fileio_write_var( restart_fid, var_id(i_momy), momy(:,:,:), var_name(i_momy), 'ZXYH' ) ! [IN]
2953  call fileio_write_var( restart_fid, var_id(i_rhot), rhot(:,:,:), var_name(i_rhot), 'ZXY' ) ! [IN]
2954 
2955  do iq = 1, qa
2956  call fileio_write_var( restart_fid, var_id(vmax+iq), qtrc(:,:,:,iq), aq_name(iq), 'ZXY' ) ! [IN]
2957  enddo
2958 
2959  endif
2960 
2969 
2970  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
module Atmosphere / Dynamics
subroutine, public atmos_phy_cp_vars_restart_write_var
Write restart.
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)
subroutine, public atmos_phy_sf_vars_restart_write_var
Write variables to restart file.
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
module Atmosphere / Physics Turbulence
logical, public atmos_sw_phy_mp
subroutine, public atmos_phy_mp_vars_restart_write_var
Write restart.
real(rp), dimension(:,:,:), allocatable, target, public momy
module Atmosphere / Physics Chemistry
subroutine, public atmos_phy_rd_vars_restart_write_var
Write variables to restart file.
module ATMOSPHERE / Physics Cloud Microphysics
subroutine, public atmos_phy_ch_vars_restart_write_var
Write restart.
subroutine, public atmos_dyn_vars_restart_write_var
Write variables to restart file.
subroutine, public atmos_phy_ae_vars_restart_write_var
Write restart.
module ATMOSPHERE / Physics Aerosol Microphysics
subroutine, public atmos_phy_tb_vars_restart_write_var
Write restart.
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 56 of file mod_atmos_vars.f90.

Referenced by mod_admin_restart::admin_restart(), mod_admin_restart::admin_restart_setup(), atmos_vars_setup(), mod_mkinit::mkinit(), and mod_rm_driver::scalerm().

56  logical, public :: atmos_restart_output = .false.

◆ atmos_restart_check

logical, public mod_atmos_vars::atmos_restart_check = .false.

check value consistency?

Definition at line 57 of file mod_atmos_vars.f90.

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

57  logical, public :: atmos_restart_check = .false.

◆ atmos_restart_in_basename

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

basename of the restart file

Definition at line 59 of file mod_atmos_vars.f90.

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

59  character(len=H_LONG), public :: atmos_restart_in_basename = ''

◆ atmos_restart_out_basename

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

basename of the output file

Definition at line 60 of file mod_atmos_vars.f90.

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

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

◆ 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 61 of file mod_atmos_vars.f90.

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

61  character(len=H_MID), public :: atmos_restart_out_title = 'ATMOS restart'

◆ atmos_restart_out_dtype

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

REAL4 or REAL8.

Definition at line 62 of file mod_atmos_vars.f90.

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

62  character(len=H_MID), public :: atmos_restart_out_dtype = 'DEFAULT'

◆ atmos_restart_in_allowmissingq

logical, public mod_atmos_vars::atmos_restart_in_allowmissingq = .false.

Definition at line 63 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup().

63  logical, public :: atmos_restart_in_allowmissingq = .false.

◆ atmos_restart_check_basename

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

Definition at line 65 of file mod_atmos_vars.f90.

Referenced by atmos_vars_restart_check(), and atmos_vars_setup().

65  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 66 of file mod_atmos_vars.f90.

Referenced by atmos_vars_restart_check(), and atmos_vars_setup().

66  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 76 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup().

76  real(RP), public, target, allocatable :: dens_avw(:,:,:)

◆ momz_avw

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

Definition at line 77 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup().

77  real(RP), public, target, allocatable :: momz_avw(:,:,:)

◆ momx_avw

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

Definition at line 78 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup().

78  real(RP), public, target, allocatable :: momx_avw(:,:,:)

◆ momy_avw

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

Definition at line 79 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup().

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

◆ rhot_avw

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

Definition at line 80 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup().

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

◆ qtrc_avw

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

Definition at line 81 of file mod_atmos_vars.f90.

Referenced by atmos_vars_setup().

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

◆ dens_av

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

Definition at line 83 of file mod_atmos_vars.f90.

Referenced by mod_atmos_dyn_driver::atmos_dyn_driver(), mod_atmos_phy_tb_driver::atmos_phy_tb_driver(), atmos_vars_restart_read(), and atmos_vars_setup().

83  real(RP), public, pointer :: dens_av(:,:,:)
real(rp), dimension(:,:,:), pointer, public dens_av

◆ momz_av

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

Definition at line 84 of file mod_atmos_vars.f90.

Referenced by mod_atmos_dyn_driver::atmos_dyn_driver(), mod_atmos_phy_tb_driver::atmos_phy_tb_driver(), atmos_vars_restart_read(), and atmos_vars_setup().

84  real(RP), public, pointer :: momz_av(:,:,:)
real(rp), dimension(:,:,:), pointer, public momz_av

◆ momx_av

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

Definition at line 85 of file mod_atmos_vars.f90.

Referenced by mod_atmos_dyn_driver::atmos_dyn_driver(), mod_atmos_phy_tb_driver::atmos_phy_tb_driver(), atmos_vars_restart_read(), and atmos_vars_setup().

85  real(RP), public, pointer :: momx_av(:,:,:)
real(rp), dimension(:,:,:), pointer, public momx_av

◆ momy_av

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

Definition at line 86 of file mod_atmos_vars.f90.

Referenced by mod_atmos_dyn_driver::atmos_dyn_driver(), mod_atmos_phy_tb_driver::atmos_phy_tb_driver(), atmos_vars_restart_read(), and atmos_vars_setup().

86  real(RP), public, pointer :: momy_av(:,:,:)
real(rp), dimension(:,:,:), pointer, public momy_av

◆ rhot_av

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

Definition at line 87 of file mod_atmos_vars.f90.

Referenced by mod_atmos_dyn_driver::atmos_dyn_driver(), mod_atmos_phy_tb_driver::atmos_phy_tb_driver(), atmos_vars_restart_read(), and atmos_vars_setup().

87  real(RP), public, pointer :: rhot_av(:,:,:)
real(rp), dimension(:,:,:), pointer, public rhot_av

◆ qtrc_av

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

Definition at line 88 of file mod_atmos_vars.f90.

Referenced by mod_atmos_dyn_driver::atmos_dyn_driver(), mod_atmos_phy_tb_driver::atmos_phy_tb_driver(), atmos_vars_restart_read(), and atmos_vars_setup().

88  real(RP), public, pointer :: qtrc_av(:,:,:,:)
real(rp), dimension(:,:,:,:), pointer, public 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

◆ temp

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

◆ pres

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

◆ w

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

Definition at line 101 of file mod_atmos_vars.f90.

Referenced by mod_atmos_phy_sf_driver::atmos_phy_sf_driver(), mod_atmos_driver::atmos_surface_set(), atmos_vars_diagnostics(), atmos_vars_history(), atmos_vars_monitor(), and atmos_vars_setup().

101  real(RP), public, allocatable :: w (:,:,:) ! velocity w [m/s]

◆ u

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

Definition at line 102 of file mod_atmos_vars.f90.

Referenced by mod_atmos_phy_sf_driver::atmos_phy_sf_driver(), mod_atmos_driver::atmos_surface_set(), atmos_vars_diagnostics(), atmos_vars_history(), atmos_vars_monitor(), and atmos_vars_setup().

102  real(RP), public, allocatable :: u (:,:,:) ! velocity u [m/s]

◆ v

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

◆ pott

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

Definition at line 104 of file mod_atmos_vars.f90.

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

104  real(RP), public, allocatable :: pott(:,:,:) ! potential temperature [K]