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

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

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


Revision 1.32 - (hide annotations) (download)
Sat Dec 4 00:20:27 2004 UTC (19 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57, checkpoint57a_post, checkpoint57a_pre
Changes since 1.31: +19 -19 lines
depth convergence accelerator: replace deltaTtracer by dTtracerLev(k)

1 jmc 1.32 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_advection.F,v 1.31 2004/09/29 04:53:30 heimbach Exp $
2 adcroft 1.2 C $Name: $
3 adcroft 1.4
4 adcroft 1.1 #include "GAD_OPTIONS.h"
5 jmc 1.30 #undef MULTIDIM_OLD_VERSION
6 adcroft 1.1
7 edhill 1.19 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
8 adcroft 1.4 CBOP
9     C !ROUTINE: GAD_ADVECTION
10    
11     C !INTERFACE: ==========================================================
12 jmc 1.17 SUBROUTINE GAD_ADVECTION(
13 jmc 1.23 I implicitAdvection, advectionScheme, vertAdvecScheme,
14     I tracerIdentity,
15 edhill 1.21 I uVel, vVel, wVel, tracer,
16     O gTracer,
17     I bi,bj, myTime,myIter,myThid)
18 adcroft 1.4
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 adcroft 1.5 C - \Delta t \partial_x (u\theta^{(n)}) + \theta^{(n)} \partial_x u$}
29 adcroft 1.4 C \item{$\theta^{(n+2/3)} = \theta^{(n+1/3)}
30 adcroft 1.5 C - \Delta t \partial_y (v\theta^{(n+1/3)}) + \theta^{(n)} \partial_y v$}
31 adcroft 1.4 C \item{$\theta^{(n+3/3)} = \theta^{(n+2/3)}
32 adcroft 1.5 C - \Delta t \partial_r (w\theta^{(n+2/3)}) + \theta^{(n)} \partial_r w$}
33 adcroft 1.4 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 adcroft 1.1 IMPLICIT NONE
40     #include "SIZE.h"
41     #include "EEPARAMS.h"
42     #include "PARAMS.h"
43     #include "GRID.h"
44     #include "GAD.h"
45 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
46     # include "tamc.h"
47     # include "tamc_keys.h"
48 heimbach 1.27 # ifdef ALLOW_PTRACERS
49     # include "PTRACERS_SIZE.h"
50     # endif
51 heimbach 1.6 #endif
52 dimitri 1.24 #ifdef ALLOW_EXCH2
53     #include "W2_EXCH2_TOPOLOGY.h"
54     #include "W2_EXCH2_PARAMS.h"
55     #endif /* ALLOW_EXCH2 */
56 adcroft 1.1
57 adcroft 1.4 C !INPUT PARAMETERS: ===================================================
58 edhill 1.21 C implicitAdvection :: implicit vertical advection (later on)
59 jmc 1.23 C advectionScheme :: advection scheme to use (Horizontal plane)
60     C vertAdvecScheme :: advection scheme to use (vertical direction)
61 edhill 1.21 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 jmc 1.17 LOGICAL implicitAdvection
71 jmc 1.23 INTEGER advectionScheme, vertAdvecScheme
72 adcroft 1.1 INTEGER tracerIdentity
73 jmc 1.17 _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 adcroft 1.1 _RL myTime
79     INTEGER myIter
80     INTEGER myThid
81    
82 adcroft 1.4 C !OUTPUT PARAMETERS: ==================================================
83 edhill 1.21 C gTracer :: tendancy array
84 adcroft 1.9 _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
85 adcroft 1.4
86     C !LOCAL VARIABLES: ====================================================
87 edhill 1.21 C maskUp :: 2-D array for mask at W points
88 jmc 1.29 C maskLocW :: 2-D array for mask at West points
89     C maskLocS :: 2-D array for mask at South points
90 edhill 1.21 C iMin,iMax, :: loop range for called routines
91     C jMin,jMax :: loop range for called routines
92 jmc 1.30 C [iMin,iMax]Upd :: loop range to update tracer field
93     C [jMin,jMax]Upd :: loop range to update tracer field
94 edhill 1.21 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 jmc 1.30 C af :: 2-D array for horizontal advective flux
103 jmc 1.29 C afx :: 2-D array for horizontal advective flux, x direction
104     C afy :: 2-D array for horizontal advective flux, y direction
105 edhill 1.21 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 jmc 1.30 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 edhill 1.21 C nipass :: number of passes in multi-dimensional method
114     C ipass :: number of the current pass being made
115 dimitri 1.24 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 jmc 1.30 C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
119 adcroft 1.1 _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120 jmc 1.29 _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121     _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122 adcroft 1.1 INTEGER iMin,iMax,jMin,jMax
123 jmc 1.30 INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd
124 jmc 1.11 INTEGER i,j,k,kup,kDown
125 adcroft 1.1 _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 jmc 1.11 _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
131 jmc 1.30 _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
132 jmc 1.29 _RL afx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
133     _RL afy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
134 adcroft 1.1 _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 jmc 1.29 LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns
139 jmc 1.30 LOGICAL interiorOnly, overlapOnly
140 adcroft 1.3 INTEGER nipass,ipass
141 dimitri 1.24 INTEGER myTile, nCFace
142 jmc 1.30 LOGICAL N_edge, S_edge, E_edge, W_edge
143 adcroft 1.4 CEOP
144 adcroft 1.1
145 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
146 heimbach 1.14 act0 = tracerIdentity - 1
147     max0 = maxpass
148 heimbach 1.6 act1 = bi - myBxLo(myThid)
149     max1 = myBxHi(myThid) - myBxLo(myThid) + 1
150     act2 = bj - myByLo(myThid)
151     max2 = myByHi(myThid) - myByLo(myThid) + 1
152     act3 = myThid - 1
153     max3 = nTx*nTy
154     act4 = ikey_dynamics - 1
155 heimbach 1.14 igadkey = (act0 + 1)
156     & + act1*max0
157     & + act2*max0*max1
158     & + act3*max0*max1*max2
159     & + act4*max0*max1*max2*max3
160 heimbach 1.15 if (tracerIdentity.GT.maxpass) then
161     print *, 'ph-pass gad_advection ', maxpass, tracerIdentity
162     STOP 'maxpass seems smaller than tracerIdentity'
163     endif
164 heimbach 1.6 #endif /* ALLOW_AUTODIFF_TAMC */
165    
166 adcroft 1.1 C-- Set up work arrays with valid (i.e. not NaN) values
167     C These inital values do not alter the numerical results. They
168     C just ensure that all memory references are to valid floating
169     C point numbers. This prevents spurious hardware signals due to
170     C uninitialised but inert locations.
171     DO j=1-OLy,sNy+OLy
172     DO i=1-OLx,sNx+OLx
173     xA(i,j) = 0. _d 0
174     yA(i,j) = 0. _d 0
175     uTrans(i,j) = 0. _d 0
176     vTrans(i,j) = 0. _d 0
177     rTrans(i,j) = 0. _d 0
178     fVerT(i,j,1) = 0. _d 0
179     fVerT(i,j,2) = 0. _d 0
180 jmc 1.11 rTransKp1(i,j)= 0. _d 0
181 adcroft 1.1 ENDDO
182     ENDDO
183    
184 jmc 1.30 C-- Set tile-specific parameters for horizontal fluxes
185     IF (useCubedSphereExchange) THEN
186     nipass=3
187     #ifdef ALLOW_AUTODIFF_TAMC
188     IF ( nipass.GT.maxcube ) STOP 'maxcube needs to be = 3'
189     #endif
190     #ifdef ALLOW_EXCH2
191     myTile = W2_myTileList(bi)
192     nCFace = exch2_myFace(myTile)
193     N_edge = exch2_isNedge(myTile).EQ.1
194     S_edge = exch2_isSedge(myTile).EQ.1
195     E_edge = exch2_isEedge(myTile).EQ.1
196     W_edge = exch2_isWedge(myTile).EQ.1
197     #else
198     nCFace = bi
199     N_edge = .TRUE.
200     S_edge = .TRUE.
201     E_edge = .TRUE.
202     W_edge = .TRUE.
203     #endif
204     ELSE
205     nipass=2
206     N_edge = .FALSE.
207     S_edge = .FALSE.
208     E_edge = .FALSE.
209     W_edge = .FALSE.
210     ENDIF
211    
212 adcroft 1.1 iMin = 1-OLx
213     iMax = sNx+OLx
214     jMin = 1-OLy
215     jMax = sNy+OLy
216    
217     C-- Start of k loop for horizontal fluxes
218     DO k=1,Nr
219 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
220 heimbach 1.14 kkey = (igadkey-1)*Nr + k
221     CADJ STORE tracer(:,:,k,bi,bj) =
222     CADJ & comlev1_bibj_k_gad, key=kkey, byte=isbyte
223 heimbach 1.6 #endif /* ALLOW_AUTODIFF_TAMC */
224 adcroft 1.1
225     C-- Get temporary terms used by tendency routines
226     CALL CALC_COMMON_FACTORS (
227     I bi,bj,iMin,iMax,jMin,jMax,k,
228     O xA,yA,uTrans,vTrans,rTrans,maskUp,
229     I myThid)
230    
231 jmc 1.11 #ifdef ALLOW_GMREDI
232     C-- Residual transp = Bolus transp + Eulerian transp
233 jmc 1.30 IF (useGMRedi)
234 jmc 1.11 & CALL GMREDI_CALC_UVFLOW(
235     & uTrans, vTrans, bi, bj, k, myThid)
236     #endif /* ALLOW_GMREDI */
237    
238 jmc 1.29 C-- Make local copy of tracer array and mask West & South
239 adcroft 1.1 DO j=1-OLy,sNy+OLy
240     DO i=1-OLx,sNx+OLx
241 jmc 1.30 localTij(i,j)=tracer(i,j,k,bi,bj)
242     maskLocW(i,j)=maskW(i,j,k,bi,bj)
243     maskLocS(i,j)=maskS(i,j,k,bi,bj)
244 adcroft 1.1 ENDDO
245     ENDDO
246    
247 heimbach 1.31 #ifndef ALLOW_AUTODIFF_TAMC
248 jmc 1.29 IF (useCubedSphereExchange) THEN
249     withSigns = .FALSE.
250     CALL FILL_CS_CORNER_UV_RS(
251     & withSigns, maskLocW,maskLocS, bi,bj, myThid )
252     ENDIF
253 heimbach 1.31 #endif
254 adcroft 1.3
255     C-- Multiple passes for different directions on different tiles
256 dimitri 1.24 C-- For cube need one pass for each of red, green and blue axes.
257 adcroft 1.3 DO ipass=1,nipass
258 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
259 heimbach 1.14 passkey = ipass + (k-1) *maxcube
260     & + (igadkey-1)*maxcube*Nr
261 heimbach 1.6 IF (nipass .GT. maxpass) THEN
262 heimbach 1.14 STOP 'GAD_ADVECTION: nipass > maxcube. check tamc.h'
263 heimbach 1.6 ENDIF
264     #endif /* ALLOW_AUTODIFF_TAMC */
265 adcroft 1.3
266 jmc 1.30 interiorOnly = .FALSE.
267     overlapOnly = .FALSE.
268     IF (useCubedSphereExchange) THEN
269     #ifdef MULTIDIM_OLD_VERSION
270     C- CubedSphere : pass 3 times, with full update of local tracer field
271     IF (ipass.EQ.1) THEN
272     calc_fluxes_X = nCFace.EQ.1 .OR. nCFace.EQ.2
273     calc_fluxes_Y = nCFace.EQ.4 .OR. nCFace.EQ.5
274     ELSEIF (ipass.EQ.2) THEN
275     calc_fluxes_X = nCFace.EQ.3 .OR. nCFace.EQ.4
276     calc_fluxes_Y = nCFace.EQ.6 .OR. nCFace.EQ.1
277     #else /* MULTIDIM_OLD_VERSION */
278     C- CubedSphere : pass 3 times, with partial update of local tracer field
279     IF (ipass.EQ.1) THEN
280     overlapOnly = MOD(nCFace,3).EQ.0
281     interiorOnly = MOD(nCFace,3).NE.0
282     calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
283     calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
284     ELSEIF (ipass.EQ.2) THEN
285     overlapOnly = MOD(nCFace,3).EQ.2
286     calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
287     calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
288     #endif /* MULTIDIM_OLD_VERSION */
289     ELSE
290     calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
291     calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
292 adcroft 1.3 ENDIF
293     ELSE
294 jmc 1.30 C- not CubedSphere
295     calc_fluxes_X = MOD(ipass,2).EQ.1
296     calc_fluxes_Y = .NOT.calc_fluxes_X
297 adcroft 1.3 ENDIF
298    
299 jmc 1.29 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
300 adcroft 1.3 C-- X direction
301     IF (calc_fluxes_X) THEN
302    
303 jmc 1.30 C- Do not compute fluxes if
304     C a) needed in overlap only
305     C and b) the overlap of myTile are not cube-face Edges
306     IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
307    
308 heimbach 1.31 #ifndef ALLOW_AUTODIFF_TAMC
309 jmc 1.30 C- Internal exchange for calculations in X
310     #ifdef MULTIDIM_OLD_VERSION
311     IF ( useCubedSphereExchange ) THEN
312     #else
313     IF ( useCubedSphereExchange .AND.
314     & ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
315     #endif
316 jmc 1.29 CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
317 jmc 1.30 ENDIF
318 heimbach 1.31 #endif
319 adcroft 1.3
320 jmc 1.30 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 heimbach 1.6
327     #ifdef ALLOW_AUTODIFF_TAMC
328 adcroft 1.7 #ifndef DISABLE_MULTIDIM_ADVECTION
329 heimbach 1.14 CADJ STORE localTij(:,:) =
330     CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
331 heimbach 1.6 #endif
332     #endif /* ALLOW_AUTODIFF_TAMC */
333    
334 jmc 1.30 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
335 jmc 1.32 CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, dTtracerLev(k),
336 jmc 1.30 I uTrans, uVel, maskLocW, localTij,
337     O af, myThid )
338     ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
339 jmc 1.32 CALL GAD_DST3_ADV_X( bi,bj,k, dTtracerLev(k),
340 jmc 1.30 I uTrans, uVel, maskLocW, localTij,
341     O af, myThid )
342     ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
343 jmc 1.32 CALL GAD_DST3FL_ADV_X( bi,bj,k, dTtracerLev(k),
344 jmc 1.30 I uTrans, uVel, maskLocW, localTij,
345     O af, myThid )
346     ELSE
347     STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
348     ENDIF
349    
350     C- Advective flux in X : done
351     ENDIF
352    
353 heimbach 1.31 #ifndef ALLOW_AUTODIFF_TAMC
354 jmc 1.30 C- Internal exchange for next calculations in Y
355     IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
356     CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
357     ENDIF
358 heimbach 1.31 #endif
359 jmc 1.30
360     C- Update the local tracer field where needed:
361    
362     C update in overlap-Only
363     IF ( overlapOnly ) THEN
364     iMinUpd = 1-Olx+1
365     iMaxUpd = sNx+Olx-1
366     C- notes: these 2 lines below have no real effect (because recip_hFac=0
367     C in corner region) but safer to keep them.
368     IF ( W_edge ) iMinUpd = 1
369     IF ( E_edge ) iMaxUpd = sNx
370    
371     IF ( S_edge ) THEN
372     DO j=1-Oly,0
373     DO i=iMinUpd,iMaxUpd
374 jmc 1.32 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
375 jmc 1.30 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
376     & *recip_rA(i,j,bi,bj)
377     & *( af(i+1,j)-af(i,j)
378     & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
379     & )
380     ENDDO
381     ENDDO
382     ENDIF
383     IF ( N_edge ) THEN
384     DO j=sNy+1,sNy+Oly
385     DO i=iMinUpd,iMaxUpd
386 jmc 1.32 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
387 jmc 1.30 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
388     & *recip_rA(i,j,bi,bj)
389     & *( af(i+1,j)-af(i,j)
390     & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
391     & )
392     ENDDO
393     ENDDO
394     ENDIF
395 heimbach 1.6
396 jmc 1.30 ELSE
397     C do not only update the overlap
398     jMinUpd = 1-Oly
399     jMaxUpd = sNy+Oly
400     IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
401     IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
402     DO j=jMinUpd,jMaxUpd
403     DO i=1-Olx+1,sNx+Olx-1
404 jmc 1.32 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
405 jmc 1.30 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
406     & *recip_rA(i,j,bi,bj)
407     & *( af(i+1,j)-af(i,j)
408     & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
409     & )
410     ENDDO
411     ENDDO
412     C- keep advective flux (for diagnostics)
413     DO j=1-Oly,sNy+Oly
414     DO i=1-Olx,sNx+Olx
415     afx(i,j) = af(i,j)
416     ENDDO
417     ENDDO
418 adcroft 1.1
419     #ifdef ALLOW_OBCS
420 jmc 1.30 C- Apply open boundary conditions
421     IF ( useOBCS ) THEN
422     IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
423     CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
424     ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
425     CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
426     ENDIF
427     ENDIF
428 adcroft 1.1 #endif /* ALLOW_OBCS */
429    
430 jmc 1.30 C- end if/else update overlap-Only
431     ENDIF
432    
433 adcroft 1.3 C-- End of X direction
434     ENDIF
435    
436 jmc 1.29 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
437 adcroft 1.3 C-- Y direction
438     IF (calc_fluxes_Y) THEN
439    
440 jmc 1.30 C- Do not compute fluxes if
441     C a) needed in overlap only
442     C and b) the overlap of myTile are not cube-face edges
443     IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
444    
445 heimbach 1.31 #ifndef ALLOW_AUTODIFF_TAMC
446 jmc 1.30 C- Internal exchange for calculations in Y
447     #ifdef MULTIDIM_OLD_VERSION
448     IF ( useCubedSphereExchange ) THEN
449     #else
450     IF ( useCubedSphereExchange .AND.
451     & ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
452     #endif
453 jmc 1.29 CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
454 jmc 1.30 ENDIF
455 heimbach 1.31 #endif
456 adcroft 1.3
457 jmc 1.30 C- Advective flux in Y
458     DO j=1-Oly,sNy+Oly
459     DO i=1-Olx,sNx+Olx
460     af(i,j) = 0.
461     ENDDO
462     ENDDO
463 heimbach 1.6
464     #ifdef ALLOW_AUTODIFF_TAMC
465 adcroft 1.7 #ifndef DISABLE_MULTIDIM_ADVECTION
466 heimbach 1.14 CADJ STORE localTij(:,:) =
467     CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
468 heimbach 1.6 #endif
469     #endif /* ALLOW_AUTODIFF_TAMC */
470    
471 jmc 1.30 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
472 jmc 1.32 CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, dTtracerLev(k),
473 jmc 1.30 I vTrans, vVel, maskLocS, localTij,
474     O af, myThid )
475     ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
476 jmc 1.32 CALL GAD_DST3_ADV_Y( bi,bj,k, dTtracerLev(k),
477 jmc 1.30 I vTrans, vVel, maskLocS, localTij,
478     O af, myThid )
479     ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
480 jmc 1.32 CALL GAD_DST3FL_ADV_Y( bi,bj,k, dTtracerLev(k),
481 jmc 1.30 I vTrans, vVel, maskLocS, localTij,
482     O af, myThid )
483     ELSE
484     STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
485     ENDIF
486    
487     C- Advective flux in Y : done
488     ENDIF
489    
490 heimbach 1.31 #ifndef ALLOW_AUTODIFF_TAMC
491 jmc 1.30 C- Internal exchange for next calculations in X
492     IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
493     CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
494     ENDIF
495 heimbach 1.31 #endif
496 jmc 1.30
497     C- Update the local tracer field where needed:
498    
499     C update in overlap-Only
500     IF ( overlapOnly ) THEN
501     jMinUpd = 1-Oly+1
502     jMaxUpd = sNy+Oly-1
503     C- notes: these 2 lines below have no real effect (because recip_hFac=0
504     C in corner region) but safer to keep them.
505     IF ( S_edge ) jMinUpd = 1
506     IF ( N_edge ) jMaxUpd = sNy
507    
508     IF ( W_edge ) THEN
509     DO j=jMinUpd,jMaxUpd
510     DO i=1-Olx,0
511 jmc 1.32 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
512 jmc 1.30 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
513     & *recip_rA(i,j,bi,bj)
514     & *( af(i,j+1)-af(i,j)
515     & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
516     & )
517     ENDDO
518     ENDDO
519     ENDIF
520     IF ( E_edge ) THEN
521     DO j=jMinUpd,jMaxUpd
522     DO i=sNx+1,sNx+Olx
523 jmc 1.32 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
524 jmc 1.30 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
525     & *recip_rA(i,j,bi,bj)
526     & *( af(i,j+1)-af(i,j)
527     & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
528     & )
529     ENDDO
530     ENDDO
531     ENDIF
532 heimbach 1.6
533 jmc 1.30 ELSE
534     C do not only update the overlap
535     iMinUpd = 1-Olx
536     iMaxUpd = sNx+Olx
537     IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
538     IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
539     DO j=1-Oly+1,sNy+Oly-1
540     DO i=iMinUpd,iMaxUpd
541 jmc 1.32 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
542 jmc 1.30 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
543     & *recip_rA(i,j,bi,bj)
544     & *( af(i,j+1)-af(i,j)
545     & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
546     & )
547     ENDDO
548     ENDDO
549     C- keep advective flux (for diagnostics)
550     DO j=1-Oly,sNy+Oly
551     DO i=1-Olx,sNx+Olx
552     afy(i,j) = af(i,j)
553     ENDDO
554     ENDDO
555 adcroft 1.3
556 adcroft 1.1 #ifdef ALLOW_OBCS
557 jmc 1.30 C- Apply open boundary conditions
558     IF (useOBCS) THEN
559     IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
560     CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
561     ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
562     CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
563     ENDIF
564     ENDIF
565 adcroft 1.1 #endif /* ALLOW_OBCS */
566 adcroft 1.3
567 jmc 1.30 C end if/else update overlap-Only
568     ENDIF
569    
570 adcroft 1.3 C-- End of Y direction
571     ENDIF
572    
573 jmc 1.18 C-- End of ipass loop
574 adcroft 1.1 ENDDO
575    
576 jmc 1.18 IF ( implicitAdvection ) THEN
577     C- explicit advection is done ; store tendency in gTracer:
578     DO j=1-Oly,sNy+Oly
579     DO i=1-Olx,sNx+Olx
580     gTracer(i,j,k,bi,bj)=
581 jmc 1.32 & (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
582 jmc 1.18 ENDDO
583     ENDDO
584     ELSE
585     C- horizontal advection done; store intermediate result in 3D array:
586     DO j=1-Oly,sNy+Oly
587     DO i=1-Olx,sNx+Olx
588     localTijk(i,j,k)=localTij(i,j)
589     ENDDO
590     ENDDO
591     ENDIF
592 adcroft 1.1
593 jmc 1.29 #ifdef ALLOW_DEBUG
594     IF ( debugLevel .GE. debLevB
595 jmc 1.30 & .AND. tracerIdentity.EQ.GAD_TEMPERATURE
596     & .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
597 jmc 1.29 & .AND. nPx.EQ.1 .AND. nPy.EQ.1
598     & .AND. useCubedSphereExchange ) THEN
599     CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_ADVECTION',
600     & afx,afy, k, standardMessageUnit,bi,bj,myThid )
601     ENDIF
602     #endif /* ALLOW_DEBUG */
603    
604 adcroft 1.1 C-- End of K loop for horizontal fluxes
605     ENDDO
606    
607 jmc 1.29 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
608    
609 jmc 1.18 IF ( .NOT.implicitAdvection ) THEN
610 adcroft 1.1 C-- Start of k loop for vertical flux
611 jmc 1.18 DO k=Nr,1,-1
612 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
613 heimbach 1.16 kkey = (igadkey-1)*Nr + k
614 heimbach 1.6 #endif /* ALLOW_AUTODIFF_TAMC */
615 adcroft 1.1 C-- kup Cycles through 1,2 to point to w-layer above
616     C-- kDown Cycles through 2,1 to point to w-layer below
617 jmc 1.18 kup = 1+MOD(k+1,2)
618     kDown= 1+MOD(k,2)
619     c kp1=min(Nr,k+1)
620     kp1Msk=1.
621     if (k.EQ.Nr) kp1Msk=0.
622 heimbach 1.6
623 jmc 1.11 C-- Compute Vertical transport
624 jmc 1.22 #ifdef ALLOW_AIM
625     C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
626     IF ( k.EQ.1 .OR.
627     & (useAIM .AND. tracerIdentity.EQ.GAD_SALINITY .AND. k.EQ.Nr)
628     & ) THEN
629     #else
630     IF ( k.EQ.1 ) THEN
631     #endif
632 jmc 1.11
633     C- Surface interface :
634 jmc 1.18 DO j=1-Oly,sNy+Oly
635     DO i=1-Olx,sNx+Olx
636 jmc 1.22 rTransKp1(i,j) = kp1Msk*rTrans(i,j)
637 jmc 1.18 rTrans(i,j) = 0.
638     fVerT(i,j,kUp) = 0.
639     ENDDO
640     ENDDO
641 jmc 1.11
642 jmc 1.18 ELSE
643     C- Interior interface :
644 jmc 1.11
645 jmc 1.18 DO j=1-Oly,sNy+Oly
646     DO i=1-Olx,sNx+Olx
647     rTransKp1(i,j) = kp1Msk*rTrans(i,j)
648     rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
649     & *maskC(i,j,k-1,bi,bj)
650 jmc 1.29 fVerT(i,j,kUp) = 0.
651 jmc 1.18 ENDDO
652     ENDDO
653 jmc 1.11
654     #ifdef ALLOW_GMREDI
655     C-- Residual transp = Bolus transp + Eulerian transp
656 jmc 1.18 IF (useGMRedi)
657 jmc 1.11 & CALL GMREDI_CALC_WFLOW(
658     & rTrans, bi, bj, k, myThid)
659     #endif /* ALLOW_GMREDI */
660    
661 heimbach 1.16 #ifdef ALLOW_AUTODIFF_TAMC
662     CADJ STORE localTijk(:,:,k)
663     CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
664     CADJ STORE rTrans(:,:)
665     CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
666     #endif /* ALLOW_AUTODIFF_TAMC */
667    
668 adcroft 1.1 C- Compute vertical advective flux in the interior:
669 jmc 1.23 IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
670 jmc 1.29 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
671 jmc 1.32 CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),
672 jmc 1.29 I rTrans, wVel, localTijk,
673     O fVerT(1-Olx,1-Oly,kUp), myThid )
674 jmc 1.23 ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN
675 jmc 1.32 CALL GAD_DST3_ADV_R( bi,bj,k, dTtracerLev(k),
676 jmc 1.29 I rTrans, wVel, localTijk,
677     O fVerT(1-Olx,1-Oly,kUp), myThid )
678 jmc 1.23 ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
679 jmc 1.32 CALL GAD_DST3FL_ADV_R( bi,bj,k, dTtracerLev(k),
680 jmc 1.29 I rTrans, wVel, localTijk,
681     O fVerT(1-Olx,1-Oly,kUp), myThid )
682 jmc 1.18 ELSE
683     STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
684     ENDIF
685 jmc 1.11
686     C- end Surface/Interior if bloc
687 jmc 1.18 ENDIF
688 heimbach 1.16
689     #ifdef ALLOW_AUTODIFF_TAMC
690     CADJ STORE rTrans(:,:)
691     CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
692     CADJ STORE rTranskp1(:,:)
693     CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
694     #endif /* ALLOW_AUTODIFF_TAMC */
695 adcroft 1.1
696 jmc 1.18 C-- Divergence of vertical fluxes
697     DO j=1-Oly,sNy+Oly
698     DO i=1-Olx,sNx+Olx
699 jmc 1.32 localTij(i,j)=localTijk(i,j,k)-dTtracerLev(k)*
700 jmc 1.18 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
701     & *recip_rA(i,j,bi,bj)
702     & *( fVerT(i,j,kUp)-fVerT(i,j,kDown)
703     & -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))
704     & )*rkFac
705     gTracer(i,j,k,bi,bj)=
706 jmc 1.32 & (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
707 jmc 1.18 ENDDO
708     ENDDO
709 adcroft 1.1
710     C-- End of K loop for vertical flux
711 jmc 1.18 ENDDO
712     C-- end of if not.implicitAdvection block
713     ENDIF
714 adcroft 1.1
715     RETURN
716     END

  ViewVC Help
Powered by ViewVC 1.1.22