INTERFACE:
subroutine adv_split_w(dt,f,fi,hi,adv,ww, &
splitfac,scheme,tag,az, &
itersmax)
Note (KK): Keep in sync with interface in advection_3d.F90
DESCRIPTION:
Executes an advection step in vertical direction. The 1D advection equation
is accompanied by an fractional step for the 1D continuity equation
Here, and
denote values before and after this operation,
respectively,
denote intermediate values when other
1D advection steps come after this and
denotes intermediate
values when other 1D advection steps came before this.
The interfacial fluxes
are calculated by means of
monotone and non-monotone schemes which are described in detail in
section 7.4.7 on page
.
USES:
use domain, only: imin,imax,jmin,jmax,kmax,ioff,joff
use advection, only: adv_interfacial_reconstruction
use advection, only: NOADV,UPSTREAM
use advection_3d, only: W_TAG
use halo_zones, only: U_TAG,V_TAG
$ use omp_lib
IMPLICIT NONE
INPUT PARAMETERS:
REALTYPE,intent(in) :: dt,splitfac
REALTYPE,dimension(I3DFIELD),intent(in),target :: f
REALTYPE,dimension(I3DFIELD),intent(in) :: ww
integer,intent(in) :: scheme,tag,itersmax
integer,dimension(E2DFIELD),intent(in) :: az
INPUT/OUTPUT PARAMETERS:
REALTYPE,dimension(I3DFIELD),target,intent(inout) :: fi,hi,advLOCAL VARIABLES:
logical :: iterate,use_limiter,allocated_aux
integer :: i,j,k,kshift,it,iters,iters_new,rc
REALTYPE :: itersm1,dti,dtik,hio,advn,fuu,fu,fd,splitfack
REALTYPE,dimension(:),allocatable :: wflux
REALTYPE,dimension(:),allocatable,target :: cfl0
REALTYPE,dimension(:),pointer :: fo,faux,fiaux,hiaux,advaux,cfls
REALTYPE,dimension(:),pointer :: p_fiaux,p_hiaux,p_advaux
REALTYPE,dimension(:),pointer :: p1d
REVISION HISTORY:
Original author(s): Hans Burchard & Karsten Bolding