/[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.40 - (show annotations) (download)
Tue Feb 21 17:20:12 2006 UTC (18 years, 4 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58b_post, checkpoint58f_post, checkpoint58d_post, checkpoint58e_post, checkpoint58g_post, checkpoint58h_post, checkpoint58j_post, checkpoint58i_post, checkpoint58c_post
Changes since 1.39: +5 -3 lines
Fix GAD keys that are now also used by seaice.

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

  ViewVC Help
Powered by ViewVC 1.1.22