/[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.62 - (show annotations) (download)
Sun Jun 28 01:05:41 2009 UTC (14 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62c, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62m, checkpoint62l, checkpoint62, checkpoint62b, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.61: +2 -2 lines
add bj in exch2 arrays and S/R

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

  ViewVC Help
Powered by ViewVC 1.1.22