SCALE-RM
mod_atmos_dyn_driver.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
17  !-----------------------------------------------------------------------------
18  !
19  !++ used modules
20  !
21  use scale_precision
22  use scale_stdio
23  use scale_prof
25  use scale_index
26  use scale_tracer
27  !-----------------------------------------------------------------------------
28  implicit none
29  private
30  !-----------------------------------------------------------------------------
31  !
32  !++ Public procedure
33  !
34  public :: atmos_dyn_driver_setup
35  public :: atmos_dyn_driver
36 
37  !-----------------------------------------------------------------------------
38  !
39  !++ Public parameters & variables
40  !
41  character(len=H_SHORT), public :: atmos_dyn_tstep_large_type = 'FVM-HEVE'
42  character(len=H_SHORT), public :: atmos_dyn_tstep_tracer_type = 'FVM-HEVE'
43 
44  character(len=H_SHORT), public :: atmos_dyn_tinteg_large_type = 'EULER' ! Type of time integration
45  ! 'RK3'
46  character(len=H_SHORT), public :: atmos_dyn_tinteg_short_type = 'RK4'
47  ! 'RK3WS2002'
48  ! 'RK3'
49  character(len=H_SHORT), public :: atmos_dyn_tinteg_tracer_type = 'RK3WS2002'
50  ! 'EULER'
51 
52  character(len=H_SHORT), public :: atmos_dyn_fvm_flux_type = 'CD4' ! Type of advective flux scheme (FVM)
53  character(len=H_SHORT), public :: atmos_dyn_fvm_flux_tracer_type = 'UD3KOREN1993'
54  ! 'CD2'
55  ! 'UD3'
56  ! 'CD4'
57  ! 'UD5'
58  ! 'CD6'
59 
60  !-----------------------------------------------------------------------------
61  !
62  !++ Private procedure
63  !
64  !-----------------------------------------------------------------------------
65  !
66  !++ Private parameters & variables
67  !
68  ! Numerical filter
69  integer, private :: atmos_dyn_numerical_diff_order = 1
70  real(RP), private :: atmos_dyn_numerical_diff_coef = 1.0e-4_rp ! nondimensional numerical diffusion
71  real(RP), private :: atmos_dyn_numerical_diff_coef_tracer = 0.0_rp ! nondimensional numerical diffusion for tracer
72  real(RP), private :: atmos_dyn_numerical_diff_sfc_fact = 1.0_rp
73  logical , private :: atmos_dyn_numerical_diff_use_refstate = .true.
74 
75  ! Coriolis force
76  logical, private :: atmos_dyn_enable_coriolis = .false. ! enable coriolis force?
77 
78  ! Divergence damping
79  real(RP), private :: atmos_dyn_divdmp_coef = 0.0_rp ! Divergence dumping coef
80 
81  ! Flux-Corrected Transport limiter
82  logical, private :: atmos_dyn_flag_fct_momentum = .false.
83  logical, private :: atmos_dyn_flag_fct_t = .false.
84  logical, private :: atmos_dyn_flag_fct_tracer = .false.
85  logical, private :: atmos_dyn_flag_fct_along_stream = .true.
86 
87  !-----------------------------------------------------------------------------
88 contains
89  !-----------------------------------------------------------------------------
91  subroutine atmos_dyn_driver_setup
92  use scale_process, only: &
94  use scale_grid, only: &
95  grid_cdz, &
96  grid_cdx, &
97  grid_cdy, &
98  grid_fdz, &
99  grid_fdx, &
100  grid_fdy
101  use scale_grid_real, only: &
102  real_lat
103  use scale_time, only: &
105  use mod_atmos_admin, only: &
106  atmos_sw_dyn, &
108  use mod_atmos_vars, only: &
109  dens, &
110  momz, &
111  momx, &
112  momy, &
113  rhot, &
114  qtrc
115  use mod_atmos_dyn_vars, only: &
116  prog
117  use scale_atmos_dyn, only: &
119  implicit none
120 
121  namelist / param_atmos_dyn / &
127  atmos_dyn_numerical_diff_order, &
128  atmos_dyn_numerical_diff_coef, &
129  atmos_dyn_numerical_diff_coef_tracer, &
130  atmos_dyn_numerical_diff_sfc_fact, &
131  atmos_dyn_numerical_diff_use_refstate, &
132  atmos_dyn_enable_coriolis, &
133  atmos_dyn_divdmp_coef, &
134  atmos_dyn_flag_fct_momentum, &
135  atmos_dyn_flag_fct_t, &
136  atmos_dyn_flag_fct_tracer, &
137  atmos_dyn_flag_fct_along_stream
138 
139  real(RP) :: DT
140  integer :: ierr
141  !---------------------------------------------------------------------------
142 
143  if( io_l ) write(io_fid_log,*)
144  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[ATMOS DYN] / Origin[SCALE-RM]'
145 
146  if ( atmos_sw_dyn ) then
147  !--- read namelist
148  rewind(io_fid_conf)
149  read(io_fid_conf,nml=param_atmos_dyn,iostat=ierr)
150  if( ierr < 0 ) then !--- missing
151  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
152  elseif( ierr > 0 ) then !--- fatal error
153  write(*,*) 'xxx Not appropriate names in namelist PARAM_ATMOS_DYN. Check!'
154  call prc_mpistop
155  endif
156  if( io_l ) write(io_fid_log,nml=param_atmos_dyn)
157 
158  dt = real(time_dtsec_atmos_dyn,kind=rp)
159 
160  if ( atmos_sw_dyn ) then
161  if( io_l ) write(io_fid_log,*) '*** Scheme for Large time step : ', trim(atmos_dyn_tinteg_large_type)
162  if( io_l ) write(io_fid_log,*) '*** Scheme for Short time step : ', trim(atmos_dyn_tinteg_short_type)
163  if( io_l ) write(io_fid_log,*) '*** Scheme for Tracer advection : ', trim(atmos_dyn_tinteg_tracer_type)
164  endif
165 
171  atmos_dyn_fvm_flux_type, & ! [IN]
173  dens, momz, momx, momy, rhot, qtrc, & ! [IN]
174  prog, & ! [IN]
175  grid_cdz, grid_cdx, grid_cdy, & ! [IN]
176  grid_fdz, grid_fdx, grid_fdy, & ! [IN]
177  atmos_dyn_enable_coriolis, & ! [IN]
178  real_lat, & ! [IN]
179  none = atmos_dyn_type=='NONE' ) ! [IN]
180  endif
181 
182  return
183  end subroutine atmos_dyn_driver_setup
184 
185  !-----------------------------------------------------------------------------
187  subroutine atmos_dyn_driver( do_flag )
188  use scale_grid, only: &
189  grid_cdz, &
190  grid_cdx, &
191  grid_cdy, &
192  grid_fdz, &
193  grid_fdx, &
194  grid_fdy, &
195  grid_rcdz, &
196  grid_rcdx, &
197  grid_rcdy, &
198  grid_rfdz, &
199  grid_rfdx, &
200  grid_rfdy
201  use scale_grid_real, only: &
202  real_phi
203  use scale_gridtrans, only: &
204  gtrans_gsqrt, &
205  gtrans_j13g, &
206  gtrans_j23g, &
207  gtrans_j33g, &
209  use scale_time, only: &
210  time_dtsec, &
212  use mod_atmos_admin, only: &
214  use mod_atmos_vars, only: &
216  dens, &
217  momz, &
218  momx, &
219  momy, &
220  rhot, &
221  qtrc, &
222  dens_av, &
223  momz_av, &
224  momx_av, &
225  momy_av, &
226  rhot_av, &
227  qtrc_av, &
228  dens_tp, &
229  momz_tp, &
230  momx_tp, &
231  momy_tp, &
232  rhot_tp, &
233  rhoq_tp
234  use mod_atmos_dyn_vars, only: &
235  prog
236  use scale_atmos_thermodyn, only: &
237  aq_cv
238  use scale_atmos_refstate, only: &
243  use scale_atmos_boundary, only: &
256 #ifndef DYN2
257  use scale_atmos_dyn, only: &
258  atmos_dyn
259 #else
260  use scale_atmos_dyn2, only: &
261  atmos_dyn
262 #endif
263  implicit none
264 
265  logical, intent(in) :: do_flag
266  !---------------------------------------------------------------------------
267 
268  if ( do_flag ) then
269  call atmos_dyn( dens, momz, momx, momy, rhot, qtrc, & ! [INOUT]
270  prog, & ! [IN]
271  dens_av, momz_av, momx_av, momy_av, rhot_av, qtrc_av, & ! [INOUT]
273  grid_cdz, grid_cdx, grid_cdy, & ! [IN]
274  grid_fdz, grid_fdx, grid_fdy, & ! [IN]
275  grid_rcdz, grid_rcdx, grid_rcdy, & ! [IN]
276  grid_rfdz, grid_rfdx, grid_rfdy, & ! [IN]
277  real_phi, & ! [IN]
278  gtrans_gsqrt, & ! [IN]
280  aq_cv, & ! [IN]
281  atmos_refstate_dens, & ! [IN]
282  atmos_refstate_pott, & ! [IN]
283  atmos_refstate_qv, & ! [IN]
284  atmos_refstate_pres, & ! [IN]
285  atmos_dyn_numerical_diff_coef, & ! [IN]
286  atmos_dyn_numerical_diff_coef_tracer, & ! [IN]
287  atmos_dyn_numerical_diff_order, & ! [IN]
288  atmos_dyn_numerical_diff_sfc_fact, & ! [IN]
289  atmos_dyn_numerical_diff_use_refstate, & ! [IN]
290  atmos_boundary_dens, & ! [IN]
291  atmos_boundary_velz, & ! [IN]
292  atmos_boundary_velx, & ! [IN]
293  atmos_boundary_vely, & ! [IN]
294  atmos_boundary_pott, & ! [IN]
295  atmos_boundary_qtrc, & ! [IN]
296  atmos_boundary_alpha_dens, & ! [IN]
297  atmos_boundary_alpha_velz, & ! [IN]
298  atmos_boundary_alpha_velx, & ! [IN]
299  atmos_boundary_alpha_vely, & ! [IN]
300  atmos_boundary_alpha_pott, & ! [IN]
301  atmos_boundary_alpha_qtrc, & ! [IN]
302  atmos_dyn_divdmp_coef, & ! [IN]
303  atmos_dyn_flag_fct_momentum, & ! [IN]
304  atmos_dyn_flag_fct_t, & ! [IN]
305  atmos_dyn_flag_fct_tracer, & ! [IN]
306  atmos_dyn_flag_fct_along_stream, & ! [IN]
307  atmos_use_average, & ! [IN]
308  time_dtsec, & ! [IN]
309  time_dtsec_atmos_dyn ) ! [IN]
310 
311  call atmos_vars_total
312  endif
313 
314  return
315  end subroutine atmos_dyn_driver
316 
317 end module mod_atmos_dyn_driver
module ATMOS admin
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 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, enable_coriolis, lat, none)
Setup.
subroutine, public prc_mpistop
Abort MPI.
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_CV, 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(:,:,:), 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]
character(len=h_short), public atmos_dyn_tstep_large_type
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
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
module STDIO
Definition: scale_stdio.F90:12
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
real(rp), dimension(:,:,:), allocatable, target, public dens
real(rp), dimension(:), allocatable, public grid_rcdz
reciprocal of center-dz
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
module grid index
subroutine, public atmos_dyn_driver_setup
Setup.
real(rp), dimension(:,:,:,:), allocatable, public atmos_boundary_qtrc
real(rp), dimension(:,:,:), pointer, public momx_av
real(rp), dimension(:,:,:,:), allocatable, public gtrans_mapf
map factor
module TRACER
module Index
Definition: scale_index.F90:14
module GRIDTRANS
real(rp), dimension(:), allocatable, public grid_fdz
z-length of grid(k+1) to grid(k) [m]
module GRID (real space)
real(dp), public time_dtsec
time interval of model [sec]
Definition: scale_time.F90:36
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
logical, public atmos_sw_dyn
subroutine, public atmos_vars_total
Budget monitor for atmosphere.
module TIME
Definition: scale_time.F90:15
real(dp), public time_dtsec_atmos_dyn
time interval of dynamics [sec]
Definition: scale_time.F90:38
module PROCESS
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]
real(rp), dimension(:), allocatable, public aq_cv
CV for each hydrometeors [J/kg/K].
real(rp), dimension(:,:,:), allocatable, public momx_tp
real(rp), dimension(:,:,:), allocatable, target, public momy
module GRID (cartesian)
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_alpha_dens
real(rp), dimension(:,:,:), allocatable, public momz_tp
real(rp), dimension(:,:,:), allocatable, public atmos_boundary_dens
module profiler
Definition: scale_prof.F90:10
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)
module ATMOSPHERE / Thermodynamics
real(rp), dimension(:,:,:), allocatable, public atmos_refstate_qv
refernce vapor [kg/kg]
module PRECISION
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.
Definition: scale_stdio.F90:55
real(rp), dimension(:,:), allocatable, public real_lat
latitude [rad,-pi,pi]
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
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]
logical, public atmos_use_average
real(rp), dimension(:,:,:,:), allocatable, target, public qtrc
real(rp), dimension(:,:,:,:), allocatable, public atmos_boundary_alpha_qtrc