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

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

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


Revision 1.41 - (show annotations) (download)
Sun Jun 18 23:27:44 2006 UTC (17 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58m_post, checkpoint58k_post, checkpoint58l_post
Changes since 1.40: +50 -41 lines
make a local copy of velocity to pass (like u,v,r_Trans) to tracer advection S/R

1 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_advection.F,v 1.40 2006/02/21 17:20:12 heimbach Exp $
2 C $Name: $
3
4 #include "GAD_OPTIONS.h"
5 #undef MULTIDIM_OLD_VERSION
6
7 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
8 CBOP
9 C !ROUTINE: GAD_ADVECTION
10
11 C !INTERFACE: ==========================================================
12 SUBROUTINE GAD_ADVECTION(
13 I implicitAdvection, advectionScheme, vertAdvecScheme,
14 I tracerIdentity,
15 I uVel, vVel, wVel, tracer,
16 O gTracer,
17 I bi,bj, myTime,myIter,myThid)
18
19 C !DESCRIPTION:
20 C Calculates the tendancy of a tracer due to advection.
21 C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}
22 C and can only be used for the non-linear advection schemes such as the
23 C direct-space-time method and flux-limiters.
24 C
25 C The algorithm is as follows:
26 C \begin{itemize}
27 C \item{$\theta^{(n+1/3)} = \theta^{(n)}
28 C - \Delta t \partial_x (u\theta^{(n)}) + \theta^{(n)} \partial_x u$}
29 C \item{$\theta^{(n+2/3)} = \theta^{(n+1/3)}
30 C - \Delta t \partial_y (v\theta^{(n+1/3)}) + \theta^{(n)} \partial_y v$}
31 C \item{$\theta^{(n+3/3)} = \theta^{(n+2/3)}
32 C - \Delta t \partial_r (w\theta^{(n+2/3)}) + \theta^{(n)} \partial_r w$}
33 C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}
34 C \end{itemize}
35 C
36 C The tendancy (output) is over-written by this routine.
37
38 C !USES: ===============================================================
39 IMPLICIT NONE
40 #include "SIZE.h"
41 #include "EEPARAMS.h"
42 #include "PARAMS.h"
43 #include "GRID.h"
44 #include "GAD.h"
45 #ifdef ALLOW_AUTODIFF_TAMC
46 # include "tamc.h"
47 # include "tamc_keys.h"
48 # ifdef ALLOW_PTRACERS
49 # include "PTRACERS_SIZE.h"
50 # endif
51 #endif
52 #ifdef ALLOW_EXCH2
53 #include "W2_EXCH2_TOPOLOGY.h"
54 #include "W2_EXCH2_PARAMS.h"
55 #endif /* ALLOW_EXCH2 */
56
57 C !INPUT PARAMETERS: ===================================================
58 C implicitAdvection :: implicit vertical advection (later on)
59 C advectionScheme :: advection scheme to use (Horizontal plane)
60 C vertAdvecScheme :: advection scheme to use (vertical direction)
61 C tracerIdentity :: tracer identifier (required only for OBCS)
62 C uVel :: velocity, zonal component
63 C vVel :: velocity, meridional component
64 C wVel :: velocity, vertical component
65 C tracer :: tracer field
66 C bi,bj :: tile indices
67 C myTime :: current time
68 C myIter :: iteration number
69 C myThid :: thread number
70 LOGICAL implicitAdvection
71 INTEGER advectionScheme, vertAdvecScheme
72 INTEGER tracerIdentity
73 _RL uVel (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
74 _RL vVel (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
75 _RL wVel (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
76 _RL tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
77 INTEGER bi,bj
78 _RL myTime
79 INTEGER myIter
80 INTEGER myThid
81
82 C !OUTPUT PARAMETERS: ==================================================
83 C gTracer :: tendancy array
84 _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
85
86 C !LOCAL VARIABLES: ====================================================
87 C maskUp :: 2-D array for mask at W points
88 C maskLocW :: 2-D array for mask at West points
89 C maskLocS :: 2-D array for mask at South points
90 C iMin,iMax, :: loop range for called routines
91 C jMin,jMax :: loop range for called routines
92 C [iMin,iMax]Upd :: loop range to update tracer field
93 C [jMin,jMax]Upd :: loop range to update tracer field
94 C i,j,k :: loop indices
95 C kUp :: index into 2 1/2D array, toggles between 1 and 2
96 C kDown :: index into 2 1/2D array, toggles between 2 and 1
97 C kp1 :: =k+1 for k<Nr, =Nr for k=Nr
98 C xA,yA :: areas of X and Y face of tracer cells
99 C uFld,vFld :: 2-D local copy of horizontal velocity, U,V components
100 C wFld :: 2-D local copy of vertical velocity
101 C uTrans,vTrans :: 2-D arrays of volume transports at U,V points
102 C rTrans :: 2-D arrays of volume transports at W points
103 C rTransKp1 :: vertical volume transport at interface k+1
104 C af :: 2-D array for horizontal advective flux
105 C afx :: 2-D array for horizontal advective flux, x direction
106 C afy :: 2-D array for horizontal advective flux, y direction
107 C fVerT :: 2 1/2D arrays for vertical advective flux
108 C localTij :: 2-D array, temporary local copy of tracer fld
109 C localTijk :: 3-D array, temporary local copy of tracer fld
110 C kp1Msk :: flag (0,1) for over-riding mask for W levels
111 C calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
112 C calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
113 C interiorOnly :: only update the interior of myTile, but not the edges
114 C overlapOnly :: only update the edges of myTile, but not the interior
115 C nipass :: number of passes in multi-dimensional method
116 C ipass :: number of the current pass being made
117 C myTile :: variables used to determine which cube face
118 C nCFace :: owns a tile for cube grid runs using
119 C :: multi-dim advection.
120 C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
121 c _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122 _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
123 _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
124 INTEGER iMin,iMax,jMin,jMax
125 INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd
126 INTEGER i,j,k,kUp,kDown
127 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
128 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
129 _RL uFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
130 _RL vFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
131 _RL wFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
132 _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
133 _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
134 _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
135 _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
136 _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
137 _RL afx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
138 _RL afy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
139 _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
140 _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
141 _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
142 _RL kp1Msk
143 LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns
144 LOGICAL interiorOnly, overlapOnly
145 INTEGER nipass,ipass
146 INTEGER nCFace
147 LOGICAL N_edge, S_edge, E_edge, W_edge
148 #ifdef ALLOW_EXCH2
149 INTEGER myTile
150 #endif
151 #ifdef ALLOW_DIAGNOSTICS
152 CHARACTER*8 diagName
153 CHARACTER*4 GAD_DIAG_SUFX, diagSufx
154 EXTERNAL GAD_DIAG_SUFX
155 #endif
156 CEOP
157
158 #ifdef ALLOW_AUTODIFF_TAMC
159 act0 = tracerIdentity - 1
160 max0 = maxpass
161 act1 = bi - myBxLo(myThid)
162 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
163 act2 = bj - myByLo(myThid)
164 max2 = myByHi(myThid) - myByLo(myThid) + 1
165 act3 = myThid - 1
166 max3 = nTx*nTy
167 act4 = ikey_dynamics - 1
168 igadkey = (act0 + 1)
169 & + act1*max0
170 & + act2*max0*max1
171 & + act3*max0*max1*max2
172 & + act4*max0*max1*max2*max3
173 if (tracerIdentity.GT.maxpass) then
174 print *, 'ph-pass gad_advection ', maxpass, tracerIdentity
175 STOP 'maxpass seems smaller than tracerIdentity'
176 endif
177 #endif /* ALLOW_AUTODIFF_TAMC */
178
179 #ifdef ALLOW_DIAGNOSTICS
180 C-- Set diagnostic suffix for the current tracer
181 IF ( useDiagnostics ) THEN
182 diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
183 ENDIF
184 #endif
185
186 C-- Set up work arrays with valid (i.e. not NaN) values
187 C These inital values do not alter the numerical results. They
188 C just ensure that all memory references are to valid floating
189 C point numbers. This prevents spurious hardware signals due to
190 C uninitialised but inert locations.
191 DO j=1-OLy,sNy+OLy
192 DO i=1-OLx,sNx+OLx
193 xA(i,j) = 0. _d 0
194 yA(i,j) = 0. _d 0
195 uTrans(i,j) = 0. _d 0
196 vTrans(i,j) = 0. _d 0
197 rTrans(i,j) = 0. _d 0
198 fVerT(i,j,1) = 0. _d 0
199 fVerT(i,j,2) = 0. _d 0
200 rTransKp1(i,j)= 0. _d 0
201 #ifdef ALLOW_AUTODIFF_TAMC
202 localTij(i,j) = 0. _d 0
203 #endif
204 ENDDO
205 ENDDO
206
207 C-- Set tile-specific parameters for horizontal fluxes
208 IF (useCubedSphereExchange) THEN
209 nipass=3
210 #ifdef ALLOW_AUTODIFF_TAMC
211 IF ( nipass.GT.maxcube ) STOP 'maxcube needs to be = 3'
212 #endif
213 #ifdef ALLOW_EXCH2
214 myTile = W2_myTileList(bi)
215 nCFace = exch2_myFace(myTile)
216 N_edge = exch2_isNedge(myTile).EQ.1
217 S_edge = exch2_isSedge(myTile).EQ.1
218 E_edge = exch2_isEedge(myTile).EQ.1
219 W_edge = exch2_isWedge(myTile).EQ.1
220 #else
221 nCFace = bi
222 N_edge = .TRUE.
223 S_edge = .TRUE.
224 E_edge = .TRUE.
225 W_edge = .TRUE.
226 #endif
227 ELSE
228 nipass=2
229 nCFace = bi
230 N_edge = .FALSE.
231 S_edge = .FALSE.
232 E_edge = .FALSE.
233 W_edge = .FALSE.
234 ENDIF
235
236 iMin = 1-OLx
237 iMax = sNx+OLx
238 jMin = 1-OLy
239 jMax = sNy+OLy
240
241 C-- Start of k loop for horizontal fluxes
242 DO k=1,Nr
243 #ifdef ALLOW_AUTODIFF_TAMC
244 kkey = (igadkey-1)*Nr + k
245 CADJ STORE tracer(:,:,k,bi,bj) =
246 CADJ & comlev1_bibj_k_gad, key=kkey, byte=isbyte
247 #endif /* ALLOW_AUTODIFF_TAMC */
248
249 C-- Get temporary terms used by tendency routines
250 CALL CALC_COMMON_FACTORS (
251 I uVel, vVel,
252 O uFld, vFld, uTrans, vTrans, xA, yA,
253 I k,bi,bj, myThid )
254
255 #ifdef ALLOW_GMREDI
256 C-- Residual transp = Bolus transp + Eulerian transp
257 IF (useGMRedi)
258 & CALL GMREDI_CALC_UVFLOW(
259 U uFld, vFld, uTrans, vTrans,
260 I k, bi, bj, myThid )
261 #endif /* ALLOW_GMREDI */
262
263 C-- Make local copy of tracer array and mask West & South
264 DO j=1-OLy,sNy+OLy
265 DO i=1-OLx,sNx+OLx
266 localTij(i,j)=tracer(i,j,k,bi,bj)
267 maskLocW(i,j)=maskW(i,j,k,bi,bj)
268 maskLocS(i,j)=maskS(i,j,k,bi,bj)
269 ENDDO
270 ENDDO
271
272 #ifndef ALLOW_AUTODIFF_TAMC
273 IF (useCubedSphereExchange) THEN
274 withSigns = .FALSE.
275 CALL FILL_CS_CORNER_UV_RS(
276 & withSigns, maskLocW,maskLocS, bi,bj, myThid )
277 ENDIF
278 #endif
279
280 C-- Multiple passes for different directions on different tiles
281 C-- For cube need one pass for each of red, green and blue axes.
282 DO ipass=1,nipass
283 #ifdef ALLOW_AUTODIFF_TAMC
284 passkey = ipass + (k-1) *maxcube
285 & + (igadkey-1)*maxcube*Nr
286 IF (nipass .GT. maxpass) THEN
287 STOP 'GAD_ADVECTION: nipass > maxcube. check tamc.h'
288 ENDIF
289 #endif /* ALLOW_AUTODIFF_TAMC */
290
291 interiorOnly = .FALSE.
292 overlapOnly = .FALSE.
293 IF (useCubedSphereExchange) THEN
294 #ifdef MULTIDIM_OLD_VERSION
295 C- CubedSphere : pass 3 times, with full update of local tracer field
296 IF (ipass.EQ.1) THEN
297 calc_fluxes_X = nCFace.EQ.1 .OR. nCFace.EQ.2
298 calc_fluxes_Y = nCFace.EQ.4 .OR. nCFace.EQ.5
299 ELSEIF (ipass.EQ.2) THEN
300 calc_fluxes_X = nCFace.EQ.3 .OR. nCFace.EQ.4
301 calc_fluxes_Y = nCFace.EQ.6 .OR. nCFace.EQ.1
302 #else /* MULTIDIM_OLD_VERSION */
303 C- CubedSphere : pass 3 times, with partial update of local tracer field
304 IF (ipass.EQ.1) THEN
305 overlapOnly = MOD(nCFace,3).EQ.0
306 interiorOnly = MOD(nCFace,3).NE.0
307 calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
308 calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
309 ELSEIF (ipass.EQ.2) THEN
310 overlapOnly = MOD(nCFace,3).EQ.2
311 calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
312 calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
313 #endif /* MULTIDIM_OLD_VERSION */
314 ELSE
315 calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
316 calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
317 ENDIF
318 ELSE
319 C- not CubedSphere
320 calc_fluxes_X = MOD(ipass,2).EQ.1
321 calc_fluxes_Y = .NOT.calc_fluxes_X
322 ENDIF
323
324 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
325 C-- X direction
326 C- Advective flux in X
327 DO j=1-Oly,sNy+Oly
328 DO i=1-Olx,sNx+Olx
329 af(i,j) = 0.
330 ENDDO
331 ENDDO
332 C
333 #ifdef ALLOW_AUTODIFF_TAMC
334 # ifndef DISABLE_MULTIDIM_ADVECTION
335 CADJ STORE localTij(:,:) =
336 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
337 CADJ STORE af(:,:) =
338 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
339 # endif
340 #endif /* ALLOW_AUTODIFF_TAMC */
341 C
342 IF (calc_fluxes_X) THEN
343
344 C- Do not compute fluxes if
345 C a) needed in overlap only
346 C and b) the overlap of myTile are not cube-face Edges
347 IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
348
349 #ifndef ALLOW_AUTODIFF_TAMC
350 C- Internal exchange for calculations in X
351 #ifdef MULTIDIM_OLD_VERSION
352 IF ( useCubedSphereExchange ) THEN
353 #else
354 IF ( useCubedSphereExchange .AND.
355 & ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
356 #endif
357 CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
358 ENDIF
359 #endif
360
361 #ifdef ALLOW_AUTODIFF_TAMC
362 # ifndef DISABLE_MULTIDIM_ADVECTION
363 CADJ STORE localTij(:,:) =
364 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
365 # endif
366 #endif /* ALLOW_AUTODIFF_TAMC */
367
368 IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
369 & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
370 CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme,
371 I dTtracerLev(k),uTrans,uFld,localTij,
372 O af, myThid )
373 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
374 CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, dTtracerLev(k),
375 I uTrans, uFld, maskLocW, localTij,
376 O af, myThid )
377 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
378 CALL GAD_DST3_ADV_X( bi,bj,k, dTtracerLev(k),
379 I uTrans, uFld, maskLocW, localTij,
380 O af, myThid )
381 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
382 CALL GAD_DST3FL_ADV_X( bi,bj,k, dTtracerLev(k),
383 I uTrans, uFld, maskLocW, localTij,
384 O af, myThid )
385 ELSE
386 STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
387 ENDIF
388
389 C- Advective flux in X : done
390 ENDIF
391
392 #ifndef ALLOW_AUTODIFF_TAMC
393 C- Internal exchange for next calculations in Y
394 IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
395 CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
396 ENDIF
397 #endif
398
399 C- Update the local tracer field where needed:
400
401 C update in overlap-Only
402 IF ( overlapOnly ) THEN
403 iMinUpd = 1-Olx+1
404 iMaxUpd = sNx+Olx-1
405 C- notes: these 2 lines below have no real effect (because recip_hFac=0
406 C in corner region) but safer to keep them.
407 IF ( W_edge ) iMinUpd = 1
408 IF ( E_edge ) iMaxUpd = sNx
409
410 IF ( S_edge ) THEN
411 DO j=1-Oly,0
412 DO i=iMinUpd,iMaxUpd
413 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
414 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
415 & *recip_rA(i,j,bi,bj)
416 & *( af(i+1,j)-af(i,j)
417 & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
418 & )
419 ENDDO
420 ENDDO
421 ENDIF
422 IF ( N_edge ) THEN
423 DO j=sNy+1,sNy+Oly
424 DO i=iMinUpd,iMaxUpd
425 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
426 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
427 & *recip_rA(i,j,bi,bj)
428 & *( af(i+1,j)-af(i,j)
429 & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
430 & )
431 ENDDO
432 ENDDO
433 ENDIF
434
435 ELSE
436 C do not only update the overlap
437 jMinUpd = 1-Oly
438 jMaxUpd = sNy+Oly
439 IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
440 IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
441 DO j=jMinUpd,jMaxUpd
442 DO i=1-Olx+1,sNx+Olx-1
443 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
444 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
445 & *recip_rA(i,j,bi,bj)
446 & *( af(i+1,j)-af(i,j)
447 & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
448 & )
449 ENDDO
450 ENDDO
451 C- keep advective flux (for diagnostics)
452 DO j=1-Oly,sNy+Oly
453 DO i=1-Olx,sNx+Olx
454 afx(i,j) = af(i,j)
455 ENDDO
456 ENDDO
457
458 #ifdef ALLOW_OBCS
459 C- Apply open boundary conditions
460 IF ( useOBCS ) THEN
461 IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
462 CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
463 ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
464 CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
465 #ifdef ALLOW_PTRACERS
466 ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
467 CALL OBCS_APPLY_PTRACER( bi, bj, k,
468 & tracerIdentity-GAD_TR1+1, localTij, myThid )
469 #endif /* ALLOW_PTRACERS */
470 ENDIF
471 ENDIF
472 #endif /* ALLOW_OBCS */
473
474 C- end if/else update overlap-Only
475 ENDIF
476
477 C-- End of X direction
478 ENDIF
479
480 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
481 C-- Y direction
482 cph-test
483 C- Advective flux in Y
484 DO j=1-Oly,sNy+Oly
485 DO i=1-Olx,sNx+Olx
486 af(i,j) = 0.
487 ENDDO
488 ENDDO
489 C
490 #ifdef ALLOW_AUTODIFF_TAMC
491 # ifndef DISABLE_MULTIDIM_ADVECTION
492 CADJ STORE localTij(:,:) =
493 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
494 CADJ STORE af(:,:) =
495 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
496 # endif
497 #endif /* ALLOW_AUTODIFF_TAMC */
498 C
499 IF (calc_fluxes_Y) THEN
500
501 C- Do not compute fluxes if
502 C a) needed in overlap only
503 C and b) the overlap of myTile are not cube-face edges
504 IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
505
506 #ifndef ALLOW_AUTODIFF_TAMC
507 C- Internal exchange for calculations in Y
508 #ifdef MULTIDIM_OLD_VERSION
509 IF ( useCubedSphereExchange ) THEN
510 #else
511 IF ( useCubedSphereExchange .AND.
512 & ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
513 #endif
514 CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
515 ENDIF
516 #endif
517
518 C- Advective flux in Y
519 DO j=1-Oly,sNy+Oly
520 DO i=1-Olx,sNx+Olx
521 af(i,j) = 0.
522 ENDDO
523 ENDDO
524
525 #ifdef ALLOW_AUTODIFF_TAMC
526 #ifndef DISABLE_MULTIDIM_ADVECTION
527 CADJ STORE localTij(:,:) =
528 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
529 #endif
530 #endif /* ALLOW_AUTODIFF_TAMC */
531
532 IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
533 & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
534 CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme,
535 I dTtracerLev(k),vTrans,vFld,localTij,
536 O af, myThid )
537 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
538 CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, dTtracerLev(k),
539 I vTrans, vFld, maskLocS, localTij,
540 O af, myThid )
541 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
542 CALL GAD_DST3_ADV_Y( bi,bj,k, dTtracerLev(k),
543 I vTrans, vFld, maskLocS, localTij,
544 O af, myThid )
545 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
546 CALL GAD_DST3FL_ADV_Y( bi,bj,k, dTtracerLev(k),
547 I vTrans, vFld, maskLocS, localTij,
548 O af, myThid )
549 ELSE
550 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
551 ENDIF
552
553 C- Advective flux in Y : done
554 ENDIF
555
556 #ifndef ALLOW_AUTODIFF_TAMC
557 C- Internal exchange for next calculations in X
558 IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
559 CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
560 ENDIF
561 #endif
562
563 C- Update the local tracer field where needed:
564
565 C update in overlap-Only
566 IF ( overlapOnly ) THEN
567 jMinUpd = 1-Oly+1
568 jMaxUpd = sNy+Oly-1
569 C- notes: these 2 lines below have no real effect (because recip_hFac=0
570 C in corner region) but safer to keep them.
571 IF ( S_edge ) jMinUpd = 1
572 IF ( N_edge ) jMaxUpd = sNy
573
574 IF ( W_edge ) THEN
575 DO j=jMinUpd,jMaxUpd
576 DO i=1-Olx,0
577 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
578 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
579 & *recip_rA(i,j,bi,bj)
580 & *( af(i,j+1)-af(i,j)
581 & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
582 & )
583 ENDDO
584 ENDDO
585 ENDIF
586 IF ( E_edge ) THEN
587 DO j=jMinUpd,jMaxUpd
588 DO i=sNx+1,sNx+Olx
589 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
590 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
591 & *recip_rA(i,j,bi,bj)
592 & *( af(i,j+1)-af(i,j)
593 & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
594 & )
595 ENDDO
596 ENDDO
597 ENDIF
598
599 ELSE
600 C do not only update the overlap
601 iMinUpd = 1-Olx
602 iMaxUpd = sNx+Olx
603 IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
604 IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
605 DO j=1-Oly+1,sNy+Oly-1
606 DO i=iMinUpd,iMaxUpd
607 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
608 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
609 & *recip_rA(i,j,bi,bj)
610 & *( af(i,j+1)-af(i,j)
611 & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
612 & )
613 ENDDO
614 ENDDO
615 C- keep advective flux (for diagnostics)
616 DO j=1-Oly,sNy+Oly
617 DO i=1-Olx,sNx+Olx
618 afy(i,j) = af(i,j)
619 ENDDO
620 ENDDO
621
622 #ifdef ALLOW_OBCS
623 C- Apply open boundary conditions
624 IF (useOBCS) THEN
625 IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
626 CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
627 ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
628 CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
629 #ifdef ALLOW_PTRACERS
630 ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
631 CALL OBCS_APPLY_PTRACER( bi, bj, k,
632 & tracerIdentity-GAD_TR1+1, localTij, myThid )
633 #endif /* ALLOW_PTRACERS */
634 ENDIF
635 ENDIF
636 #endif /* ALLOW_OBCS */
637
638 C end if/else update overlap-Only
639 ENDIF
640
641 C-- End of Y direction
642 ENDIF
643
644 C-- End of ipass loop
645 ENDDO
646
647 IF ( implicitAdvection ) THEN
648 C- explicit advection is done ; store tendency in gTracer:
649 DO j=1-Oly,sNy+Oly
650 DO i=1-Olx,sNx+Olx
651 gTracer(i,j,k,bi,bj)=
652 & (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
653 ENDDO
654 ENDDO
655 ELSE
656 C- horizontal advection done; store intermediate result in 3D array:
657 DO j=1-Oly,sNy+Oly
658 DO i=1-Olx,sNx+Olx
659 localTijk(i,j,k)=localTij(i,j)
660 ENDDO
661 ENDDO
662 ENDIF
663
664 #ifdef ALLOW_DIAGNOSTICS
665 IF ( useDiagnostics ) THEN
666 diagName = 'ADVx'//diagSufx
667 CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid)
668 diagName = 'ADVy'//diagSufx
669 CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid)
670 ENDIF
671 #endif
672
673 #ifdef ALLOW_DEBUG
674 IF ( debugLevel .GE. debLevB
675 & .AND. tracerIdentity.EQ.GAD_TEMPERATURE
676 & .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
677 & .AND. nPx.EQ.1 .AND. nPy.EQ.1
678 & .AND. useCubedSphereExchange ) THEN
679 CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_ADVECTION',
680 & afx,afy, k, standardMessageUnit,bi,bj,myThid )
681 ENDIF
682 #endif /* ALLOW_DEBUG */
683
684 C-- End of K loop for horizontal fluxes
685 ENDDO
686
687 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
688
689 IF ( .NOT.implicitAdvection ) THEN
690 C-- Start of k loop for vertical flux
691 DO k=Nr,1,-1
692 #ifdef ALLOW_AUTODIFF_TAMC
693 kkey = (igadkey-1)*Nr + k
694 #endif /* ALLOW_AUTODIFF_TAMC */
695 C-- kUp Cycles through 1,2 to point to w-layer above
696 C-- kDown Cycles through 2,1 to point to w-layer below
697 kUp = 1+MOD(k+1,2)
698 kDown= 1+MOD(k,2)
699 c kp1=min(Nr,k+1)
700 kp1Msk=1.
701 if (k.EQ.Nr) kp1Msk=0.
702
703 C-- Compute Vertical transport
704 #ifdef ALLOW_AIM
705 C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
706 IF ( k.EQ.1 .OR.
707 & (useAIM .AND. tracerIdentity.EQ.GAD_SALINITY .AND. k.EQ.Nr)
708 & ) THEN
709 #else
710 IF ( k.EQ.1 ) THEN
711 #endif
712
713 C- Surface interface :
714 DO j=1-Oly,sNy+Oly
715 DO i=1-Olx,sNx+Olx
716 rTransKp1(i,j) = kp1Msk*rTrans(i,j)
717 wFld(i,j) = 0.
718 rTrans(i,j) = 0.
719 fVerT(i,j,kUp) = 0.
720 ENDDO
721 ENDDO
722
723 ELSE
724 C- Interior interface :
725
726 DO j=1-Oly,sNy+Oly
727 DO i=1-Olx,sNx+Olx
728 rTransKp1(i,j) = kp1Msk*rTrans(i,j)
729 wFld(i,j) = wVel(i,j,k,bi,bj)
730 rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
731 & *maskC(i,j,k-1,bi,bj)
732 fVerT(i,j,kUp) = 0.
733 ENDDO
734 ENDDO
735
736 #ifdef ALLOW_GMREDI
737 C-- Residual transp = Bolus transp + Eulerian transp
738 IF (useGMRedi)
739 & CALL GMREDI_CALC_WFLOW(
740 U wFld, rTrans,
741 I k, bi, bj, myThid )
742 #endif /* ALLOW_GMREDI */
743
744 #ifdef ALLOW_AUTODIFF_TAMC
745 CADJ STORE localTijk(:,:,k)
746 CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
747 CADJ STORE rTrans(:,:)
748 CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
749 #endif /* ALLOW_AUTODIFF_TAMC */
750
751 C- Compute vertical advective flux in the interior:
752 IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
753 & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
754 CALL GAD_DST2U1_ADV_R( bi,bj,k, advectionScheme,
755 I dTtracerLev(k),rTrans,wFld,localTijk,
756 O fVerT(1-Olx,1-Oly,kUp), myThid )
757 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
758 CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),
759 I rTrans, wFld, localTijk,
760 O fVerT(1-Olx,1-Oly,kUp), myThid )
761 ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN
762 CALL GAD_DST3_ADV_R( bi,bj,k, dTtracerLev(k),
763 I rTrans, wFld, localTijk,
764 O fVerT(1-Olx,1-Oly,kUp), myThid )
765 ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
766 CALL GAD_DST3FL_ADV_R( bi,bj,k, dTtracerLev(k),
767 I rTrans, wFld, localTijk,
768 O fVerT(1-Olx,1-Oly,kUp), myThid )
769 ELSE
770 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
771 ENDIF
772
773 C- end Surface/Interior if bloc
774 ENDIF
775
776 #ifdef ALLOW_AUTODIFF_TAMC
777 CADJ STORE rTrans(:,:)
778 CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
779 CADJ STORE rTranskp1(:,:)
780 CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
781 #endif /* ALLOW_AUTODIFF_TAMC */
782
783 C-- Divergence of vertical fluxes
784 DO j=1-Oly,sNy+Oly
785 DO i=1-Olx,sNx+Olx
786 localTij(i,j)=localTijk(i,j,k)-dTtracerLev(k)*
787 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
788 & *recip_rA(i,j,bi,bj)
789 & *( fVerT(i,j,kDown)-fVerT(i,j,kUp)
790 & -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))
791 & )*rkSign
792 gTracer(i,j,k,bi,bj)=
793 & (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
794 ENDDO
795 ENDDO
796
797 #ifdef ALLOW_DIAGNOSTICS
798 IF ( useDiagnostics ) THEN
799 diagName = 'ADVr'//diagSufx
800 CALL DIAGNOSTICS_FILL( fVerT(1-Olx,1-Oly,kUp),
801 & diagName, k,1, 2,bi,bj, myThid)
802 ENDIF
803 #endif
804
805 C-- End of K loop for vertical flux
806 ENDDO
807 C-- end of if not.implicitAdvection block
808 ENDIF
809
810 RETURN
811 END

  ViewVC Help
Powered by ViewVC 1.1.22