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  real(RP), private :: atmos_dyn_wdamp_tau = -1.0_rp ! maximum tau for Rayleigh damping of w [s]
76  real(RP), private :: atmos_dyn_wdamp_height = -1.0_rp ! height to start apply Rayleigh damping [m]
77  integer, private :: atmos_dyn_wdamp_layer = -1 ! layer number to start apply Rayleigh damping [num]
78 
79  ! Coriolis force
80  logical, private :: atmos_dyn_enable_coriolis = .false. ! enable coriolis force?
81 
82  ! Divergence damping
83  real(RP), private :: atmos_dyn_divdmp_coef = 0.0_rp ! Divergence dumping coef
84 
85  ! Flux-Corrected Transport limiter
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.
90 
91  !-----------------------------------------------------------------------------
92 contains
93  !-----------------------------------------------------------------------------
95  subroutine atmos_dyn_driver_setup
96  use scale_process, only: &
98  use scale_grid, only: &
99  grid_fz, &
100  grid_cdz, &
101  grid_cdx, &
102  grid_cdy, &
103  grid_fdz, &
104  grid_fdx, &
105  grid_fdy
106  use scale_grid_real, only: &
107  real_lat
108  use scale_time, only: &
110  use mod_atmos_admin, only: &
111  atmos_sw_dyn, &
113  use mod_atmos_vars, only: &
114  dens, &
115  momz, &
116  momx, &
117  momy, &
118  rhot, &
119  qtrc
120  use mod_atmos_dyn_vars, only: &
121  prog
122  use scale_atmos_dyn, only: &
124  implicit none
125 
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
146 
147  real(RP) :: dt
148  integer :: ierr
149  !---------------------------------------------------------------------------
150 
151  if( io_l ) write(io_fid_log,*)
152  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[ATMOS DYN] / Origin[SCALE-RM]'
153 
154  if ( atmos_sw_dyn ) then
155 
156  !--- read namelist
157  rewind(io_fid_conf)
158  read(io_fid_conf,nml=param_atmos_dyn,iostat=ierr)
159  if( ierr < 0 ) then !--- missing
160  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
161  elseif( ierr > 0 ) then !--- fatal error
162  write(*,*) 'xxx Not appropriate names in namelist PARAM_ATMOS_DYN. Check!'
163  call prc_mpistop
164  endif
165  if( io_nml ) write(io_fid_nml,nml=param_atmos_dyn)
166 
167  dt = real(time_dtsec_atmos_dyn,kind=rp)
168 
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!'
171  call prc_mpistop
172  elseif( atmos_dyn_wdamp_layer > 0 ) then
173  atmos_dyn_wdamp_height = grid_fz(atmos_dyn_wdamp_layer+ks-1)
174  endif
175 
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!'
180  call prc_mpistop
181  end if
182 
183  if ( atmos_sw_dyn ) then
184  if( io_l ) write(io_fid_log,*)
185  if( io_l ) write(io_fid_log,*) '*** Scheme for Large time step : ', trim(atmos_dyn_tinteg_large_type)
186  if( io_l ) write(io_fid_log,*) '*** Scheme for Short time step : ', trim(atmos_dyn_tinteg_short_type)
187  if( io_l ) write(io_fid_log,*) '*** Scheme for Tracer advection : ', trim(atmos_dyn_tinteg_tracer_type)
188  endif
189 
195  atmos_dyn_fvm_flux_type, & ! [IN]
197  dens, momz, momx, momy, rhot, qtrc, & ! [IN]
198  prog, & ! [IN]
199  grid_cdz, grid_cdx, grid_cdy, & ! [IN]
200  grid_fdz, grid_fdx, grid_fdy, & ! [IN]
201  atmos_dyn_wdamp_tau, & ! [IN]
202  atmos_dyn_wdamp_height, & ! [IN]
203  grid_fz, & ! [IN]
204  atmos_dyn_enable_coriolis, & ! [IN]
205  real_lat, & ! [IN]
206  none = atmos_dyn_type=='NONE' ) ! [IN]
207  endif
208 
209  return
210  end subroutine atmos_dyn_driver_setup
211 
212  !-----------------------------------------------------------------------------
214  subroutine atmos_dyn_driver( do_flag )
215  use scale_grid, only: &
216  grid_cdz, &
217  grid_cdx, &
218  grid_cdy, &
219  grid_fdz, &
220  grid_fdx, &
221  grid_fdy, &
222  grid_rcdz, &
223  grid_rcdx, &
224  grid_rcdy, &
225  grid_rfdz, &
226  grid_rfdx, &
227  grid_rfdy
228  use scale_grid_real, only: &
229  real_phi
230  use scale_gridtrans, only: &
231  gtrans_gsqrt, &
232  gtrans_j13g, &
233  gtrans_j23g, &
234  gtrans_j33g, &
236  use scale_time, only: &
237  time_dtsec, &
239  use mod_atmos_admin, only: &
241  use mod_atmos_vars, only: &
243  dens, &
244  momz, &
245  momx, &
246  momy, &
247  rhot, &
248  qtrc, &
249  dens_av, &
250  momz_av, &
251  momx_av, &
252  momy_av, &
253  rhot_av, &
254  qtrc_av, &
255  dens_tp, &
256  momz_tp, &
257  momx_tp, &
258  momy_tp, &
259  rhot_tp, &
260  rhoq_tp
261  use mod_atmos_dyn_vars, only: &
262  prog
263  use scale_atmos_refstate, only: &
268  use scale_atmos_boundary, only: &
281  use scale_atmos_dyn, only: &
282  atmos_dyn
283  implicit none
284 
285  logical, intent(in) :: do_flag
286  !---------------------------------------------------------------------------
287 
288  if ( do_flag ) then
289  call atmos_dyn( dens, momz, momx, momy, rhot, qtrc, & ! [INOUT]
290  prog, & ! [IN]
291  dens_av, momz_av, momx_av, momy_av, rhot_av, qtrc_av, & ! [INOUT]
293  grid_cdz, grid_cdx, grid_cdy, & ! [IN]
294  grid_fdz, grid_fdx, grid_fdy, & ! [IN]
295  grid_rcdz, grid_rcdx, grid_rcdy, & ! [IN]
296  grid_rfdz, grid_rfdx, grid_rfdy, & ! [IN]
297  real_phi, & ! [IN]
298  gtrans_gsqrt, & ! [IN]
301  atmos_refstate_dens, & ! [IN]
302  atmos_refstate_pott, & ! [IN]
303  atmos_refstate_qv, & ! [IN]
304  atmos_refstate_pres, & ! [IN]
305  atmos_dyn_numerical_diff_coef, & ! [IN]
306  atmos_dyn_numerical_diff_coef_tracer, & ! [IN]
307  atmos_dyn_numerical_diff_order, & ! [IN]
308  atmos_dyn_numerical_diff_sfc_fact, & ! [IN]
309  atmos_dyn_numerical_diff_use_refstate, & ! [IN]
310  atmos_boundary_dens, & ! [IN]
311  atmos_boundary_velz, & ! [IN]
312  atmos_boundary_velx, & ! [IN]
313  atmos_boundary_vely, & ! [IN]
314  atmos_boundary_pott, & ! [IN]
315  atmos_boundary_qtrc, & ! [IN]
316  atmos_boundary_alpha_dens, & ! [IN]
317  atmos_boundary_alpha_velz, & ! [IN]
318  atmos_boundary_alpha_velx, & ! [IN]
319  atmos_boundary_alpha_vely, & ! [IN]
320  atmos_boundary_alpha_pott, & ! [IN]
321  atmos_boundary_alpha_qtrc, & ! [IN]
322  atmos_dyn_divdmp_coef, & ! [IN]
323  atmos_dyn_flag_fct_momentum, & ! [IN]
324  atmos_dyn_flag_fct_t, & ! [IN]
325  atmos_dyn_flag_fct_tracer, & ! [IN]
326  atmos_dyn_flag_fct_along_stream, & ! [IN]
327  atmos_use_average, & ! [IN]
328  time_dtsec, & ! [IN]
329  time_dtsec_atmos_dyn ) ! [IN]
330 
331  call atmos_vars_total
332  endif
333 
334  return
335  end subroutine atmos_dyn_driver
336 
337 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 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)
Definition: scale_stdio.F90:61
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
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.
module grid index
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)
Definition: scale_stdio.F90:62
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
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.
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]
integer, public ks
start point of inner domain: z, local
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)
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]
integer, public io_fid_nml
Log file ID (only for output namelist)
Definition: scale_stdio.F90:57
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