/[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.39 - (hide annotations) (download)
Thu Dec 8 15:44:34 2005 UTC (18 years, 6 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57y_post, checkpoint58, checkpoint58a_post, checkpoint57z_post
Changes since 1.38: +37 -10 lines
First step for a NLFS adjoint
o initially suppress rStar (new flag DISABLE_RSTAR_CODE)
o new init. routines for calc_r_star, calc_surf_dr
o still need to deal with ini_masks_etc
o testreport seemed happy

1 heimbach 1.39 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_advection.F,v 1.38 2005/11/05 01:01:51 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 jmc 1.38 INTEGER nCFace
142 jmc 1.30 LOGICAL N_edge, S_edge, E_edge, W_edge
143 jmc 1.38 #ifdef ALLOW_EXCH2
144     INTEGER myTile
145     #endif
146 jmc 1.33 #ifdef ALLOW_DIAGNOSTICS
147     CHARACTER*8 diagName
148     CHARACTER*4 GAD_DIAG_SUFX, diagSufx
149     EXTERNAL GAD_DIAG_SUFX
150     #endif
151 adcroft 1.4 CEOP
152 adcroft 1.1
153 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
154 heimbach 1.14 act0 = tracerIdentity - 1
155     max0 = maxpass
156 heimbach 1.6 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 heimbach 1.14 igadkey = (act0 + 1)
164     & + act1*max0
165     & + act2*max0*max1
166     & + act3*max0*max1*max2
167     & + act4*max0*max1*max2*max3
168 heimbach 1.15 if (tracerIdentity.GT.maxpass) then
169     print *, 'ph-pass gad_advection ', maxpass, tracerIdentity
170     STOP 'maxpass seems smaller than tracerIdentity'
171     endif
172 heimbach 1.6 #endif /* ALLOW_AUTODIFF_TAMC */
173    
174 jmc 1.33 #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 adcroft 1.1 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 jmc 1.11 rTransKp1(i,j)= 0. _d 0
196 heimbach 1.39 #ifdef ALLOW_AUTODIFF_TAMC
197     localTij(i,j) = 0. _d 0
198     #endif
199 adcroft 1.1 ENDDO
200     ENDDO
201    
202 jmc 1.30 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 jmc 1.38 nCFace = bi
225 jmc 1.30 N_edge = .FALSE.
226     S_edge = .FALSE.
227     E_edge = .FALSE.
228     W_edge = .FALSE.
229     ENDIF
230    
231 adcroft 1.1 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 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
239 heimbach 1.14 kkey = (igadkey-1)*Nr + k
240     CADJ STORE tracer(:,:,k,bi,bj) =
241     CADJ & comlev1_bibj_k_gad, key=kkey, byte=isbyte
242 heimbach 1.6 #endif /* ALLOW_AUTODIFF_TAMC */
243 adcroft 1.1
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 jmc 1.11 #ifdef ALLOW_GMREDI
251     C-- Residual transp = Bolus transp + Eulerian transp
252 jmc 1.30 IF (useGMRedi)
253 jmc 1.11 & CALL GMREDI_CALC_UVFLOW(
254     & uTrans, vTrans, bi, bj, k, myThid)
255     #endif /* ALLOW_GMREDI */
256    
257 jmc 1.29 C-- Make local copy of tracer array and mask West & South
258 adcroft 1.1 DO j=1-OLy,sNy+OLy
259     DO i=1-OLx,sNx+OLx
260 jmc 1.30 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 adcroft 1.1 ENDDO
264     ENDDO
265    
266 heimbach 1.31 #ifndef ALLOW_AUTODIFF_TAMC
267 jmc 1.29 IF (useCubedSphereExchange) THEN
268     withSigns = .FALSE.
269     CALL FILL_CS_CORNER_UV_RS(
270     & withSigns, maskLocW,maskLocS, bi,bj, myThid )
271     ENDIF
272 heimbach 1.31 #endif
273 adcroft 1.3
274     C-- Multiple passes for different directions on different tiles
275 dimitri 1.24 C-- For cube need one pass for each of red, green and blue axes.
276 adcroft 1.3 DO ipass=1,nipass
277 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
278 heimbach 1.14 passkey = ipass + (k-1) *maxcube
279     & + (igadkey-1)*maxcube*Nr
280 heimbach 1.6 IF (nipass .GT. maxpass) THEN
281 heimbach 1.14 STOP 'GAD_ADVECTION: nipass > maxcube. check tamc.h'
282 heimbach 1.6 ENDIF
283     #endif /* ALLOW_AUTODIFF_TAMC */
284 adcroft 1.3
285 jmc 1.30 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 adcroft 1.3 ENDIF
312     ELSE
313 jmc 1.30 C- not CubedSphere
314     calc_fluxes_X = MOD(ipass,2).EQ.1
315     calc_fluxes_Y = .NOT.calc_fluxes_X
316 adcroft 1.3 ENDIF
317    
318 jmc 1.29 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
319 adcroft 1.3 C-- X direction
320 heimbach 1.39 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     cph-test
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 /* ALLOW_AUTODIFF_TAMC */
334     C
335 adcroft 1.3 IF (calc_fluxes_X) THEN
336    
337 jmc 1.30 C- Do not compute fluxes if
338     C a) needed in overlap only
339     C and b) the overlap of myTile are not cube-face Edges
340     IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
341    
342 heimbach 1.31 #ifndef ALLOW_AUTODIFF_TAMC
343 jmc 1.30 C- Internal exchange for calculations in X
344     #ifdef MULTIDIM_OLD_VERSION
345     IF ( useCubedSphereExchange ) THEN
346     #else
347     IF ( useCubedSphereExchange .AND.
348     & ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
349     #endif
350 jmc 1.29 CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
351 jmc 1.30 ENDIF
352 heimbach 1.31 #endif
353 adcroft 1.3
354 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
355 heimbach 1.39 # ifndef DISABLE_MULTIDIM_ADVECTION
356 heimbach 1.14 CADJ STORE localTij(:,:) =
357     CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
358 heimbach 1.39 # endif
359 heimbach 1.6 #endif /* ALLOW_AUTODIFF_TAMC */
360    
361 jmc 1.37 IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
362     & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
363     CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme,
364     I dTtracerLev(k),uTrans,uVel,localTij,
365     O af, myThid )
366     ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
367 jmc 1.32 CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, dTtracerLev(k),
368 jmc 1.30 I uTrans, uVel, maskLocW, localTij,
369     O af, myThid )
370     ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
371 jmc 1.32 CALL GAD_DST3_ADV_X( bi,bj,k, dTtracerLev(k),
372 jmc 1.30 I uTrans, uVel, maskLocW, localTij,
373     O af, myThid )
374     ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
375 jmc 1.32 CALL GAD_DST3FL_ADV_X( bi,bj,k, dTtracerLev(k),
376 jmc 1.30 I uTrans, uVel, maskLocW, localTij,
377     O af, myThid )
378     ELSE
379     STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
380     ENDIF
381    
382     C- Advective flux in X : done
383     ENDIF
384    
385 heimbach 1.31 #ifndef ALLOW_AUTODIFF_TAMC
386 jmc 1.30 C- Internal exchange for next calculations in Y
387     IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
388     CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
389     ENDIF
390 heimbach 1.31 #endif
391 jmc 1.30
392     C- Update the local tracer field where needed:
393    
394     C update in overlap-Only
395     IF ( overlapOnly ) THEN
396     iMinUpd = 1-Olx+1
397     iMaxUpd = sNx+Olx-1
398     C- notes: these 2 lines below have no real effect (because recip_hFac=0
399     C in corner region) but safer to keep them.
400     IF ( W_edge ) iMinUpd = 1
401     IF ( E_edge ) iMaxUpd = sNx
402    
403     IF ( S_edge ) THEN
404     DO j=1-Oly,0
405     DO i=iMinUpd,iMaxUpd
406 jmc 1.32 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
407 jmc 1.30 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
408     & *recip_rA(i,j,bi,bj)
409     & *( af(i+1,j)-af(i,j)
410     & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
411     & )
412     ENDDO
413     ENDDO
414     ENDIF
415     IF ( N_edge ) THEN
416     DO j=sNy+1,sNy+Oly
417     DO i=iMinUpd,iMaxUpd
418 jmc 1.32 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
419 jmc 1.30 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
420     & *recip_rA(i,j,bi,bj)
421     & *( af(i+1,j)-af(i,j)
422     & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
423     & )
424     ENDDO
425     ENDDO
426     ENDIF
427 heimbach 1.6
428 jmc 1.30 ELSE
429     C do not only update the overlap
430     jMinUpd = 1-Oly
431     jMaxUpd = sNy+Oly
432     IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
433     IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
434     DO j=jMinUpd,jMaxUpd
435     DO i=1-Olx+1,sNx+Olx-1
436 jmc 1.32 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
437 jmc 1.30 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
438     & *recip_rA(i,j,bi,bj)
439     & *( af(i+1,j)-af(i,j)
440     & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
441     & )
442     ENDDO
443     ENDDO
444     C- keep advective flux (for diagnostics)
445     DO j=1-Oly,sNy+Oly
446     DO i=1-Olx,sNx+Olx
447     afx(i,j) = af(i,j)
448     ENDDO
449     ENDDO
450 adcroft 1.1
451     #ifdef ALLOW_OBCS
452 jmc 1.30 C- Apply open boundary conditions
453     IF ( useOBCS ) THEN
454     IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
455     CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
456     ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
457     CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
458 mlosch 1.36 #ifdef ALLOW_PTRACERS
459     ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
460     CALL OBCS_APPLY_PTRACER( bi, bj, k,
461     & tracerIdentity-GAD_TR1+1, localTij, myThid )
462     #endif /* ALLOW_PTRACERS */
463 jmc 1.30 ENDIF
464     ENDIF
465 adcroft 1.1 #endif /* ALLOW_OBCS */
466    
467 jmc 1.30 C- end if/else update overlap-Only
468     ENDIF
469    
470 adcroft 1.3 C-- End of X direction
471     ENDIF
472    
473 jmc 1.29 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
474 adcroft 1.3 C-- Y direction
475 heimbach 1.39 cph-test
476     C- Advective flux in Y
477     DO j=1-Oly,sNy+Oly
478     DO i=1-Olx,sNx+Olx
479     af(i,j) = 0.
480     ENDDO
481     ENDDO
482     C
483     #ifdef ALLOW_AUTODIFF_TAMC
484     cph-test
485     CADJ STORE localTij(:,:) =
486     CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
487     CADJ STORE af(:,:) =
488     CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
489     #endif /* ALLOW_AUTODIFF_TAMC */
490     C
491 adcroft 1.3 IF (calc_fluxes_Y) THEN
492    
493 jmc 1.30 C- Do not compute fluxes if
494     C a) needed in overlap only
495     C and b) the overlap of myTile are not cube-face edges
496     IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
497    
498 heimbach 1.31 #ifndef ALLOW_AUTODIFF_TAMC
499 jmc 1.30 C- Internal exchange for calculations in Y
500     #ifdef MULTIDIM_OLD_VERSION
501     IF ( useCubedSphereExchange ) THEN
502     #else
503     IF ( useCubedSphereExchange .AND.
504     & ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
505     #endif
506 jmc 1.29 CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
507 jmc 1.30 ENDIF
508 heimbach 1.31 #endif
509 adcroft 1.3
510 jmc 1.30 C- Advective flux in Y
511     DO j=1-Oly,sNy+Oly
512     DO i=1-Olx,sNx+Olx
513     af(i,j) = 0.
514     ENDDO
515     ENDDO
516 heimbach 1.6
517     #ifdef ALLOW_AUTODIFF_TAMC
518 adcroft 1.7 #ifndef DISABLE_MULTIDIM_ADVECTION
519 heimbach 1.14 CADJ STORE localTij(:,:) =
520     CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
521 heimbach 1.6 #endif
522     #endif /* ALLOW_AUTODIFF_TAMC */
523    
524 jmc 1.37 IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
525     & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
526     CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme,
527     I dTtracerLev(k),vTrans,vVel,localTij,
528     O af, myThid )
529     ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
530 jmc 1.32 CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, dTtracerLev(k),
531 jmc 1.30 I vTrans, vVel, maskLocS, localTij,
532     O af, myThid )
533     ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
534 jmc 1.32 CALL GAD_DST3_ADV_Y( bi,bj,k, dTtracerLev(k),
535 jmc 1.30 I vTrans, vVel, maskLocS, localTij,
536     O af, myThid )
537     ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
538 jmc 1.32 CALL GAD_DST3FL_ADV_Y( bi,bj,k, dTtracerLev(k),
539 jmc 1.30 I vTrans, vVel, maskLocS, localTij,
540     O af, myThid )
541     ELSE
542     STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
543     ENDIF
544    
545     C- Advective flux in Y : done
546     ENDIF
547    
548 heimbach 1.31 #ifndef ALLOW_AUTODIFF_TAMC
549 jmc 1.30 C- Internal exchange for next calculations in X
550     IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
551     CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
552     ENDIF
553 heimbach 1.31 #endif
554 jmc 1.30
555     C- Update the local tracer field where needed:
556    
557     C update in overlap-Only
558     IF ( overlapOnly ) THEN
559     jMinUpd = 1-Oly+1
560     jMaxUpd = sNy+Oly-1
561     C- notes: these 2 lines below have no real effect (because recip_hFac=0
562     C in corner region) but safer to keep them.
563     IF ( S_edge ) jMinUpd = 1
564     IF ( N_edge ) jMaxUpd = sNy
565    
566     IF ( W_edge ) THEN
567     DO j=jMinUpd,jMaxUpd
568     DO i=1-Olx,0
569 jmc 1.32 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
570 jmc 1.30 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
571     & *recip_rA(i,j,bi,bj)
572     & *( af(i,j+1)-af(i,j)
573     & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
574     & )
575     ENDDO
576     ENDDO
577     ENDIF
578     IF ( E_edge ) THEN
579     DO j=jMinUpd,jMaxUpd
580     DO i=sNx+1,sNx+Olx
581 jmc 1.32 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
582 jmc 1.30 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
583     & *recip_rA(i,j,bi,bj)
584     & *( af(i,j+1)-af(i,j)
585     & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
586     & )
587     ENDDO
588     ENDDO
589     ENDIF
590 heimbach 1.6
591 jmc 1.30 ELSE
592     C do not only update the overlap
593     iMinUpd = 1-Olx
594     iMaxUpd = sNx+Olx
595     IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
596     IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
597     DO j=1-Oly+1,sNy+Oly-1
598     DO i=iMinUpd,iMaxUpd
599 jmc 1.32 localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
600 jmc 1.30 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
601     & *recip_rA(i,j,bi,bj)
602     & *( af(i,j+1)-af(i,j)
603     & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
604     & )
605     ENDDO
606     ENDDO
607     C- keep advective flux (for diagnostics)
608     DO j=1-Oly,sNy+Oly
609     DO i=1-Olx,sNx+Olx
610     afy(i,j) = af(i,j)
611     ENDDO
612     ENDDO
613 adcroft 1.3
614 adcroft 1.1 #ifdef ALLOW_OBCS
615 jmc 1.30 C- Apply open boundary conditions
616     IF (useOBCS) THEN
617     IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
618     CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
619     ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
620     CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
621 mlosch 1.36 #ifdef ALLOW_PTRACERS
622     ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
623     CALL OBCS_APPLY_PTRACER( bi, bj, k,
624     & tracerIdentity-GAD_TR1+1, localTij, myThid )
625     #endif /* ALLOW_PTRACERS */
626 jmc 1.30 ENDIF
627     ENDIF
628 adcroft 1.1 #endif /* ALLOW_OBCS */
629 adcroft 1.3
630 jmc 1.30 C end if/else update overlap-Only
631     ENDIF
632    
633 adcroft 1.3 C-- End of Y direction
634     ENDIF
635    
636 jmc 1.18 C-- End of ipass loop
637 adcroft 1.1 ENDDO
638    
639 jmc 1.18 IF ( implicitAdvection ) THEN
640     C- explicit advection is done ; store tendency in gTracer:
641     DO j=1-Oly,sNy+Oly
642     DO i=1-Olx,sNx+Olx
643     gTracer(i,j,k,bi,bj)=
644 jmc 1.32 & (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
645 jmc 1.18 ENDDO
646     ENDDO
647     ELSE
648     C- horizontal advection done; store intermediate result in 3D array:
649     DO j=1-Oly,sNy+Oly
650     DO i=1-Olx,sNx+Olx
651     localTijk(i,j,k)=localTij(i,j)
652     ENDDO
653     ENDDO
654     ENDIF
655 adcroft 1.1
656 jmc 1.33 #ifdef ALLOW_DIAGNOSTICS
657     IF ( useDiagnostics ) THEN
658     diagName = 'ADVx'//diagSufx
659 jmc 1.34 CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid)
660 jmc 1.33 diagName = 'ADVy'//diagSufx
661 jmc 1.34 CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid)
662 jmc 1.33 ENDIF
663     #endif
664    
665 jmc 1.29 #ifdef ALLOW_DEBUG
666     IF ( debugLevel .GE. debLevB
667 jmc 1.30 & .AND. tracerIdentity.EQ.GAD_TEMPERATURE
668     & .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
669 jmc 1.29 & .AND. nPx.EQ.1 .AND. nPy.EQ.1
670     & .AND. useCubedSphereExchange ) THEN
671     CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_ADVECTION',
672     & afx,afy, k, standardMessageUnit,bi,bj,myThid )
673     ENDIF
674     #endif /* ALLOW_DEBUG */
675    
676 adcroft 1.1 C-- End of K loop for horizontal fluxes
677     ENDDO
678    
679 jmc 1.29 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
680    
681 jmc 1.18 IF ( .NOT.implicitAdvection ) THEN
682 adcroft 1.1 C-- Start of k loop for vertical flux
683 jmc 1.18 DO k=Nr,1,-1
684 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
685 heimbach 1.16 kkey = (igadkey-1)*Nr + k
686 heimbach 1.6 #endif /* ALLOW_AUTODIFF_TAMC */
687 adcroft 1.1 C-- kup Cycles through 1,2 to point to w-layer above
688     C-- kDown Cycles through 2,1 to point to w-layer below
689 jmc 1.18 kup = 1+MOD(k+1,2)
690     kDown= 1+MOD(k,2)
691     c kp1=min(Nr,k+1)
692     kp1Msk=1.
693     if (k.EQ.Nr) kp1Msk=0.
694 heimbach 1.6
695 jmc 1.11 C-- Compute Vertical transport
696 jmc 1.22 #ifdef ALLOW_AIM
697     C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
698     IF ( k.EQ.1 .OR.
699     & (useAIM .AND. tracerIdentity.EQ.GAD_SALINITY .AND. k.EQ.Nr)
700     & ) THEN
701     #else
702     IF ( k.EQ.1 ) THEN
703     #endif
704 jmc 1.11
705     C- Surface interface :
706 jmc 1.18 DO j=1-Oly,sNy+Oly
707     DO i=1-Olx,sNx+Olx
708 jmc 1.22 rTransKp1(i,j) = kp1Msk*rTrans(i,j)
709 jmc 1.18 rTrans(i,j) = 0.
710     fVerT(i,j,kUp) = 0.
711     ENDDO
712     ENDDO
713 jmc 1.11
714 jmc 1.18 ELSE
715     C- Interior interface :
716 jmc 1.11
717 jmc 1.18 DO j=1-Oly,sNy+Oly
718     DO i=1-Olx,sNx+Olx
719     rTransKp1(i,j) = kp1Msk*rTrans(i,j)
720     rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
721     & *maskC(i,j,k-1,bi,bj)
722 jmc 1.29 fVerT(i,j,kUp) = 0.
723 jmc 1.18 ENDDO
724     ENDDO
725 jmc 1.11
726     #ifdef ALLOW_GMREDI
727     C-- Residual transp = Bolus transp + Eulerian transp
728 jmc 1.18 IF (useGMRedi)
729 jmc 1.11 & CALL GMREDI_CALC_WFLOW(
730     & rTrans, bi, bj, k, myThid)
731     #endif /* ALLOW_GMREDI */
732    
733 heimbach 1.16 #ifdef ALLOW_AUTODIFF_TAMC
734     CADJ STORE localTijk(:,:,k)
735     CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
736     CADJ STORE rTrans(:,:)
737     CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
738     #endif /* ALLOW_AUTODIFF_TAMC */
739    
740 adcroft 1.1 C- Compute vertical advective flux in the interior:
741 jmc 1.37 IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
742     & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
743     CALL GAD_DST2U1_ADV_R( bi,bj,k, advectionScheme,
744     I dTtracerLev(k),rTrans,wVel,localTijk,
745     O fVerT(1-Olx,1-Oly,kUp), myThid )
746     ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
747 jmc 1.32 CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),
748 jmc 1.29 I rTrans, wVel, localTijk,
749     O fVerT(1-Olx,1-Oly,kUp), myThid )
750 jmc 1.23 ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN
751 jmc 1.32 CALL GAD_DST3_ADV_R( bi,bj,k, dTtracerLev(k),
752 jmc 1.29 I rTrans, wVel, localTijk,
753     O fVerT(1-Olx,1-Oly,kUp), myThid )
754 jmc 1.23 ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
755 jmc 1.32 CALL GAD_DST3FL_ADV_R( bi,bj,k, dTtracerLev(k),
756 jmc 1.29 I rTrans, wVel, localTijk,
757     O fVerT(1-Olx,1-Oly,kUp), myThid )
758 jmc 1.18 ELSE
759     STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
760     ENDIF
761 jmc 1.11
762     C- end Surface/Interior if bloc
763 jmc 1.18 ENDIF
764 heimbach 1.16
765     #ifdef ALLOW_AUTODIFF_TAMC
766     CADJ STORE rTrans(:,:)
767     CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
768     CADJ STORE rTranskp1(:,:)
769     CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
770     #endif /* ALLOW_AUTODIFF_TAMC */
771 adcroft 1.1
772 jmc 1.18 C-- Divergence of vertical fluxes
773     DO j=1-Oly,sNy+Oly
774     DO i=1-Olx,sNx+Olx
775 jmc 1.32 localTij(i,j)=localTijk(i,j,k)-dTtracerLev(k)*
776 jmc 1.18 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
777     & *recip_rA(i,j,bi,bj)
778 jmc 1.35 & *( fVerT(i,j,kDown)-fVerT(i,j,kUp)
779     & -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))
780     & )*rkSign
781 jmc 1.18 gTracer(i,j,k,bi,bj)=
782 jmc 1.32 & (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
783 jmc 1.18 ENDDO
784     ENDDO
785 adcroft 1.1
786 jmc 1.33 #ifdef ALLOW_DIAGNOSTICS
787     IF ( useDiagnostics ) THEN
788     diagName = 'ADVr'//diagSufx
789     CALL DIAGNOSTICS_FILL( fVerT(1-Olx,1-Oly,kUp),
790 jmc 1.34 & diagName, k,1, 2,bi,bj, myThid)
791 jmc 1.33 ENDIF
792     #endif
793    
794 adcroft 1.1 C-- End of K loop for vertical flux
795 jmc 1.18 ENDDO
796     C-- end of if not.implicitAdvection block
797     ENDIF
798 adcroft 1.1
799     RETURN
800     END

  ViewVC Help
Powered by ViewVC 1.1.22