/[MITgcm]/MITgcm/pkg/generic_advdiff/gad_dst3fl_impl_r.F
ViewVC logotype

Annotation of /MITgcm/pkg/generic_advdiff/gad_dst3fl_impl_r.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.5 - (hide annotations) (download)
Wed Oct 5 18:43:36 2016 UTC (7 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, HEAD
Changes since 1.4: +11 -2 lines
- add deep atmosphere and anelastic scaling factor in implicit vertical
  advection routines (gad_*_impl_r.F).

1 jmc 1.5 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_dst3fl_impl_r.F,v 1.4 2011/12/01 14:14:44 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "GAD_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: GAD_DST3FL_IMPL_R
8     C !INTERFACE:
9     SUBROUTINE GAD_DST3FL_IMPL_R(
10     I bi,bj,k, iMin,iMax,jMin,jMax,
11 jmc 1.4 I deltaTarg, rTrans, recip_hFac, tFld,
12 jmc 1.1 O a5d, b5d, c5d, d5d, e5d,
13     I myThid )
14    
15     C !DESCRIPTION:
16    
17     C Compute matrix element to solve vertical advection implicitly
18     C using 3rd order Direct Space and Time (DST) advection scheme
19     C with Flux-Limiter.
20     C Method:
21     C contribution of vertical transport at interface k is added
22     C to matrix lines k and k-1
23    
24     C !USES:
25     IMPLICIT NONE
26    
27     C == Global variables ===
28     #include "SIZE.h"
29     #include "GRID.h"
30     #include "EEPARAMS.h"
31     #include "PARAMS.h"
32     #include "GAD.h"
33    
34     C !INPUT/OUTPUT PARAMETERS:
35     C == Routine Arguments ==
36 jmc 1.4 C bi,bj :: tile indices
37     C k :: vertical level
38     C iMin,iMax :: computation domain
39     C jMin,jMax :: computation domain
40     C deltaTarg :: time step
41     C rTrans :: vertical volume transport
42     C recip_hFac :: inverse of cell open-depth factor
43     C tFld :: tracer field
44     C a5d :: 2nd lower diag of pentadiagonal matrix
45     C b5d :: 1rst lower diag of pentadiagonal matrix
46     C c5d :: main diag of pentadiagonal matrix
47     C d5d :: 1rst upper diag of pentadiagonal matrix
48     C e5d :: 2nd upper diag of pentadiagonal matrix
49     C myThid :: thread number
50 jmc 1.1 INTEGER bi,bj,k
51     INTEGER iMin,iMax,jMin,jMax
52 jmc 1.4 _RL deltaTarg(Nr)
53     _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
54     _RS recip_hFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
55     _RL tFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
56     _RL a5d (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
57     _RL b5d (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
58     _RL c5d (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
59     _RL d5d (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
60     _RL e5d (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
61 jmc 1.1 INTEGER myThid
62    
63     C == Local Variables ==
64 jmc 1.4 C i,j :: loop indices
65     C kp1 :: =min( k+1 , Nr )
66     C km2 :: =max( k-2 , 1 )
67     C wCFL :: Courant-Friedrich-Levy number
68     C lowFac :: low order term factor
69     C highFac :: high order term factor
70     C rCenter :: centered contribution
71     C rUpwind :: upwind contribution
72     C rC4km, rC4kp :: high order contributions
73 jmc 1.1 INTEGER i,j,kp1,km2
74     _RL wCFL, rCenter, rUpwind
75     _RL lowFac (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76     _RL highFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77     _RL rC4km, rC4kp
78     _RL mskM, mskP, maskM2, maskP1
79     _RL Rj, Rjh, cL1, cH3, cM2, th1, th2
80     _RL deltaTcfl
81     CEOP
82    
83     C-- process interior interface only:
84     IF ( k.GT.1 .AND. k.LE.Nr ) THEN
85    
86     km2=MAX(1,k-2)
87     kp1=MIN(Nr,k+1)
88     maskP1 = 1. _d 0
89     maskM2 = 1. _d 0
90     IF ( k.LE.2 ) maskM2 = 0. _d 0
91     IF ( k.GE.Nr) maskP1 = 0. _d 0
92    
93     C-- Compute the low-order term & high-order term fractions :
94     deltaTcfl = deltaTarg(k)
95     C DST-3 Flux-Limiter Advection Scheme:
96     C- Limiter: Psi=max(0,min(1,cL1+theta*cH1,theta*(1-cfl)/cfl) )
97     C with theta=Rjh/Rj ;
98     C is linearize arround the current value of theta(tFld) & cfl:
99     C lowFac & highFac are set such as Psi*Rj = lowFac*Rj + highFac*Rjh
100     DO j=jMin,jMax
101     DO i=iMin,iMax
102     wCFL = deltaTcfl*ABS(rTrans(i,j))
103     & *recip_rA(i,j,bi,bj)*recip_drC(k)
104 jmc 1.5 & *recip_deepFac2F(k)*recip_rhoFacF(k)
105 jmc 1.1 cL1 = (2. _d 0 -wCFL)*(1. _d 0 -wCFL)*oneSixth
106     cH3 = (1. _d 0 -wCFL*wCFL)*oneSixth
107     c cM2 = (1. _d 0 - wCFL)/( wCFL +1. _d -20)
108     cM2 = (1. _d 0 + wCFL)/( wCFL +1. _d -20)
109    
110     Rj =(tFld(i,j,k) -tFld(i,j,k-1))
111     IF ( rTrans(i,j).GT.0. _d 0 ) THEN
112     Rjh = (tFld(i,j,k-1)-tFld(i,j,km2))*maskC(i,j,km2,bi,bj)
113     ELSE
114     Rjh = (tFld(i,j,kp1)-tFld(i,j,k) )*maskC(i,j,kp1,bi,bj)
115     ENDIF
116     IF ( Rj*Rjh.LE.0. _d 0 ) THEN
117     C- 1rst case: theta < 0 (Rj & Rjh opposite sign) => Psi = 0
118     lowFac(i,j) = 0. _d 0
119     highFac(i,j)= 0. _d 0
120     ELSE
121     Rj = ABS(Rj)
122     Rjh = ABS(Rjh)
123     th1 = cL1*Rj+cH3*Rjh
124     th2 = cM2*Rjh
125     IF ( th1.LE.th2 .AND. th1.LE.Rj ) THEN
126     C- 2nd case: cL1+theta*cH3 = min of the three = Psi
127     lowFac(i,j) = cL1
128     highFac(i,j)= cH3
129     ELSEIF ( th2.LT.th1 .AND. th2.LE.Rj ) THEN
130     C- 3rd case: theta*cM2 = min of the three = Psi
131     lowFac(i,j) = 0. _d 0
132     highFac(i,j)= cM2
133     ELSE
134     C- 4th case (Rj < th1 & Rj < th2) : 1 = min of the three = Psi
135     lowFac(i,j) = 1. _d 0
136     highFac(i,j)= 0. _d 0
137     ENDIF
138     ENDIF
139     ENDDO
140     ENDDO
141    
142     C-- Add centered & upwind contributions
143     DO j=jMin,jMax
144     DO i=iMin,iMax
145     rCenter= 0.5 _d 0 *rTrans(i,j)*recip_rA(i,j,bi,bj)*rkSign
146     mskM = maskC(i,j,km2,bi,bj)*maskM2
147     mskP = maskC(i,j,kp1,bi,bj)*maskP1
148     rUpwind= (0.5 _d 0 -lowFac(i,j))*ABS(rCenter)*2. _d 0
149     rC4km = highFac(i,j)*(rCenter+ABS(rCenter))*mskM
150     rC4kp = highFac(i,j)*(rCenter-ABS(rCenter))*mskP
151    
152     a5d(i,j,k) = a5d(i,j,k)
153     & + rC4km
154     & *deltaTarg(k)
155 jmc 1.4 & *recip_hFac(i,j,k)*recip_drF(k)
156 jmc 1.5 & *recip_deepFac2C(k)*recip_rhoFacC(k)
157 jmc 1.1 b5d(i,j,k) = b5d(i,j,k)
158     & - ( (rCenter+rUpwind) + rC4km )
159     & *deltaTarg(k)
160 jmc 1.4 & *recip_hFac(i,j,k)*recip_drF(k)
161 jmc 1.5 & *recip_deepFac2C(k)*recip_rhoFacC(k)
162 jmc 1.1 c5d(i,j,k) = c5d(i,j,k)
163     & - ( (rCenter-rUpwind) + rC4kp )
164     & *deltaTarg(k)
165 jmc 1.4 & *recip_hFac(i,j,k)*recip_drF(k)
166 jmc 1.5 & *recip_deepFac2C(k)*recip_rhoFacC(k)
167 jmc 1.1 d5d(i,j,k) = d5d(i,j,k)
168     & + rC4kp
169     & *deltaTarg(k)
170 jmc 1.4 & *recip_hFac(i,j,k)*recip_drF(k)
171 jmc 1.5 & *recip_deepFac2C(k)*recip_rhoFacC(k)
172 jmc 1.1 b5d(i,j,k-1) = b5d(i,j,k-1)
173     & - rC4km
174     & *deltaTarg(k-1)
175 jmc 1.4 & *recip_hFac(i,j,k-1)*recip_drF(k-1)
176 jmc 1.5 & *recip_deepFac2C(k-1)*recip_rhoFacC(k-1)
177 jmc 1.1 c5d(i,j,k-1) = c5d(i,j,k-1)
178     & + ( (rCenter+rUpwind) + rC4km )
179     & *deltaTarg(k-1)
180 jmc 1.4 & *recip_hFac(i,j,k-1)*recip_drF(k-1)
181 jmc 1.5 & *recip_deepFac2C(k-1)*recip_rhoFacC(k-1)
182 jmc 1.1 d5d(i,j,k-1) = d5d(i,j,k-1)
183     & + ( (rCenter-rUpwind) + rC4kp )
184     & *deltaTarg(k-1)
185 jmc 1.4 & *recip_hFac(i,j,k-1)*recip_drF(k-1)
186 jmc 1.5 & *recip_deepFac2C(k-1)*recip_rhoFacC(k-1)
187 jmc 1.1 e5d(i,j,k-1) = e5d(i,j,k-1)
188     & - rC4kp
189     & *deltaTarg(k-1)
190 jmc 1.5 & *recip_hFac(i,j,k-1)*recip_drF(k-1)
191     & *recip_deepFac2C(k-1)*recip_rhoFacC(k-1)
192 jmc 1.1 ENDDO
193     ENDDO
194    
195     C-- process interior interface only: end
196     ENDIF
197    
198     RETURN
199     END

  ViewVC Help
Powered by ViewVC 1.1.22