/[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.36 - (hide annotations) (download)
Mon Oct 10 05:53:49 2005 UTC (18 years, 7 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint57v_post, checkpint57u_post
Changes since 1.35: +10 -0 lines
o OBCS and PTRACERS: add open boundary support for passive tracers
  - either use homogenous (pseudo) v.Neumann conditions or prescribe
    OB-values from file; this is not different from the way theta and salinity
    are treated
  - however, Orlanski-radiation conditions are not supported, and the model
    will stop if you use pTracers and Orlanski at the same time.
  - beefed up the rountine obcs_external_fields_load: now only those open
    boundary values are overwritten with values from files for which there
    are really files, otherwise the OB-fields remain untouched. This makes
    it possible to use different OBs at different ends of the domain (as
    with EXF)
  - TODO: add support for OB?w and OB?eta, which can currently not be read
    from a file.

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

  ViewVC Help
Powered by ViewVC 1.1.22