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