SCALE-RM
scale_atmos_dyn_tstep_tracer_fvm_heve.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
13 !-------------------------------------------------------------------------------
14 #include "inc_openmp.h"
16  !-----------------------------------------------------------------------------
17  !
18  !++ used modules
19  !
20  use scale_precision
21  use scale_stdio
22  use scale_prof
24  use scale_index
25  use scale_tracer
26 
27 #ifdef DEBUG
28  use scale_debug, only: &
29  check
30  use scale_const, only: &
31  undef => const_undef, &
32  iundef => const_undef2
33 #endif
34  !-----------------------------------------------------------------------------
35  implicit none
36  private
37  !-----------------------------------------------------------------------------
38  !
39  !++ Public procedure
40  !
43 
44  !-----------------------------------------------------------------------------
45  !
46  !++ Public parameters & variables
47  !
48  !-----------------------------------------------------------------------------
49  !
50  !++ Private procedure
51  !
52  !-----------------------------------------------------------------------------
53  !
54  !++ Private parameters & variables
55  !
56  !-----------------------------------------------------------------------------
57 contains
58 
59  !-----------------------------------------------------------------------------
61  subroutine atmos_dyn_tstep_tracer_fvm_heve_setup( type )
62  use scale_process, only: &
64  implicit none
65  character(len=*), intent(in) :: type
66 
67  if ( type /= 'FVM-HEVE' ) then
68  write(*,*) 'xxx Tstep_tracer_type is not "FVM-HEVE"!'
69  call prc_mpistop
70  end if
71 
72  return
74 
76  QTRCo, & ! (out)
77  qtrc, qtrc0, rhoq_t, &! (in)
78  dens0, dens, & ! (in)
79  mflx_hi, num_diff, & ! (in)
80  gsqrt, mapf, & ! (in)
81  cdz, rcdz, rcdx, rcdy, & ! (in)
82  dtl, & ! (in)
83  flag_fct_tracer, & ! (in)
84  flag_fct_along_stream ) ! (in)
85  use scale_gridtrans, only: &
86  i_xyz, &
87  i_xyw, &
88  i_uyz, &
89  i_xvz, &
90  i_xy, &
91  i_uy, &
92  i_xv
93  use scale_atmos_dyn_common, only: &
95  use scale_atmos_dyn_fvm_flux, only: &
99  use scale_atmos_dyn_fvm_flux_ud1, only: &
103  implicit none
104  real(RP), intent(inout) :: qtrco (ka,ia,ja) ! could be identical to QTRC0
105  real(RP), intent(in) :: qtrc (ka,ia,ja)
106  real(RP), intent(in) :: qtrc0 (ka,ia,ja)
107  real(RP), intent(in) :: rhoq_t (ka,ia,ja)
108  real(RP), intent(in) :: dens0 (ka,ia,ja)
109  real(RP), intent(in) :: dens (ka,ia,ja)
110  real(RP), intent(in) :: mflx_hi (ka,ia,ja,3)
111  real(RP), intent(in) :: num_diff(ka,ia,ja,3)
112  real(RP), intent(in) :: gsqrt (ka,ia,ja,7)
113  real(RP), intent(in) :: mapf (ia,ja,2)
114  real(RP), intent(in) :: cdz(ka)
115  real(RP), intent(in) :: rcdz(ka)
116  real(RP), intent(in) :: rcdx(ia)
117  real(RP), intent(in) :: rcdy(ja)
118  real(RP), intent(in) :: dtl
119  logical, intent(in) :: flag_fct_tracer
120  logical, intent(in) :: flag_fct_along_stream
121 
122 
123  ! For tracer advection
124  real(RP) :: qflx_hi (ka,ia,ja,3) ! rho * vel(x,y,z) * phi @ (u,v,w)-face high order
125  real(RP) :: qflx_lo (ka,ia,ja,3) ! rho * vel(x,y,z) * phi, monotone flux
126  real(RP) :: qflx_anti(ka,ia,ja,3) ! anti-diffusive flux
127 
128  integer :: iis, iie
129  integer :: jjs, jje
130  integer :: i, j, k
131  !---------------------------------------------------------------------------
132 
133 #ifdef DEBUG
134  qflx_hi(:,:,:,:) = undef
135  qflx_lo(:,:,:,:) = undef
136 #endif
137 
138  do jjs = js, je, jblock
139  jje = jjs+jblock-1
140  do iis = is, ie, iblock
141  iie = iis+iblock-1
142 
143  ! at (x, y, w)
144  call atmos_dyn_fvm_fluxz_xyz_tracer( qflx_hi(:,:,:,zdir), & ! (out)
145  mflx_hi(:,:,:,zdir), qtrc, gsqrt(:,:,:,i_xyw), & ! (in)
146  num_diff(:,:,:,zdir), & ! (in)
147  cdz, & ! (in)
148  iis, iie, jjs, jje ) ! (in)
149 
150  ! at (u, y, z)
151  call atmos_dyn_fvm_fluxx_xyz_tracer( qflx_hi(:,:,:,xdir), & ! (out)
152  mflx_hi(:,:,:,xdir), qtrc, gsqrt(:,:,:,i_uyz), & ! (in)
153  num_diff(:,:,:,xdir), & ! (in)
154  cdz, & ! (in)
155  iis, iie, jjs, jje ) ! (in)
156 
157  ! at (x, v, z)
158  call atmos_dyn_fvm_fluxy_xyz_tracer( qflx_hi(:,:,:,ydir), & ! (out)
159  mflx_hi(:,:,:,ydir), qtrc, gsqrt(:,:,:,i_xvz), & ! (in)
160  num_diff(:,:,:,ydir), & ! (in)
161  cdz, & ! (in)
162  iis, iie, jjs, jje ) ! (in)
163 
164  if ( flag_fct_tracer ) then
165 
166  call atmos_dyn_fvm_fluxz_xyz_ud1( qflx_lo(:,:,:,zdir), & ! (out)
167  mflx_hi(:,:,:,zdir), qtrc0, gsqrt(:,:,:,i_xyw), & ! (in)
168  num_diff(:,:,:,zdir), & ! (in)
169  cdz, & ! (in)
170  iis-1, iie+1, jjs-1, jje+1 ) ! (in)
171 
172  call atmos_dyn_fvm_fluxx_xyz_ud1( qflx_lo(:,:,:,xdir), & ! (out)
173  mflx_hi(:,:,:,xdir), qtrc0, gsqrt(:,:,:,i_uyz), & ! (in)
174  num_diff(:,:,:,xdir), & ! (in)
175  cdz, & ! (in)
176  iis-1, iie+1, jjs-1, jje+1 ) ! (in)
177 
178  call atmos_dyn_fvm_fluxy_xyz_ud1( qflx_lo(:,:,:,ydir), & ! (out)
179  mflx_hi(:,:,:,ydir), qtrc0, gsqrt(:,:,:,i_xvz), & ! (in)
180  num_diff(:,:,:,ydir), & ! (in)
181  cdz, & ! (in)
182  iis-1, iie+1, jjs-1, jje+1 ) ! (in)
183  end if
184 
185  enddo
186  enddo
187 
188  if ( flag_fct_tracer ) then
189 
190  call atmos_dyn_fct( qflx_anti, & ! (out)
191  qtrc0, dens0, dens, & ! (in)
192  qflx_hi, qflx_lo, & ! (in)
193  mflx_hi, & ! (in)
194  rcdz, rcdx, rcdy, & ! (in)
195  gsqrt(:,:,:,i_xyz), & ! (in)
196  mapf, dtl, & ! (in)
197  flag_fct_along_stream ) ! (in)
198 
199  do jjs = js, je, jblock
200  jje = jjs+jblock-1
201  do iis = is, ie, iblock
202  iie = iis+iblock-1
203 
204  !$omp parallel do private(i,j,k) OMP_SCHEDULE_ collapse(2)
205  do j = jjs, jje
206  do i = iis, iie
207  do k = ks, ke
208  qtrco(k,i,j) = ( qtrc0(k,i,j) * dens0(k,i,j) &
209  + dtl * ( - ( ( qflx_hi(k ,i ,j ,zdir) - qflx_anti(k ,i ,j ,zdir) &
210  - qflx_hi(k-1,i ,j ,zdir) + qflx_anti(k-1,i ,j ,zdir) ) * rcdz(k) &
211  + ( qflx_hi(k ,i ,j ,xdir) - qflx_anti(k ,i ,j ,xdir) &
212  - qflx_hi(k ,i-1,j ,xdir) + qflx_anti(k ,i-1,j ,xdir) ) * rcdx(i) &
213  + ( qflx_hi(k ,i ,j ,ydir) - qflx_anti(k ,i ,j ,ydir) &
214  - qflx_hi(k ,i ,j-1,ydir) + qflx_anti(k ,i ,j-1,ydir) ) * rcdy(j) &
215  ) * mapf(i,j,1) * mapf(i,j,2) / gsqrt(k,i,j,i_xyz) &
216  + rhoq_t(k,i,j) ) ) / dens(k,i,j)
217  enddo
218  enddo
219  enddo
220 
221  enddo
222  enddo
223 
224  else ! skip FCT
225 
226  do jjs = js, je, jblock
227  jje = jjs+jblock-1
228  do iis = is, ie, iblock
229  iie = iis+iblock-1
230 
231  !$omp parallel do default(none) private(i,j,k) OMP_SCHEDULE_ collapse(2) &
232  !$omp shared(JJS,JJE,IIS,IIE,KS,KE,QTRCo,QTRC0,DENS0,dtl,qflx_hi,RCDZ,RCDX,RCDY,MAPF) &
233  !$omp shared(GSQRT,RHOQ_t,DENS,I_XYZ)
234  do j = jjs, jje
235  do i = iis, iie
236  do k = ks, ke
237  qtrco(k,i,j) = ( qtrc0(k,i,j) * dens0(k,i,j) &
238  + dtl * ( - ( ( qflx_hi(k,i,j,zdir) - qflx_hi(k-1,i ,j ,zdir) ) * rcdz(k) &
239  + ( qflx_hi(k,i,j,xdir) - qflx_hi(k ,i-1,j ,xdir) ) * rcdx(i) &
240  + ( qflx_hi(k,i,j,ydir) - qflx_hi(k ,i ,j-1,ydir) ) * rcdy(j) &
241  ) * mapf(i,j,1) * mapf(i,j,2) / gsqrt(k,i,j,i_xyz) &
242  + rhoq_t(k,i,j) ) ) / dens(k,i,j)
243  enddo
244  enddo
245  enddo
246 
247  enddo
248  enddo
249 
250  end if
251 
252  return
253  end subroutine atmos_dyn_tstep_tracer_fvm_heve
254 
integer, public is
start point of inner domain: x, local
module DEBUG
Definition: scale_debug.F90:13
integer, public i_xvz
integer, public je
end point of inner domain: y, local
subroutine, public atmos_dyn_fvm_fluxy_xyz_ud1(flux, mflx, val, GSQRT, num_diff, CDZ, IIS, IIE, JJS, JJE)
calculation Y-flux at XYZ
subroutine, public prc_mpistop
Abort MPI.
subroutine, public atmos_dyn_tstep_tracer_fvm_heve(QTRCo, QTRC, QTRC0, RHOQ_t, DENS0, DENS, mflx_hi, num_diff, GSQRT, MAPF, CDZ, RCDZ, RCDX, RCDY, dtl, FLAG_FCT_TRACER, FLAG_FCT_ALONG_STREAM)
subroutine, public atmos_dyn_fvm_fluxz_xyz_ud1(flux, mflx, val, GSQRT, num_diff, CDZ, IIS, IIE, JJS, JJE)
calculation z-flux at XYZ
integer, public iblock
block size for cache blocking: x
integer, parameter, public zdir
module STDIO
Definition: scale_stdio.F90:12
integer, parameter, public ydir
integer, public ke
end point of inner domain: z, local
integer, parameter, public xdir
procedure(flux_phi), pointer, public atmos_dyn_fvm_fluxy_xyz_tracer
integer, public i_xy
subroutine, public check(current_line, v)
Undefined value checker.
Definition: scale_debug.F90:58
real(rp), public const_undef
Definition: scale_const.F90:43
module grid index
module TRACER
module Index
Definition: scale_index.F90:14
integer, public ia
of whole cells: x, local, with HALO
module GRIDTRANS
procedure(flux_phi), pointer, public atmos_dyn_fvm_fluxx_xyz_tracer
integer, public ka
of whole cells: z, local, with HALO
integer, public i_uy
integer, public jblock
block size for cache blocking: y
integer, public i_xyw
procedure(flux_phi), pointer, public atmos_dyn_fvm_fluxz_xyz_tracer
integer, public js
start point of inner domain: y, local
integer, parameter, public const_undef2
undefined value (INT2)
Definition: scale_const.F90:40
module Atmosphere / Dynamics common
module PROCESS
module CONSTANT
Definition: scale_const.F90:14
subroutine, public atmos_dyn_tstep_tracer_fvm_heve_setup(type)
Setup.
integer, public ks
start point of inner domain: z, local
integer, public i_xv
module profiler
Definition: scale_prof.F90:10
integer, public ie
end point of inner domain: x, local
module scale_atmos_dyn_fvm_flux
integer, public i_uyz
module PRECISION
subroutine, public atmos_dyn_fct(qflx_anti, phi_in, DENS0, DENS, qflx_hi, qflx_lo, mflx_hi, rdz, rdx, rdy, GSQRT, MAPF, dt, flag_vect)
Flux Correction Transport Limiter.
integer, public i_xyz
subroutine, public atmos_dyn_fvm_fluxx_xyz_ud1(flux, mflx, val, GSQRT, num_diff, CDZ, IIS, IIE, JJS, JJE)
calculation X-flux at XYZ
module scale_atmos_dyn_fvm_flux_ud1
integer, public ja
of whole cells: y, local, with HALO