69 integer,
private :: atmos_dyn_numerical_diff_order = 1
70 real(RP),
private :: atmos_dyn_numerical_diff_coef = 1.0e-4_rp
71 real(RP),
private :: atmos_dyn_numerical_diff_coef_tracer = 0.0_rp
72 real(RP),
private :: atmos_dyn_numerical_diff_sfc_fact = 1.0_rp
73 logical ,
private :: atmos_dyn_numerical_diff_use_refstate = .true.
75 real(RP),
private :: atmos_dyn_wdamp_tau = -1.0_rp
76 real(RP),
private :: atmos_dyn_wdamp_height = -1.0_rp
77 integer,
private :: atmos_dyn_wdamp_layer = -1
80 logical,
private :: atmos_dyn_enable_coriolis = .false.
83 real(RP),
private :: atmos_dyn_divdmp_coef = 0.0_rp
86 logical,
private :: atmos_dyn_flag_fct_momentum = .false.
87 logical,
private :: atmos_dyn_flag_fct_t = .false.
88 logical,
private :: atmos_dyn_flag_fct_tracer = .false.
89 logical,
private :: atmos_dyn_flag_fct_along_stream = .true.
126 namelist / param_atmos_dyn / &
132 atmos_dyn_numerical_diff_order, &
133 atmos_dyn_numerical_diff_coef, &
134 atmos_dyn_numerical_diff_coef_tracer, &
135 atmos_dyn_numerical_diff_sfc_fact, &
136 atmos_dyn_numerical_diff_use_refstate, &
137 atmos_dyn_wdamp_tau, &
138 atmos_dyn_wdamp_height, &
139 atmos_dyn_wdamp_layer, &
140 atmos_dyn_enable_coriolis, &
141 atmos_dyn_divdmp_coef, &
142 atmos_dyn_flag_fct_momentum, &
143 atmos_dyn_flag_fct_t, &
144 atmos_dyn_flag_fct_tracer, &
145 atmos_dyn_flag_fct_along_stream
152 if(
io_l )
write(
io_fid_log,*)
'++++++ Module[DRIVER] / Categ[ATMOS DYN] / Origin[SCALE-RM]' 160 if(
io_l )
write(
io_fid_log,*)
'*** Not found namelist. Default used.' 161 elseif( ierr > 0 )
then 162 write(*,*)
'xxx Not appropriate names in namelist PARAM_ATMOS_DYN. Check!' 169 if ( atmos_dyn_wdamp_layer >
kmax )
then 170 write(*,*)
'xxx ATMOS_DYN_wdamp_layer should be less than total number of vertical layer(KA). Check!' 172 elseif( atmos_dyn_wdamp_layer > 0 )
then 173 atmos_dyn_wdamp_height =
grid_fz(atmos_dyn_wdamp_layer+
ks-1)
176 if ( atmos_dyn_wdamp_tau < 0.0_rp )
then 177 atmos_dyn_wdamp_tau = dt * 10.0_rp
178 elseif ( atmos_dyn_wdamp_tau < dt )
then 179 write(*,*)
'xxx ATMOS_DYN_wdamp_tau should be larger than TIME_DT_ATMOS_DYN. Check!' 201 atmos_dyn_wdamp_tau, &
202 atmos_dyn_wdamp_height, &
204 atmos_dyn_enable_coriolis, &
285 logical,
intent(in) :: do_flag
305 atmos_dyn_numerical_diff_coef, &
306 atmos_dyn_numerical_diff_coef_tracer, &
307 atmos_dyn_numerical_diff_order, &
308 atmos_dyn_numerical_diff_sfc_fact, &
309 atmos_dyn_numerical_diff_use_refstate, &
322 atmos_dyn_divdmp_coef, &
323 atmos_dyn_flag_fct_momentum, &
324 atmos_dyn_flag_fct_t, &
325 atmos_dyn_flag_fct_tracer, &
326 atmos_dyn_flag_fct_along_stream, &
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_velx
real(rp), dimension(:,:,:), allocatable, public dens_tp
real(rp), dimension(:,:,:), allocatable, target, public momz
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_velz
real(rp), dimension(:), allocatable, public grid_rcdy
reciprocal of center-dy
subroutine, public prc_mpistop
Abort MPI.
real(rp), dimension(:,:,:), allocatable, target, public rhot
real(rp), dimension(:,:,:,:), allocatable, public gtrans_j23g
(2,3) element of Jacobian matrix * {G}^1/2
real(rp), dimension(:,:,:), allocatable, public momy_tp
real(rp), dimension(:), allocatable, public grid_fdy
y-length of grid(j+1) to grid(j) [m]
real(rp), dimension(qa_max), public tracer_r
character(len=h_short), public atmos_dyn_tstep_large_type
logical, public io_l
output log or not? (this process)
real(rp), dimension(:), allocatable, public grid_rcdx
reciprocal of center-dx
character(len=h_short), public atmos_dyn_fvm_flux_type
module Atmosphere / Dynamics
module ATMOSPHERE / Reference state
real(rp), dimension(:,:,:), allocatable, public atmos_refstate_pott
refernce potential temperature [K]
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_alpha_pott
module ATMOSPHERIC Variables
module Atmosphere / Dynamics FENT + FCT
real(rp), dimension(:,:,:,:), pointer, public qtrc_av
real(rp), dimension(:,:,:), allocatable, target, public momx
real(rp), public gtrans_j33g
(3,3) element of Jacobian matrix * {G}^1/2
real(rp), dimension(:,:,:), allocatable, public rhot_tp
character(len=h_short), public atmos_dyn_tinteg_tracer_type
module Atmosphere / Dynamics
real(rp), dimension(:), allocatable, public grid_rfdy
reciprocal of face-dy
subroutine, public atmos_dyn_setup(DYN_Tinteg_Short_TYPE, DYN_Tinteg_Tracer_TYPE, DYN_Tinteg_Large_TYPE, DYN_Tstep_Tracer_TYPE, DYN_Tstep_Large_TYPE, DYN_FVM_FLUX_TYPE, DYN_FVM_FLUX_TYPE_TRACER, DENS, MOMZ, MOMX, MOMY, RHOT, QTRC, PROG, CDZ, CDX, CDY, FDZ, FDX, FDY, wdamp_tau, wdamp_height, FZ, enable_coriolis, lat, none)
Setup.
real(rp), dimension(:,:,:), allocatable, target, public dens
real(rp), dimension(:), allocatable, public grid_rcdz
reciprocal of center-dz
real(rp), dimension(qa_max), public tracer_cv
subroutine, public atmos_dyn_driver(do_flag)
Dynamical Process (Wrapper)
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_alpha_velz
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_alpha_vely
subroutine, public atmos_dyn(DENS, MOMZ, MOMX, MOMY, RHOT, QTRC, PROG, DENS_av, MOMZ_av, MOMX_av, MOMY_av, RHOT_av, QTRC_av, DENS_tp, MOMZ_tp, MOMX_tp, MOMY_tp, RHOT_tp, RHOQ_tp, CDZ, CDX, CDY, FDZ, FDX, FDY, RCDZ, RCDX, RCDY, RFDZ, RFDX, RFDY, PHI, GSQRT, J13G, J23G, J33G, MAPF, AQ_R, AQ_CV, AQ_CP, AQ_MASS, REF_dens, REF_pott, REF_qv, REF_pres, ND_COEF, ND_COEF_Q, ND_ORDER, ND_SFC_FACT, ND_USE_RS, DAMP_DENS, DAMP_VELZ, DAMP_VELX, DAMP_VELY, DAMP_POTT, DAMP_QTRC, DAMP_alpha_DENS, DAMP_alpha_VELZ, DAMP_alpha_VELX, DAMP_alpha_VELY, DAMP_alpha_POTT, DAMP_alpha_QTRC, divdmp_coef, FLAG_FCT_MOMENTUM, FLAG_FCT_T, FLAG_FCT_TRACER, FLAG_FCT_ALONG_STREAM, USE_AVERAGE, DTSEC, DTSEC_DYN)
Dynamical Process.
real(rp), dimension(qa_max), public tracer_cp
subroutine, public atmos_dyn_driver_setup
Setup.
logical, public io_nml
output log or not? (for namelist, this process)
real(rp), dimension(:,:,:,:), allocatable, public atmos_boundary_qtrc
real(rp), dimension(:,:,:), pointer, public momx_av
real(rp), dimension(:,:,:,:), allocatable, public gtrans_mapf
map factor
real(rp), dimension(:), allocatable, public grid_fdz
z-length of grid(k+1) to grid(k) [m]
real(dp), public time_dtsec
time interval of model [sec]
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_vely
character(len=h_short), public atmos_dyn_tinteg_short_type
real(rp), dimension(:,:,:), allocatable, public atmos_refstate_dens
refernce density [kg/m3]
character(len=h_short), public atmos_dyn_tstep_tracer_type
real(rp), dimension(:,:,:,:), allocatable, public rhoq_tp
integer, public kmax
of computational cells: z, local
real(rp), dimension(:), allocatable, public grid_fz
face coordinate [m]: z, local=global
logical, public atmos_sw_dyn
subroutine, public atmos_vars_total
Budget monitor for atmosphere.
real(dp), public time_dtsec_atmos_dyn
time interval of dynamics [sec]
character(len=h_short), public atmos_dyn_tinteg_large_type
real(rp), dimension(:,:,:), pointer, public dens_av
real(rp), dimension(:,:,:,:), allocatable, public prog
real(rp), dimension(:,:,:,:), allocatable, public gtrans_j13g
(1,3) element of Jacobian matrix * {G}^1/2
real(rp), dimension(:,:,:), allocatable, public atmos_refstate_pres
refernce pressure [Pa]
integer, public ks
start point of inner domain: z, local
real(rp), dimension(:,:,:), allocatable, public momx_tp
real(rp), dimension(:,:,:), allocatable, target, public momy
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_alpha_dens
real(rp), dimension(:,:,:), allocatable, public momz_tp
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_dens
real(rp), dimension(:,:,:,:), allocatable, public gtrans_gsqrt
transformation metrics from Z to Xi, {G}^1/2
real(rp), dimension(:,:,:), allocatable, public real_phi
geopotential [m2/s2] (cell center)
real(rp), dimension(:,:,:), allocatable, public atmos_refstate_qv
refernce vapor [kg/kg]
real(rp), dimension(:), allocatable, public grid_cdz
z-length of control volume [m]
real(rp), dimension(:), allocatable, public grid_fdx
x-length of grid(i+1) to grid(i) [m]
real(rp), dimension(:), allocatable, public grid_cdy
y-length of control volume [m]
module ATMOSPHERE / Boundary treatment
character(len=h_short), public atmos_dyn_type
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_pott
real(rp), dimension(:,:,:), pointer, public momz_av
real(rp), dimension(:), allocatable, public grid_rfdx
reciprocal of face-dx
real(rp), dimension(:), allocatable, public grid_rfdz
reciprocal of face-dz
character(len=h_short), public atmos_dyn_fvm_flux_tracer_type
real(rp), dimension(:,:,:), pointer, public rhot_av
integer, public io_fid_conf
Config file ID.
real(rp), dimension(:,:), allocatable, public real_lat
latitude [rad,-pi,pi]
integer, public io_fid_log
Log file ID.
real(rp), dimension(:,:,:), pointer, public momy_av
integer, parameter, public rp
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_alpha_velx
real(rp), dimension(:), allocatable, public grid_cdx
x-length of control volume [m]
integer, public io_fid_nml
Log file ID (only for output namelist)
real(rp), dimension(qa_max), public tracer_mass
logical, public atmos_use_average
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
real(rp), dimension(:,:,:,:), allocatable, public atmos_boundary_alpha_qtrc