/[MITgcm]/MITgcm/pkg/seaice/seaice_advection.F
ViewVC logotype

Annotation of /MITgcm/pkg/seaice/seaice_advection.F

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


Revision 1.1 - (hide annotations) (download)
Thu Feb 16 10:41:48 2006 UTC (18 years, 2 months ago) by mlosch
Branch: MAIN
 add a few new advection schemes to seaice:
 ENUM_UPWIND_1RST, ENUM_DST2, ENUM_FLUX_LIMIT, ENUM_DST3,
 ENUM_DST3_FLUX_LIMIT
 Default is still the old one

1 mlosch 1.1 C $Header: $
2     C $Name: $
3    
4     #include "GAD_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7     CBOP
8     C !ROUTINE: SEAICE_ADVECTION
9    
10     C !INTERFACE: ==========================================================
11     SUBROUTINE SEAICE_ADVECTION(
12     I advectionScheme,
13     I tracerIdentity,
14     I uVel, vVel, tracer,
15     O gTracer,
16     I bi, bj, myTime, myIter, myThid)
17    
18     C !DESCRIPTION:
19     C Calculates the tendency of a tracer due to advection.
20     C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}
21     C and can only be used for the non-linear advection schemes such as the
22     C direct-space-time method and flux-limiters.
23     C
24     C This routine is an adaption of the GAD_ADVECTION for 2D-fields.
25     C Seaice velocities are not divergence free; therefore the contribution
26     C tracer*div(u) that is present in gad_advection is removed in this routine.
27     C
28     C The algorithm is as follows:
29     C \begin{itemize}
30     C \item{$\theta^{(n+1/2)} = \theta^{(n)}
31     C - \Delta t \partial_x (u\theta^{(n)}) + \theta^{(n)} \partial_x u$}
32     C \item{$\theta^{(n+2/2)} = \theta^{(n+1/2)}
33     C - \Delta t \partial_y (v\theta^{(n+1/2)}) + \theta^{(n)} \partial_y v$}
34     C \item{$G_\theta = ( \theta^{(n+2/2)} - \theta^{(n)} )/\Delta t$}
35     C \end{itemize}
36     C
37     C The tendency (output) is over-written by this routine.
38    
39     C !USES: ===============================================================
40     IMPLICIT NONE
41     #include "SIZE.h"
42     #include "EEPARAMS.h"
43     #include "PARAMS.h"
44     #include "GRID.h"
45     #include "GAD.h"
46     #include "SEAICE_PARAMS.h"
47     #ifdef ALLOW_AUTODIFF_TAMC
48     # include "tamc.h"
49     # include "tamc_keys.h"
50     #endif
51     #ifdef ALLOW_EXCH2
52     #include "W2_EXCH2_TOPOLOGY.h"
53     #include "W2_EXCH2_PARAMS.h"
54     #endif /* ALLOW_EXCH2 */
55    
56     C !INPUT PARAMETERS: ===================================================
57     C implicitAdvection :: implicit vertical advection (later on)
58     C advectionScheme :: advection scheme to use (Horizontal plane)
59     C tracerIdentity :: tracer identifier (required only for OBCS)
60     C uVel :: velocity, zonal component
61     C vVel :: velocity, meridional component
62     C tracer :: tracer field
63     C bi,bj :: tile indices
64     C myTime :: current time
65     C myIter :: iteration number
66     C myThid :: thread number
67     INTEGER advectionScheme
68     INTEGER tracerIdentity
69     _RL uVel (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
70     _RL vVel (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
71     _RL tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
72     INTEGER bi,bj
73     _RL myTime
74     INTEGER myIter
75     INTEGER myThid
76    
77     C !OUTPUT PARAMETERS: ==================================================
78     C gTracer :: tendancy array
79     _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
80    
81     C !LOCAL VARIABLES: ====================================================
82     C maskLocW :: 2-D array for mask at West points
83     C maskLocS :: 2-D array for mask at South points
84     C iMin,iMax, :: loop range for called routines
85     C jMin,jMax :: loop range for called routines
86     C [iMin,iMax]Upd :: loop range to update tracer field
87     C [jMin,jMax]Upd :: loop range to update tracer field
88     C i,j,k :: loop indices
89     C kp1 :: =k+1 for k<Nr, =Nr for k=Nr
90     C xA,yA :: areas of X and Y face of tracer cells
91     C uTrans,vTrans :: 2-D arrays of volume transports at U,V points
92     C af :: 2-D array for horizontal advective flux
93     C afx :: 2-D array for horizontal advective flux, x direction
94     C afy :: 2-D array for horizontal advective flux, y direction
95     C fVerT :: 2 1/2D arrays for vertical advective flux
96     C localTij :: 2-D array, temporary local copy of tracer fld
97     C localTijk :: 3-D array, temporary local copy of tracer fld
98     C kp1Msk :: flag (0,1) for over-riding mask for W levels
99     C calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
100     C calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
101     C interiorOnly :: only update the interior of myTile, but not the edges
102     C overlapOnly :: only update the edges of myTile, but not the interior
103     C nipass :: number of passes in multi-dimensional method
104     C ipass :: number of the current pass being made
105     C myTile :: variables used to determine which cube face
106     C nCFace :: owns a tile for cube grid runs using
107     C :: multi-dim advection.
108     C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
109     _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
110     _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
111     INTEGER iMin,iMax,jMin,jMax
112     INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd
113     INTEGER i,j,k
114     _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
115     _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
116     _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
117     _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
118     _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
119     _RL afx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120     _RL afy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121     _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
122     _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
123     LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns
124     LOGICAL interiorOnly, overlapOnly
125     INTEGER nipass,ipass
126     INTEGER nCFace
127     LOGICAL N_edge, S_edge, E_edge, W_edge
128     #ifdef ALLOW_EXCH2
129     INTEGER myTile
130     #endif
131     #ifdef ALLOW_DIAGNOSTICS
132     CHARACTER*8 diagName
133     CHARACTER*4 GAD_DIAG_SUFX, diagSufx
134     EXTERNAL GAD_DIAG_SUFX
135     #endif
136     CEOP
137    
138     #ifdef ALLOW_AUTODIFF_TAMC
139     act0 = tracerIdentity - 1
140     max0 = maxpass
141     act1 = bi - myBxLo(myThid)
142     max1 = myBxHi(myThid) - myBxLo(myThid) + 1
143     act2 = bj - myByLo(myThid)
144     max2 = myByHi(myThid) - myByLo(myThid) + 1
145     act3 = myThid - 1
146     max3 = nTx*nTy
147     act4 = ikey_dynamics - 1
148     igadkey = (act0 + 1)
149     & + act1*max0
150     & + act2*max0*max1
151     & + act3*max0*max1*max2
152     & + act4*max0*max1*max2*max3
153     if (tracerIdentity.GT.maxpass) then
154     print *, 'ph-pass gad_advection ', maxpass, tracerIdentity
155     STOP 'maxpass seems smaller than tracerIdentity'
156     endif
157     #endif /* ALLOW_AUTODIFF_TAMC */
158    
159     CML#ifdef ALLOW_DIAGNOSTICS
160     CMLC-- Set diagnostic suffix for the current tracer
161     CML IF ( useDiagnostics ) THEN
162     CML diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
163     CML ENDIF
164     CML#endif
165    
166     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     fVerT(i,j,1) = 0. _d 0
178     fVerT(i,j,2) = 0. _d 0
179     #ifdef ALLOW_AUTODIFF_TAMC
180     localTij(i,j) = 0. _d 0
181     #endif
182     ENDDO
183     ENDDO
184    
185     C-- Set tile-specific parameters for horizontal fluxes
186     IF (useCubedSphereExchange) THEN
187     nipass=3
188     #ifdef ALLOW_AUTODIFF_TAMC
189     IF ( nipass.GT.maxcube ) STOP 'maxcube needs to be = 3'
190     #endif
191     #ifdef ALLOW_EXCH2
192     myTile = W2_myTileList(bi)
193     nCFace = exch2_myFace(myTile)
194     N_edge = exch2_isNedge(myTile).EQ.1
195     S_edge = exch2_isSedge(myTile).EQ.1
196     E_edge = exch2_isEedge(myTile).EQ.1
197     W_edge = exch2_isWedge(myTile).EQ.1
198     #else
199     nCFace = bi
200     N_edge = .TRUE.
201     S_edge = .TRUE.
202     E_edge = .TRUE.
203     W_edge = .TRUE.
204     #endif
205     ELSE
206     nipass=2
207     nCFace = bi
208     N_edge = .FALSE.
209     S_edge = .FALSE.
210     E_edge = .FALSE.
211     W_edge = .FALSE.
212     ENDIF
213    
214     iMin = 1-OLx
215     iMax = sNx+OLx
216     jMin = 1-OLy
217     jMax = sNy+OLy
218    
219     C-- Start of k loop for horizontal fluxes
220     k = 1
221     #ifdef ALLOW_AUTODIFF_TAMC
222     kkey = (igadkey-1)*Nr + k
223     CADJ STORE tracer(:,:,bi,bj) =
224     CADJ & comlev1_bibj_k_gad, key=kkey, byte=isbyte
225     #endif /* ALLOW_AUTODIFF_TAMC */
226    
227     C Content of CALC_COMMON_FACTORS, adapted for 2D fields
228     C-- Get temporary terms used by tendency routines
229    
230     C-- Calculate tracer cell face open areas
231     DO j=jMin,jMax
232     DO i=iMin,iMax
233     xA(i,j) = _dyG(i,j,bi,bj) * maskW(i,j,k,bi,bj)
234     yA(i,j) = _dxG(i,j,bi,bj) * maskS(i,j,k,bi,bj)
235     ENDDO
236     ENDDO
237    
238     C-- Calculate velocity field "volume transports" through
239     C-- tracer cell faces.
240     DO j=jMin,jMax
241     DO i=iMin,iMax
242     uTrans(i,j) = uVel(i,j,bi,bj)*xA(i,j)
243     vTrans(i,j) = vVel(i,j,bi,bj)*yA(i,j)
244     ENDDO
245     ENDDO
246     C end of CALC_COMMON_FACTORS, adapted for 2D fields
247    
248     C-- Make local copy of tracer array and mask West & South
249     DO j=1-OLy,sNy+OLy
250     DO i=1-OLx,sNx+OLx
251     localTij(i,j)=tracer(i,j,bi,bj)
252     maskLocW(i,j)=maskW(i,j,k,bi,bj)
253     maskLocS(i,j)=maskS(i,j,k,bi,bj)
254     ENDDO
255     ENDDO
256    
257     #ifndef ALLOW_AUTODIFF_TAMC
258     IF (useCubedSphereExchange) THEN
259     withSigns = .FALSE.
260     CALL FILL_CS_CORNER_UV_RS(
261     & withSigns, maskLocW,maskLocS, bi,bj, myThid )
262     ENDIF
263     #endif
264    
265     C-- Multiple passes for different directions on different tiles
266     C-- For cube need one pass for each of red, green and blue axes.
267     DO ipass=1,nipass
268     #ifdef ALLOW_AUTODIFF_TAMC
269     passkey = ipass + (k-1) *maxcube
270     & + (igadkey-1)*maxcube*Nr
271     IF (nipass .GT. maxpass) THEN
272     STOP 'SEAICE_ADVECTION: nipass > maxcube. check tamc.h'
273     ENDIF
274     #endif /* ALLOW_AUTODIFF_TAMC */
275    
276     interiorOnly = .FALSE.
277     overlapOnly = .FALSE.
278     IF (useCubedSphereExchange) THEN
279     C-- CubedSphere : pass 3 times, with partial update of local tracer field
280     IF (ipass.EQ.1) THEN
281     overlapOnly = MOD(nCFace,3).EQ.0
282     interiorOnly = MOD(nCFace,3).NE.0
283     calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
284     calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
285     ELSEIF (ipass.EQ.2) THEN
286     overlapOnly = MOD(nCFace,3).EQ.2
287     calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
288     calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
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     ENDIF
293     ELSE
294     C-- not CubedSphere
295     calc_fluxes_X = MOD(ipass,2).EQ.1
296     calc_fluxes_Y = .NOT.calc_fluxes_X
297     ENDIF
298    
299     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
300     C-- X direction
301     C- Advective flux in X
302     DO j=1-Oly,sNy+Oly
303     DO i=1-Olx,sNx+Olx
304     af(i,j) = 0.
305     ENDDO
306     ENDDO
307     C
308     #ifdef ALLOW_AUTODIFF_TAMC
309     cph-test
310     CADJ STORE localTij(:,:) =
311     CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
312     CADJ STORE af(:,:) =
313     CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
314     #endif /* ALLOW_AUTODIFF_TAMC */
315     C
316     IF (calc_fluxes_X) THEN
317    
318     C- Do not compute fluxes if
319     C a) needed in overlap only
320     C and b) the overlap of myTile are not cube-face Edges
321     IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
322    
323     #ifndef ALLOW_AUTODIFF_TAMC
324     C- Internal exchange for calculations in X
325     #ifdef MULTIDIM_OLD_VERSION
326     IF ( useCubedSphereExchange ) THEN
327     #else
328     IF ( useCubedSphereExchange .AND.
329     & ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
330     #endif
331     CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
332     ENDIF
333     #endif
334    
335     #ifdef ALLOW_AUTODIFF_TAMC
336     # ifndef DISABLE_MULTIDIM_ADVECTION
337     CADJ STORE localTij(:,:) =
338     CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
339     # endif
340     #endif /* ALLOW_AUTODIFF_TAMC */
341    
342     IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
343     & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
344     CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme,
345     I SEAICE_deltaTtherm,uTrans,uVel,localTij,
346     O af, myThid )
347     ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
348     CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, SEAICE_deltaTtherm,
349     I uTrans, uVel, maskLocW, localTij,
350     O af, myThid )
351     ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
352     CALL GAD_DST3_ADV_X( bi,bj,k, SEAICE_deltaTtherm,
353     I uTrans, uVel, maskLocW, localTij,
354     O af, myThid )
355     ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
356     CALL GAD_DST3FL_ADV_X( bi,bj,k, SEAICE_deltaTtherm,
357     I uTrans, uVel, maskLocW, localTij,
358     O af, myThid )
359     ELSE
360     STOP
361     & 'SEAICE_ADVECTION: adv. scheme incompatibale with multi-dim'
362     ENDIF
363    
364     C-- Advective flux in X : done
365     ENDIF
366    
367     #ifndef ALLOW_AUTODIFF_TAMC
368     C-- Internal exchange for next calculations in Y
369     IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
370     CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
371     ENDIF
372     #endif
373    
374     C- Update the local tracer field where needed:
375    
376     C update in overlap-Only
377     IF ( overlapOnly ) THEN
378     iMinUpd = 1-Olx+1
379     iMaxUpd = sNx+Olx-1
380     C-- notes: these 2 lines below have no real effect (because recip_hFac=0
381     C in corner region) but safer to keep them.
382     IF ( W_edge ) iMinUpd = 1
383     IF ( E_edge ) iMaxUpd = sNx
384    
385     IF ( S_edge ) THEN
386     DO j=1-Oly,0
387     DO i=iMinUpd,iMaxUpd
388     localTij(i,j)=localTij(i,j)-SEAICE_deltaTtherm*
389     & maskC(i,j,k,bi,bj)
390     & *recip_rA(i,j,bi,bj)
391     & *( af(i+1,j)-af(i,j)
392     & )
393     ENDDO
394     ENDDO
395     ENDIF
396     IF ( N_edge ) THEN
397     DO j=sNy+1,sNy+Oly
398     DO i=iMinUpd,iMaxUpd
399     localTij(i,j)=localTij(i,j)-SEAICE_deltaTtherm*
400     & maskC(i,j,k,bi,bj)
401     & *recip_rA(i,j,bi,bj)
402     & *( af(i+1,j)-af(i,j)
403     & )
404     ENDDO
405     ENDDO
406     ENDIF
407    
408     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     localTij(i,j)=localTij(i,j)-SEAICE_deltaTtherm*
417     & maskC(i,j,k,bi,bj)
418     & *recip_rA(i,j,bi,bj)
419     & *( af(i+1,j)-af(i,j)
420     & )
421     ENDDO
422     ENDDO
423     C-- keep advective flux (for diagnostics)
424     DO j=1-Oly,sNy+Oly
425     DO i=1-Olx,sNx+Olx
426     afx(i,j) = af(i,j)
427     ENDDO
428     ENDDO
429    
430     C This is for later
431     CML#ifdef ALLOW_OBCS
432     CMLC- Apply open boundary conditions
433     CML IF ( useOBCS ) THEN
434     CML IF (tracerIdentity.EQ.GAD_HEFF) THEN
435     CML CALL OBCS_APPLY_HEFF( bi, bj, k, localTij, myThid )
436     CML ELSEIF (tracerIdentity.EQ.GAD_AREA) THEN
437     CML CALL OBCS_APPLY_AREA( bi, bj, k, localTij, myThid )
438     CML ENDIF
439     CML ENDIF
440     CML#endif /* ALLOW_OBCS */
441    
442     C- end if/else update overlap-Only
443     ENDIF
444    
445     C-- End of X direction
446     ENDIF
447    
448     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
449     C-- Y direction
450     cph-test
451     C- Advective flux in Y
452     DO j=1-Oly,sNy+Oly
453     DO i=1-Olx,sNx+Olx
454     af(i,j) = 0.
455     ENDDO
456     ENDDO
457     C
458     #ifdef ALLOW_AUTODIFF_TAMC
459     cph-test
460     CADJ STORE localTij(:,:) =
461     CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
462     CADJ STORE af(:,:) =
463     CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
464     #endif /* ALLOW_AUTODIFF_TAMC */
465     C
466     IF (calc_fluxes_Y) THEN
467    
468     C- Do not compute fluxes if
469     C a) needed in overlap only
470     C and b) the overlap of myTile are not cube-face edges
471     IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
472    
473     #ifndef ALLOW_AUTODIFF_TAMC
474     C- Internal exchange for calculations in Y
475     #ifdef MULTIDIM_OLD_VERSION
476     IF ( useCubedSphereExchange ) THEN
477     #else
478     IF ( useCubedSphereExchange .AND.
479     & ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
480     #endif
481     CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
482     ENDIF
483     #endif
484    
485     C- Advective flux in Y
486     DO j=1-Oly,sNy+Oly
487     DO i=1-Olx,sNx+Olx
488     af(i,j) = 0.
489     ENDDO
490     ENDDO
491    
492     #ifdef ALLOW_AUTODIFF_TAMC
493     #ifndef DISABLE_MULTIDIM_ADVECTION
494     CADJ STORE localTij(:,:) =
495     CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
496     #endif
497     #endif /* ALLOW_AUTODIFF_TAMC */
498    
499     IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
500     & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
501     CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme,
502     I SEAICE_deltaTtherm,vTrans,vVel,localTij,
503     O af, myThid )
504     ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
505     CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, SEAICE_deltaTtherm,
506     I vTrans, vVel, maskLocS, localTij,
507     O af, myThid )
508     ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
509     CALL GAD_DST3_ADV_Y( bi,bj,k, SEAICE_deltaTtherm,
510     I vTrans, vVel, maskLocS, localTij,
511     O af, myThid )
512     ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
513     CALL GAD_DST3FL_ADV_Y( bi,bj,k, SEAICE_deltaTtherm,
514     I vTrans, vVel, maskLocS, localTij,
515     O af, myThid )
516     ELSE
517     STOP
518     & 'SEAICE_ADVECTION: adv. scheme incompatibale with mutli-dim'
519     ENDIF
520    
521     C- Advective flux in Y : done
522     ENDIF
523    
524     #ifndef ALLOW_AUTODIFF_TAMC
525     C- Internal exchange for next calculations in X
526     IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
527     CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
528     ENDIF
529     #endif
530    
531     C- Update the local tracer field where needed:
532    
533     C update in overlap-Only
534     IF ( overlapOnly ) THEN
535     jMinUpd = 1-Oly+1
536     jMaxUpd = sNy+Oly-1
537     C- notes: these 2 lines below have no real effect (because recip_hFac=0
538     C in corner region) but safer to keep them.
539     IF ( S_edge ) jMinUpd = 1
540     IF ( N_edge ) jMaxUpd = sNy
541    
542     IF ( W_edge ) THEN
543     DO j=jMinUpd,jMaxUpd
544     DO i=1-Olx,0
545     localTij(i,j)=localTij(i,j)-SEAICE_deltaTtherm*
546     & maskC(i,j,k,bi,bj)
547     & *recip_rA(i,j,bi,bj)
548     & *( af(i,j+1)-af(i,j)
549     & )
550     ENDDO
551     ENDDO
552     ENDIF
553     IF ( E_edge ) THEN
554     DO j=jMinUpd,jMaxUpd
555     DO i=sNx+1,sNx+Olx
556     localTij(i,j)=localTij(i,j)-SEAICE_deltaTtherm*
557     & maskC(i,j,k,bi,bj)
558     & *recip_rA(i,j,bi,bj)
559     & *( af(i,j+1)-af(i,j)
560     & )
561     ENDDO
562     ENDDO
563     ENDIF
564    
565     ELSE
566     C do not only update the overlap
567     iMinUpd = 1-Olx
568     iMaxUpd = sNx+Olx
569     IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
570     IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
571     DO j=1-Oly+1,sNy+Oly-1
572     DO i=iMinUpd,iMaxUpd
573     localTij(i,j)=localTij(i,j)-SEAICE_deltaTtherm*
574     & maskC(i,j,k,bi,bj)
575     & *recip_rA(i,j,bi,bj)
576     & *( af(i,j+1)-af(i,j)
577     & )
578     ENDDO
579     ENDDO
580     C-- keep advective flux (for diagnostics)
581     DO j=1-Oly,sNy+Oly
582     DO i=1-Olx,sNx+Olx
583     afy(i,j) = af(i,j)
584     ENDDO
585     ENDDO
586    
587     C-- Save this for later
588     CML#ifdef ALLOW_OBCS
589     CMLC- Apply open boundary conditions
590     CML IF (useOBCS) THEN
591     CML IF (tracerIdentity.EQ.GAD_HEFF) THEN
592     CML CALL OBCS_APPLY_HEFF( bi, bj, k, localTij, myThid )
593     CML ELSEIF (tracerIdentity.EQ.GAD_AREA) THEN
594     CML CALL OBCS_APPLY_AREA( bi, bj, k, localTij, myThid )
595     CML ENDIF
596     CML ENDIF
597     CML#endif /* ALLOW_OBCS */
598    
599     C end if/else update overlap-Only
600     ENDIF
601    
602     C-- End of Y direction
603     ENDIF
604    
605     C-- End of ipass loop
606     ENDDO
607    
608     C- explicit advection is done ; store tendency in gTracer:
609     DO j=1-Oly,sNy+Oly
610     DO i=1-Olx,sNx+Olx
611     gTracer(i,j,bi,bj)=
612     & (localTij(i,j)-tracer(i,j,bi,bj))/SEAICE_deltaTtherm
613     ENDDO
614     ENDDO
615    
616     CML#ifdef ALLOW_DIAGNOSTICS
617     CML IF ( useDiagnostics ) THEN
618     CML diagName = 'ADVx'//diagSufx
619     CML CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid)
620     CML diagName = 'ADVy'//diagSufx
621     CML CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid)
622     CML ENDIF
623     CML#endif
624    
625     #ifdef ALLOW_DEBUG
626     IF ( debugLevel .GE. debLevB
627     & .AND. tracerIdentity.EQ.GAD_HEFF
628     & .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
629     & .AND. nPx.EQ.1 .AND. nPy.EQ.1
630     & .AND. useCubedSphereExchange ) THEN
631     CALL DEBUG_CS_CORNER_UV( ' afx,afy from SEAICE_ADVECTION',
632     & afx,afy, k, standardMessageUnit,bi,bj,myThid )
633     ENDIF
634     #endif /* ALLOW_DEBUG */
635    
636     RETURN
637     END

  ViewVC Help
Powered by ViewVC 1.1.22