SCALE-RM
scale_atmos_dyn_tstep_short.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
10 !-------------------------------------------------------------------------------
11 #include "scalelib.h"
13  !-----------------------------------------------------------------------------
14  !
15  !++ used modules
16  !
17  use scale_precision
18  use scale_io
19  use scale_prof
21  use scale_index
22  use scale_tracer
23  !-----------------------------------------------------------------------------
24  implicit none
25  private
26  !-----------------------------------------------------------------------------
27  !
28  !++ Public procedure
29  !
31 
32  abstract interface
33 
34  subroutine short_setup
35  end subroutine short_setup
36 
38  subroutine short( DENS_new, MOMZ_new, MOMX_new, MOMY_new, RHOT_new, & ! (out)
39  prog_new, & ! (out)
40  mflx_hi, tflx_hi, & ! (out)
41  dens0, momz0, momx0, momy0, rhot0, & ! (in)
42  dens, momz, momx, momy, rhot, & ! (in)
43  dens_t, momz_t, momx_t, momy_t, rhot_t, & ! (in)
44  prog0, prog, & ! (in)
45  dpres0, rt2p, corioli, & ! (in)
46  num_diff, wdamp_coef, divdmp_coef, ddiv, & ! (in)
47  flag_fct_momentum, flag_fct_t, & ! (in)
48  flag_fct_along_stream, & ! (in)
49  cdz, fdz, fdx, fdy, & ! (in)
50  rcdz, rcdx, rcdy, rfdz, rfdx, rfdy, & ! (in)
51  phi, gsqrt, j13g, j23g, j33g, mapf, & ! (in)
52  ref_dens, ref_rhot, & ! (in)
53  bnd_w, bnd_e, bnd_s, bnd_n, twod, & ! (in)
54  dtrk, last ) ! (in)
55  use scale_precision
57  use scale_index
58  real(RP), intent(out) :: DENS_new(KA,IA,JA) ! prognostic variables
59  real(RP), intent(out) :: MOMZ_new(KA,IA,JA) !
60  real(RP), intent(out) :: MOMX_new(KA,IA,JA) !
61  real(RP), intent(out) :: MOMY_new(KA,IA,JA) !
62  real(RP), intent(out) :: RHOT_new(KA,IA,JA) !
63  real(RP), intent(out) :: PROG_new(KA,IA,JA,VA) !
64 
65  real(RP), intent(inout) :: mflx_hi(KA,IA,JA,3) ! mass flux
66  real(RP), intent(out) :: tflx_hi(KA,IA,JA,3) ! internal energy flux
67 
68  real(RP), intent(in),target :: DENS0(KA,IA,JA) ! prognostic variables at previous dynamical time step
69  real(RP), intent(in),target :: MOMZ0(KA,IA,JA) !
70  real(RP), intent(in),target :: MOMX0(KA,IA,JA) !
71  real(RP), intent(in),target :: MOMY0(KA,IA,JA) !
72  real(RP), intent(in),target :: RHOT0(KA,IA,JA) !
73 
74  real(RP), intent(in) :: DENS(KA,IA,JA) ! prognostic variables at previous RK step
75  real(RP), intent(in) :: MOMZ(KA,IA,JA) !
76  real(RP), intent(in) :: MOMX(KA,IA,JA) !
77  real(RP), intent(in) :: MOMY(KA,IA,JA) !
78  real(RP), intent(in) :: RHOT(KA,IA,JA) !
79 
80  real(RP), intent(in) :: DENS_t(KA,IA,JA) ! tendency
81  real(RP), intent(in) :: MOMZ_t(KA,IA,JA) !
82  real(RP), intent(in) :: MOMX_t(KA,IA,JA) !
83  real(RP), intent(in) :: MOMY_t(KA,IA,JA) !
84  real(RP), intent(in) :: RHOT_t(KA,IA,JA) !
85 
86  real(RP), intent(in) :: PROG0(KA,IA,JA,VA)
87  real(RP), intent(in) :: PROG (KA,IA,JA,VA)
88 
89  real(RP), intent(in) :: DPRES0 (KA,IA,JA)
90  real(RP), intent(in) :: RT2P (KA,IA,JA)
91  real(RP), intent(in) :: CORIOLI ( IA,JA)
92  real(RP), intent(in) :: num_diff(KA,IA,JA,5,3)
93  real(RP), intent(in) :: wdamp_coef(KA)
94  real(RP), intent(in) :: divdmp_coef
95  real(RP), intent(in) :: DDIV(KA,IA,JA)
96 
97  logical, intent(in) :: FLAG_FCT_MOMENTUM
98  logical, intent(in) :: FLAG_FCT_T
99  logical, intent(in) :: FLAG_FCT_ALONG_STREAM
100 
101  real(RP), intent(in) :: CDZ (KA)
102  real(RP), intent(in) :: FDZ (KA-1)
103  real(RP), intent(in) :: FDX (IA-1)
104  real(RP), intent(in) :: FDY (JA-1)
105  real(RP), intent(in) :: RCDZ(KA)
106  real(RP), intent(in) :: RCDX(IA)
107  real(RP), intent(in) :: RCDY(JA)
108  real(RP), intent(in) :: RFDZ(KA-1)
109  real(RP), intent(in) :: RFDX(IA-1)
110  real(RP), intent(in) :: RFDY(JA-1)
111 
112  real(RP), intent(in) :: PHI (KA,IA,JA)
113  real(RP), intent(in) :: GSQRT (KA,IA,JA,7)
114  real(RP), intent(in) :: J13G (KA,IA,JA,7)
115  real(RP), intent(in) :: J23G (KA,IA,JA,7)
116  real(RP), intent(in) :: J33G
117  real(RP), intent(in) :: MAPF (IA,JA,2,4)
118  real(RP), intent(in) :: REF_dens(KA,IA,JA)
119  real(RP), intent(in) :: REF_rhot(KA,IA,JA)
120 
121  logical, intent(in) :: BND_W
122  logical, intent(in) :: BND_E
123  logical, intent(in) :: BND_S
124  logical, intent(in) :: BND_N
125  logical, intent(in) :: TwoD
126 
127  real(RP), intent(in) :: dtrk
128  logical, intent(in) :: last
129  end subroutine short
130 
131  end interface
132 
133  procedure(short_setup), pointer :: atmos_dyn_tstep_short_setup => null()
135  procedure(short), pointer :: atmos_dyn_tstep_short => null()
136  public :: atmos_dyn_tstep_short
137 
138  !-----------------------------------------------------------------------------
139  !
140  !++ Public parameters & variables
141  !
142  !-----------------------------------------------------------------------------
143  !
144  !++ Private procedure
145  !
146  !-----------------------------------------------------------------------------
147  !
148  !++ Private parameters & variables
149  !
150  !-----------------------------------------------------------------------------
151 contains
152  !-----------------------------------------------------------------------------
155  ATMOS_DYN_TYPE, &
156  VA_out, &
157  VAR_NAME, VAR_DESC, VAR_UNIT )
158  use scale_precision
160  use scale_index
161  use scale_prc, only: &
162  prc_abort
175  implicit none
176 
177  character(len=*), intent(in) :: atmos_dyn_type
178  integer, intent(out) :: va_out
179  character(len=H_SHORT), intent(out) :: var_name(:)
180  character(len=H_MID), intent(out) :: var_desc(:)
181  character(len=H_SHORT), intent(out) :: var_unit(:)
182  !---------------------------------------------------------------------------
183 
184  select case( atmos_dyn_type )
185  case( 'FVM-HEVE', 'HEVE' )
186 
187  call atmos_dyn_tstep_short_fvm_heve_regist( atmos_dyn_type, & ! [IN]
188  va_out, & ! [OUT]
189  var_name, var_desc, var_unit ) ! [OUT]
190 
193 
194  case( 'FVM-HEVI', 'HEVI' )
195 
196  call atmos_dyn_tstep_short_fvm_hevi_regist( atmos_dyn_type, & ! [IN]
197  va_out, & ! [OUT]
198  var_name, var_desc, var_unit ) ! [OUT]
199 
202 
203  case( 'FVM-HIVI', 'HIVI' )
204 
205  log_error("ATMOS_DYN_Tstep_short_regist",*) 'HIVI is tentatively disabled'
206  call prc_abort
207 
208  call atmos_dyn_tstep_short_fvm_hivi_regist( atmos_dyn_type, & ! [IN]
209  va_out, & ! [OUT]
210  var_name, var_desc, var_unit ) ! [OUT]
211 
214 
215  case( 'OFF', 'NONE' )
216 
217  va_out = 0
218  var_name(:) = ""
219  var_desc(:) = ""
220  var_unit(:) = ""
221 
222  case default
223  log_error("ATMOS_DYN_Tstep_short_regist",*) 'ATMOS_DYN_TYPE is invalid: ', atmos_dyn_type
224  call prc_abort
225  end select
226 
227  return
228  end subroutine atmos_dyn_tstep_short_regist
229 
subroutine, public atmos_dyn_tstep_short_fvm_heve_regist(ATMOS_DYN_TYPE, VA_out, VAR_NAME, VAR_DESC, VAR_UNIT)
Register.
subroutine, public atmos_dyn_tstep_short_fvm_heve(DENS_RK, MOMZ_RK, MOMX_RK, MOMY_RK, RHOT_RK, PROG_RK, mflx_hi, tflx_hi, DENS0, MOMZ0, MOMX0, MOMY0, RHOT0, DENS, MOMZ, MOMX, MOMY, RHOT, DENS_t, MOMZ_t, MOMX_t, MOMY_t, RHOT_t, PROG0, PROG, DPRES0, RT2P, CORIOLI, num_diff, wdamp_coef, divdmp_coef, DDIV, FLAG_FCT_MOMENTUM, FLAG_FCT_T, FLAG_FCT_ALONG_STREAM, CDZ, FDZ, FDX, FDY, RCDZ, RCDX, RCDY, RFDZ, RFDX, RFDY, PHI, GSQRT, J13G, J23G, J33G, MAPF, REF_dens, REF_rhot, BND_W, BND_E, BND_S, BND_N, TwoD, dtrk, last)
subroutine, public atmos_dyn_tstep_short_fvm_hevi_regist(ATMOS_DYN_TYPE, VA_out, VAR_NAME, VAR_DESC, VAR_UNIT)
Register.
subroutine, public atmos_dyn_tstep_short_fvm_hevi(DENS_RK, MOMZ_RK, MOMX_RK, MOMY_RK, RHOT_RK, PROG_RK, mflx_hi, tflx_hi, DENS0, MOMZ0, MOMX0, MOMY0, RHOT0, DENS, MOMZ, MOMX, MOMY, RHOT, DENS_t, MOMZ_t, MOMX_t, MOMY_t, RHOT_t, PROG0, PROG, DPRES0, RT2P, CORIOLI, num_diff, wdamp_coef, divdmp_coef, DDIV, FLAG_FCT_MOMENTUM, FLAG_FCT_T, FLAG_FCT_ALONG_STREAM, CDZ, FDZ, FDX, FDY, RCDZ, RCDX, RCDY, RFDZ, RFDX, RFDY, PHI, GSQRT, J13G, J23G, J33G, MAPF, REF_dens, REF_rhot, BND_W, BND_E, BND_S, BND_N, TwoD, dtrk, last)
subroutine, public atmos_dyn_tstep_short_fvm_hivi(DENS_RK, MOMZ_RK, MOMX_RK, MOMY_RK, RHOT_RK, PROG_RK, mflx_hi, tflx_hi, DENS0, MOMZ0, MOMX0, MOMY0, RHOT0, DENS, MOMZ, MOMX, MOMY, RHOT, DENS_t, MOMZ_t, MOMX_t, MOMY_t, RHOT_t, PROG0, PROG, DPRES0, RT2P, CORIOLI, num_diff, wdamp_coef, divdmp_coef, DDIV, FLAG_FCT_MOMENTUM, FLAG_FCT_T, FLAG_FCT_ALONG_STREAM, CDZ, FDZ, FDX, FDY, RCDZ, RCDX, RCDY, RFDZ, RFDX, RFDY, PHI, GSQRT, J13G, J23G, J33G, MAPF, REF_dens, REF_rhot, BND_W, BND_E, BND_S, BND_N, TwoD, dtrk, last)
subroutine, public atmos_dyn_tstep_short_fvm_hivi_regist(ATMOS_DYN_TYPE, VA_out, VAR_NAME, VAR_DESC, VAR_UNIT)
Register.
module Atmosphere / Dynamical scheme
procedure(short), pointer, public atmos_dyn_tstep_short
subroutine, public atmos_dyn_tstep_short_regist(ATMOS_DYN_TYPE, VA_out, VAR_NAME, VAR_DESC, VAR_UNIT)
Register.
procedure(short_setup), pointer, public atmos_dyn_tstep_short_setup
module atmosphere / grid / cartesC index
module Index
Definition: scale_index.F90:11
module STDIO
Definition: scale_io.F90:10
module PROCESS
Definition: scale_prc.F90:11
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:350
module PRECISION
module profiler
Definition: scale_prof.F90:11
module TRACER