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

Contents of /MITgcm/pkg/generic_advdiff/gad_calc_rhs.F

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


Revision 1.2 - (show annotations) (download)
Thu Jul 12 00:26:30 2001 UTC (22 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre7, checkpoint40pre6, checkpoint40pre8, checkpoint40pre2, checkpoint40pre4, checkpoint40pre5
Changes since 1.1: +38 -12 lines
move the "surface" correction term here (fix problem with mask)
 and add a 3rd order advection scheme option

1 C $Header: /u/gcmpack/models/MITgcmUV/pkg/generic_advdiff/gad_calc_rhs.F,v 1.1 2001/05/30 19:34:48 adcroft Exp $
2 C $Name: $
3
4 #include "GAD_OPTIONS.h"
5
6 SUBROUTINE GAD_CALC_RHS(
7 I bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
8 I xA,yA,uTrans,vTrans,rTrans,maskUp,
9 I diffKh, diffK4, KappaRT, Tracer,
10 I tracerIdentity,
11 U fVerT, gTracer,
12 I myThid )
13 C /==========================================================\
14 C | SUBROUTINE GAD_CALC_RHS |
15 C |==========================================================|
16 C \==========================================================/
17 IMPLICIT NONE
18
19 C == GLobal variables ==
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #include "GRID.h"
24 #include "DYNVARS.h"
25 #include "GAD.h"
26
27 C == Routine arguments ==
28 INTEGER k,kUp,kDown,kM1
29 INTEGER bi,bj,iMin,iMax,jMin,jMax
30 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
31 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
32 _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
33 _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
34 _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
35 _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
36 _RL diffKh, diffK4
37 _RL KappaRT(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
38 _RL Tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
39 INTEGER tracerIdentity
40 _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
41 _RL gTracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
42 INTEGER myThid
43
44 C == Local variables ==
45 C I, J, K - Loop counters
46 INTEGER i,j
47 LOGICAL TOP_LAYER
48 _RL afFacT, dfFacT
49 _RL df4 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
50 _RL fZon (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51 _RL fMer (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
52 _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
53 _RL df (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
54 _RL localT(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
55
56 #ifdef ALLOW_AUTODIFF_TAMC
57 C-- only the kUp part of fverT is set in this subroutine
58 C-- the kDown is still required
59 fVerT(1,1,kDown) = fVerT(1,1,kDown)
60 #endif
61 DO j=1-OLy,sNy+OLy
62 DO i=1-OLx,sNx+OLx
63 fZon(i,j) = 0.0
64 fMer(i,j) = 0.0
65 fVerT(i,j,kUp) = 0.0
66 ENDDO
67 ENDDO
68
69 afFacT = 1. _d 0
70 dfFacT = 1. _d 0
71 TOP_LAYER = K .EQ. 1
72
73 C-- Make local copy of tracer array
74 DO j=1-OLy,sNy+OLy
75 DO i=1-OLx,sNx+OLx
76 localT(i,j)=tracer(i,j,k,bi,bj)
77 ENDDO
78 ENDDO
79
80
81 C-- Pre-calculate del^2 T if bi-harmonic coefficient is non-zero
82 IF (diffK4 .NE. 0.) THEN
83 CALL GAD_GRAD_X(bi,bj,k,xA,localT,fZon,myThid)
84 CALL GAD_GRAD_Y(bi,bj,k,yA,localT,fMer,myThid)
85 CALL GAD_DEL2(bi,bj,k,fZon,fMer,df4,myThid)
86 ENDIF
87
88 C-- Initialize net flux in X direction
89 DO j=1-Oly,sNy+Oly
90 DO i=1-Olx,sNx+Olx
91 fZon(i,j) = 0.
92 ENDDO
93 ENDDO
94
95 C- Advective flux in X
96 IF (gad_advection_scheme.EQ.ENUM_CENTERED_2ND) THEN
97 CALL GAD_C2_ADV_X(bi,bj,k,uTrans,localT,af,myThid)
98 ELSEIF (gad_advection_scheme.EQ.ENUM_FLUX_LIMIT) THEN
99 CALL GAD_FLUXLIMIT_ADV_X(
100 & bi,bj,k,deltaTtracer,uTrans,uVel,localT,af,myThid)
101 ELSEIF (gad_advection_scheme.EQ.ENUM_UPWIND_3RD ) THEN
102 CALL GAD_U3_ADV_X(bi,bj,k,uTrans,localT,af,myThid)
103 ELSEIF (gad_advection_scheme.EQ.ENUM_CENTERED_4TH) THEN
104 CALL GAD_C4_ADV_X(bi,bj,k,uTrans,localT,af,myThid)
105 ELSE
106 STOP 'GAD_CALC_RHS: Bad gad_advection_scheme (X)'
107 ENDIF
108 DO j=jMin,jMax
109 DO i=iMin,iMax
110 fZon(i,j) = fZon(i,j) + af(i,j)
111 ENDDO
112 ENDDO
113
114 C- Diffusive flux in X
115 IF (diffKh.NE.0.) THEN
116 CALL GAD_DIFF_X(bi,bj,k,xA,diffKh,localT,df,myThid)
117 ELSE
118 DO j=jMin,jMax
119 DO i=iMin,iMax
120 df(i,j) = 0.
121 ENDDO
122 ENDDO
123 ENDIF
124
125 #ifdef ALLOW_GMREDI
126 C- GM/Redi flux in X
127 IF (useGMRedi) THEN
128 C *note* should update GMREDI_XTRANSPORT to use localT and set df *aja*
129 CALL GMREDI_XTRANSPORT(
130 I iMin,iMax,jMin,jMax,bi,bj,K,
131 I xA,Tracer,
132 U df,
133 I myThid)
134 ENDIF
135 #endif
136 DO j=jMin,jMax
137 DO i=iMin,iMax
138 fZon(i,j) = fZon(i,j) + df(i,j)
139 ENDDO
140 ENDDO
141
142 C- Bi-harmonic duffusive flux in X
143 IF (diffK4 .NE. 0.) THEN
144 CALL GAD_BIHARM_X(bi,bj,k,xA,df4,diffK4,df,myThid)
145 DO j=jMin,jMax
146 DO i=iMin,iMax
147 fZon(i,j) = fZon(i,j) + df(i,j)
148 ENDDO
149 ENDDO
150 ENDIF
151
152 C-- Initialize net flux in Y direction
153 DO j=1-Oly,sNy+Oly
154 DO i=1-Olx,sNx+Olx
155 fMer(i,j) = 0.
156 ENDDO
157 ENDDO
158
159 C- Advective flux in Y
160 IF (gad_advection_scheme.EQ.ENUM_CENTERED_2ND) THEN
161 CALL GAD_C2_ADV_Y(bi,bj,k,vTrans,localT,af,myThid)
162 ELSEIF (gad_advection_scheme.EQ.ENUM_FLUX_LIMIT) THEN
163 CALL GAD_FLUXLIMIT_ADV_Y(
164 & bi,bj,k,deltaTtracer,vTrans,vVel,localT,af,myThid)
165 ELSEIF (gad_advection_scheme.EQ.ENUM_UPWIND_3RD ) THEN
166 CALL GAD_U3_ADV_Y(bi,bj,k,vTrans,localT,af,myThid)
167 ELSEIF (gad_advection_scheme.EQ.ENUM_CENTERED_4TH) THEN
168 CALL GAD_C4_ADV_Y(bi,bj,k,vTrans,localT,af,myThid)
169 ELSE
170 STOP 'GAD_CALC_RHS: Bad gad_advection_scheme (Y)'
171 ENDIF
172 DO j=1-Oly,sNy+Oly
173 DO i=1-Olx,sNx+Olx
174 fMer(i,j) = fMer(i,j) + af(i,j)
175 ENDDO
176 ENDDO
177
178 C- Diffusive flux in Y
179 IF (diffKh.NE.0.) THEN
180 CALL GAD_DIFF_Y(bi,bj,k,yA,diffKh,localT,df,myThid)
181 ELSE
182 DO j=1-Oly,sNy+Oly
183 DO i=1-Olx,sNx+Olx
184 df(i,j) = 0.
185 ENDDO
186 ENDDO
187 ENDIF
188
189 #ifdef ALLOW_GMREDI
190 C- GM/Redi flux in Y
191 IF (useGMRedi) THEN
192 CALL GMREDI_YTRANSPORT(
193 C *note* should update GMREDI_YTRANSPORT to use localT and set df *aja*
194 I iMin,iMax,jMin,jMax,bi,bj,K,
195 I yA,Tracer,
196 U df,
197 I myThid)
198 ENDIF
199 #endif
200 DO j=1-Oly,sNy+Oly
201 DO i=1-Olx,sNx+Olx
202 fMer(i,j) = fMer(i,j) + df(i,j)
203 ENDDO
204 ENDDO
205
206 C- Bi-harmonic flux in Y
207 IF (diffK4 .NE. 0.) THEN
208 CALL GAD_BIHARM_Y(bi,bj,k,yA,df4,diffK4,df,myThid)
209 DO j=1-Oly,sNy+Oly
210 DO i=1-Olx,sNx+Olx
211 fMer(i,j) = fMer(i,j) + df(i,j)
212 ENDDO
213 ENDDO
214 ENDIF
215
216 C-- Initialize net flux in R
217 DO j=jMin,jMax
218 DO i=iMin,iMax
219 fVerT(i,j,kUp) = 0.
220 ENDDO
221 ENDDO
222
223 C- Advective flux in R
224 C Note: wVel needs to be masked
225 IF (K.GE.2) THEN
226 C- Compute vertical advective flux in the interior:
227 IF (gad_advection_scheme.EQ.ENUM_CENTERED_2ND) THEN
228 CALL GAD_C2_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)
229 ELSEIF (gad_advection_scheme.EQ.ENUM_FLUX_LIMIT) THEN
230 CALL GAD_FLUXLIMIT_ADV_R(
231 & bi,bj,k,deltaTtracer,rTrans,wVel,tracer,af,myThid)
232 ELSEIF (gad_advection_scheme.EQ.ENUM_UPWIND_3RD ) THEN
233 CALL GAD_U3_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)
234 ELSEIF (gad_advection_scheme.EQ.ENUM_CENTERED_4TH) THEN
235 CALL GAD_C4_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)
236 c CALL GAD_C2_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)
237 ELSE
238 STOP 'GAD_CALC_RHS: Bad gad_advection_scheme (R)'
239 ENDIF
240 C- Surface "correction" term at k>1 :
241 DO j=1-Oly,sNy+Oly
242 DO i=1-Olx,sNx+Olx
243 af(i,j) = af(i,j)
244 & + (maskC(i,j,k,bi,bj)-maskC(i,j,k-1,bi,bj))*
245 & rTrans(i,j)*Tracer(i,j,k,bi,bj)
246 ENDDO
247 ENDDO
248 ELSE
249 C- Surface "correction" term at k=1 :
250 DO j=1-Oly,sNy+Oly
251 DO i=1-Olx,sNx+Olx
252 af(i,j) = rTrans(i,j)*Tracer(i,j,k,bi,bj)
253 ENDDO
254 ENDDO
255 ENDIF
256 C- add the advective flux to fVerT
257 DO j=jMin,jMax
258 DO i=iMin,iMax
259 fVerT(i,j,kUp) = fVerT(i,j,kUp) + afFacT*af(i,j)
260 ENDDO
261 ENDDO
262
263 C- Diffusive flux in R
264 C Note: For K=1 then KM1=1 and this gives a dT/dr = 0 upper
265 C boundary condition.
266 IF (implicitDiffusion) THEN
267 DO j=jMin,jMax
268 DO i=iMin,iMax
269 df(i,j) = 0.
270 ENDDO
271 ENDDO
272 ELSE
273 CALL GAD_DIFF_R(bi,bj,k,KappaRT,tracer,df,myThid)
274 ENDIF
275 c DO j=jMin,jMax
276 c DO i=iMin,iMax
277 c fVerT(i,j,kUp) = fVerT(i,j,kUp) + dfFacT*df(i,j)*maskUp(i,j)
278 c ENDDO
279 c ENDDO
280
281 #ifdef ALLOW_GMREDI
282 C- GM/Redi flux in R
283 IF (useGMRedi) THEN
284 C *note* should update GMREDI_RTRANSPORT to set df *aja*
285 CALL GMREDI_RTRANSPORT(
286 I iMin,iMax,jMin,jMax,bi,bj,K,
287 I maskUp,Tracer,
288 U df,
289 I myThid)
290 c DO j=jMin,jMax
291 c DO i=iMin,iMax
292 c fVerT(i,j,kUp) = fVerT(i,j,kUp) + dfFacT*df(i,j)*maskUp(i,j)
293 c ENDDO
294 c ENDDO
295 ENDIF
296 #endif
297
298 DO j=jMin,jMax
299 DO i=iMin,iMax
300 fVerT(i,j,kUp) = fVerT(i,j,kUp) + dfFacT*df(i,j)*maskUp(i,j)
301 ENDDO
302 ENDDO
303
304 #ifdef ALLOW_KPP
305 C- Add non local KPP transport term (ghat) to diffusive T flux.
306 IF (useKPP) THEN
307 DO j=jMin,jMax
308 DO i=iMin,iMax
309 df(i,j) = 0.
310 ENDDO
311 ENDDO
312 IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
313 C *note* should update KPP_TRANSPORT_T to set df *aja*
314 CALL KPP_TRANSPORT_T(
315 I iMin,iMax,jMin,jMax,bi,bj,k,km1,
316 I KappaRT,
317 U df )
318 ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
319 CALL KPP_TRANSPORT_S(
320 I iMin,iMax,jMin,jMax,bi,bj,k,km1,
321 I KappaRT,
322 U df )
323 ELSE
324 STOP 'GAD_CALC_RHS: Ooops'
325 ENDIF
326 DO j=jMin,jMax
327 DO i=iMin,iMax
328 fVerT(i,j,kUp) = fVerT(i,j,kUp) + dfFacT*df(i,j)*maskUp(i,j)
329 ENDDO
330 ENDDO
331 ENDIF
332 #endif
333
334 C-- Divergence of fluxes
335 DO j=jMin,jMax
336 DO i=iMin,iMax
337 gTracer(i,j,k,bi,bj)=
338 & -_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
339 & *recip_rA(i,j,bi,bj)
340 & *(
341 & +( fZon(i+1,j)-fZon(i,j) )
342 & +( fMer(i,j+1)-fMer(i,j) )
343 & +( fVerT(i,j,kUp)-fVerT(i,j,kDown) )*rkFac
344 & )
345 ENDDO
346 ENDDO
347
348 RETURN
349 END

  ViewVC Help
Powered by ViewVC 1.1.22