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

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

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


Revision 1.3 - (show annotations) (download)
Mon Jun 19 15:48:35 2006 UTC (17 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58n_post, checkpoint58q_post, checkpoint58o_post, checkpoint58k_post, checkpoint58p_post, checkpoint58m_post
Changes since 1.2: +13 -9 lines
use a local copy of ice velocity for DST advection schemes

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_advection.F,v 1.2 2006/02/21 17:20:12 heimbach Exp $
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 uFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
117 _RL vFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
118 _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
119 _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120 _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121 _RL afx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122 _RL afy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
123 _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
124 _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
125 LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns
126 LOGICAL interiorOnly, overlapOnly
127 INTEGER nipass,ipass
128 INTEGER nCFace
129 LOGICAL N_edge, S_edge, E_edge, W_edge
130 #ifdef ALLOW_EXCH2
131 INTEGER myTile
132 #endif
133 #ifdef ALLOW_DIAGNOSTICS
134 CHARACTER*8 diagName
135 CHARACTER*4 GAD_DIAG_SUFX, diagSufx
136 EXTERNAL GAD_DIAG_SUFX
137 #endif
138 CEOP
139
140 #ifdef ALLOW_AUTODIFF_TAMC
141 act0 = tracerIdentity - 1
142 max0 = maxpass
143 act1 = bi - myBxLo(myThid)
144 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
145 act2 = bj - myByLo(myThid)
146 max2 = myByHi(myThid) - myByLo(myThid) + 1
147 act3 = myThid - 1
148 max3 = nTx*nTy
149 act4 = ikey_dynamics - 1
150 igadkey = (act0 + 1)
151 & + act1*max0
152 & + act2*max0*max1
153 & + act3*max0*max1*max2
154 & + act4*max0*max1*max2*max3
155 if (tracerIdentity.GT.maxpass) then
156 print *, 'ph-pass gad_advection ', maxpass, tracerIdentity
157 STOP 'maxpass seems smaller than tracerIdentity'
158 endif
159 #endif /* ALLOW_AUTODIFF_TAMC */
160
161 CML#ifdef ALLOW_DIAGNOSTICS
162 CMLC-- Set diagnostic suffix for the current tracer
163 CML IF ( useDiagnostics ) THEN
164 CML diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
165 CML ENDIF
166 CML#endif
167
168 C-- Set up work arrays with valid (i.e. not NaN) values
169 C These inital values do not alter the numerical results. They
170 C just ensure that all memory references are to valid floating
171 C point numbers. This prevents spurious hardware signals due to
172 C uninitialised but inert locations.
173 DO j=1-OLy,sNy+OLy
174 DO i=1-OLx,sNx+OLx
175 xA(i,j) = 0. _d 0
176 yA(i,j) = 0. _d 0
177 uTrans(i,j) = 0. _d 0
178 vTrans(i,j) = 0. _d 0
179 fVerT(i,j,1) = 0. _d 0
180 fVerT(i,j,2) = 0. _d 0
181 #ifdef ALLOW_AUTODIFF_TAMC
182 localTij(i,j) = 0. _d 0
183 #endif
184 ENDDO
185 ENDDO
186
187 C-- Set tile-specific parameters for horizontal fluxes
188 IF (useCubedSphereExchange) THEN
189 nipass=3
190 #ifdef ALLOW_AUTODIFF_TAMC
191 IF ( nipass.GT.maxcube ) STOP 'maxcube needs to be = 3'
192 #endif
193 #ifdef ALLOW_EXCH2
194 myTile = W2_myTileList(bi)
195 nCFace = exch2_myFace(myTile)
196 N_edge = exch2_isNedge(myTile).EQ.1
197 S_edge = exch2_isSedge(myTile).EQ.1
198 E_edge = exch2_isEedge(myTile).EQ.1
199 W_edge = exch2_isWedge(myTile).EQ.1
200 #else
201 nCFace = bi
202 N_edge = .TRUE.
203 S_edge = .TRUE.
204 E_edge = .TRUE.
205 W_edge = .TRUE.
206 #endif
207 ELSE
208 nipass=2
209 nCFace = bi
210 N_edge = .FALSE.
211 S_edge = .FALSE.
212 E_edge = .FALSE.
213 W_edge = .FALSE.
214 ENDIF
215
216 iMin = 1-OLx
217 iMax = sNx+OLx
218 jMin = 1-OLy
219 jMax = sNy+OLy
220
221 C-- Start of k loop for horizontal fluxes
222 k = 1
223 #ifdef ALLOW_AUTODIFF_TAMC
224 kkey = (igadkey-1)*Nr + k
225 CADJ STORE tracer(:,:,bi,bj) =
226 CADJ & comlev1_bibj_k_gad, key=kkey, byte=isbyte
227 #endif /* ALLOW_AUTODIFF_TAMC */
228
229 C Content of CALC_COMMON_FACTORS, adapted for 2D fields
230 C-- Get temporary terms used by tendency routines
231
232 C-- Calculate tracer cell face open areas
233 DO j=jMin,jMax
234 DO i=iMin,iMax
235 xA(i,j) = _dyG(i,j,bi,bj) * maskW(i,j,k,bi,bj)
236 yA(i,j) = _dxG(i,j,bi,bj) * maskS(i,j,k,bi,bj)
237 ENDDO
238 ENDDO
239
240 C-- Calculate velocity field "volume transports" through
241 C-- tracer cell faces.
242 DO j=jMin,jMax
243 DO i=iMin,iMax
244 uFld(i,j) = uVel(i,j,bi,bj)
245 vFld(i,j) = vVel(i,j,bi,bj)
246 uTrans(i,j) = uVel(i,j,bi,bj)*xA(i,j)
247 vTrans(i,j) = vVel(i,j,bi,bj)*yA(i,j)
248 ENDDO
249 ENDDO
250 C end of CALC_COMMON_FACTORS, adapted for 2D fields
251
252 C-- Make local copy of tracer array and mask West & South
253 DO j=1-OLy,sNy+OLy
254 DO i=1-OLx,sNx+OLx
255 localTij(i,j)=tracer(i,j,bi,bj)
256 maskLocW(i,j)=maskW(i,j,k,bi,bj)
257 maskLocS(i,j)=maskS(i,j,k,bi,bj)
258 ENDDO
259 ENDDO
260
261 #ifndef ALLOW_AUTODIFF_TAMC
262 IF (useCubedSphereExchange) THEN
263 withSigns = .FALSE.
264 CALL FILL_CS_CORNER_UV_RS(
265 & withSigns, maskLocW,maskLocS, bi,bj, myThid )
266 ENDIF
267 #endif
268
269 C-- Multiple passes for different directions on different tiles
270 C-- For cube need one pass for each of red, green and blue axes.
271 DO ipass=1,nipass
272 #ifdef ALLOW_AUTODIFF_TAMC
273 passkey = ipass + (k-1) *maxcube
274 & + (igadkey-1)*maxcube*Nr
275 IF (nipass .GT. maxpass) THEN
276 STOP 'SEAICE_ADVECTION: nipass > maxcube. check tamc.h'
277 ENDIF
278 #endif /* ALLOW_AUTODIFF_TAMC */
279
280 interiorOnly = .FALSE.
281 overlapOnly = .FALSE.
282 IF (useCubedSphereExchange) THEN
283 C-- CubedSphere : pass 3 times, with partial update of local tracer field
284 IF (ipass.EQ.1) THEN
285 overlapOnly = MOD(nCFace,3).EQ.0
286 interiorOnly = MOD(nCFace,3).NE.0
287 calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
288 calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
289 ELSEIF (ipass.EQ.2) THEN
290 overlapOnly = MOD(nCFace,3).EQ.2
291 calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
292 calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
293 ELSE
294 calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
295 calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
296 ENDIF
297 ELSE
298 C-- not CubedSphere
299 calc_fluxes_X = MOD(ipass,2).EQ.1
300 calc_fluxes_Y = .NOT.calc_fluxes_X
301 ENDIF
302
303 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
304 C-- X direction
305 C- Advective flux in X
306 DO j=1-Oly,sNy+Oly
307 DO i=1-Olx,sNx+Olx
308 af(i,j) = 0.
309 ENDDO
310 ENDDO
311 C
312 #ifdef ALLOW_AUTODIFF_TAMC
313 CADJ STORE localTij(:,:) =
314 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
315 # ifndef DISABLE_MULTIDIM_ADVECTION
316 CADJ STORE af(:,:) =
317 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
318 # endif
319 #endif /* ALLOW_AUTODIFF_TAMC */
320 C
321 IF (calc_fluxes_X) THEN
322
323 C- Do not compute fluxes if
324 C a) needed in overlap only
325 C and b) the overlap of myTile are not cube-face Edges
326 IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
327
328 #ifndef ALLOW_AUTODIFF_TAMC
329 C- Internal exchange for calculations in X
330 #ifdef MULTIDIM_OLD_VERSION
331 IF ( useCubedSphereExchange ) THEN
332 #else
333 IF ( useCubedSphereExchange .AND.
334 & ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
335 #endif
336 CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
337 ENDIF
338 #endif
339
340 #ifdef ALLOW_AUTODIFF_TAMC
341 # ifndef DISABLE_MULTIDIM_ADVECTION
342 CADJ STORE localTij(:,:) =
343 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
344 # endif
345 #endif /* ALLOW_AUTODIFF_TAMC */
346
347 IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
348 & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
349 CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme,
350 I SEAICE_deltaTtherm,uTrans,uFld,localTij,
351 O af, myThid )
352 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
353 CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, SEAICE_deltaTtherm,
354 I uTrans, uFld, maskLocW, localTij,
355 O af, myThid )
356 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
357 CALL GAD_DST3_ADV_X( bi,bj,k, SEAICE_deltaTtherm,
358 I uTrans, uFld, maskLocW, localTij,
359 O af, myThid )
360 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
361 CALL GAD_DST3FL_ADV_X( bi,bj,k, SEAICE_deltaTtherm,
362 I uTrans, uFld, maskLocW, localTij,
363 O af, myThid )
364 ELSE
365 STOP
366 & 'SEAICE_ADVECTION: adv. scheme incompatibale with multi-dim'
367 ENDIF
368
369 C-- Advective flux in X : done
370 ENDIF
371
372 #ifndef ALLOW_AUTODIFF_TAMC
373 C-- Internal exchange for next calculations in Y
374 IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
375 CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
376 ENDIF
377 #endif
378
379 C- Update the local tracer field where needed:
380
381 C update in overlap-Only
382 IF ( overlapOnly ) THEN
383 iMinUpd = 1-Olx+1
384 iMaxUpd = sNx+Olx-1
385 C-- notes: these 2 lines below have no real effect (because recip_hFac=0
386 C in corner region) but safer to keep them.
387 IF ( W_edge ) iMinUpd = 1
388 IF ( E_edge ) iMaxUpd = sNx
389
390 IF ( S_edge ) THEN
391 DO j=1-Oly,0
392 DO i=iMinUpd,iMaxUpd
393 localTij(i,j)=localTij(i,j)-SEAICE_deltaTtherm*
394 & maskC(i,j,k,bi,bj)
395 & *recip_rA(i,j,bi,bj)
396 & *( af(i+1,j)-af(i,j)
397 & )
398 ENDDO
399 ENDDO
400 ENDIF
401 IF ( N_edge ) THEN
402 DO j=sNy+1,sNy+Oly
403 DO i=iMinUpd,iMaxUpd
404 localTij(i,j)=localTij(i,j)-SEAICE_deltaTtherm*
405 & maskC(i,j,k,bi,bj)
406 & *recip_rA(i,j,bi,bj)
407 & *( af(i+1,j)-af(i,j)
408 & )
409 ENDDO
410 ENDDO
411 ENDIF
412
413 ELSE
414 C do not only update the overlap
415 jMinUpd = 1-Oly
416 jMaxUpd = sNy+Oly
417 IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
418 IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
419 DO j=jMinUpd,jMaxUpd
420 DO i=1-Olx+1,sNx+Olx-1
421 localTij(i,j)=localTij(i,j)-SEAICE_deltaTtherm*
422 & maskC(i,j,k,bi,bj)
423 & *recip_rA(i,j,bi,bj)
424 & *( af(i+1,j)-af(i,j)
425 & )
426 ENDDO
427 ENDDO
428 C-- keep advective flux (for diagnostics)
429 DO j=1-Oly,sNy+Oly
430 DO i=1-Olx,sNx+Olx
431 afx(i,j) = af(i,j)
432 ENDDO
433 ENDDO
434
435 C This is for later
436 CML#ifdef ALLOW_OBCS
437 CMLC- Apply open boundary conditions
438 CML IF ( useOBCS ) THEN
439 CML IF (tracerIdentity.EQ.GAD_HEFF) THEN
440 CML CALL OBCS_APPLY_HEFF( bi, bj, k, localTij, myThid )
441 CML ELSEIF (tracerIdentity.EQ.GAD_AREA) THEN
442 CML CALL OBCS_APPLY_AREA( bi, bj, k, localTij, myThid )
443 CML ENDIF
444 CML ENDIF
445 CML#endif /* ALLOW_OBCS */
446
447 C- end if/else update overlap-Only
448 ENDIF
449
450 C-- End of X direction
451 ENDIF
452
453 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
454 C-- Y direction
455 cph-test
456 C- Advective flux in Y
457 DO j=1-Oly,sNy+Oly
458 DO i=1-Olx,sNx+Olx
459 af(i,j) = 0.
460 ENDDO
461 ENDDO
462 C
463 #ifdef ALLOW_AUTODIFF_TAMC
464 # ifndef DISABLE_MULTIDIM_ADVECTION
465 CADJ STORE localTij(:,:) =
466 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
467 CADJ STORE af(:,:) =
468 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
469 # endif
470 #endif /* ALLOW_AUTODIFF_TAMC */
471 C
472 IF (calc_fluxes_Y) THEN
473
474 C- Do not compute fluxes if
475 C a) needed in overlap only
476 C and b) the overlap of myTile are not cube-face edges
477 IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
478
479 #ifndef ALLOW_AUTODIFF_TAMC
480 C- Internal exchange for calculations in Y
481 #ifdef MULTIDIM_OLD_VERSION
482 IF ( useCubedSphereExchange ) THEN
483 #else
484 IF ( useCubedSphereExchange .AND.
485 & ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
486 #endif
487 CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
488 ENDIF
489 #endif
490
491 C- Advective flux in Y
492 DO j=1-Oly,sNy+Oly
493 DO i=1-Olx,sNx+Olx
494 af(i,j) = 0.
495 ENDDO
496 ENDDO
497
498 #ifdef ALLOW_AUTODIFF_TAMC
499 #ifndef DISABLE_MULTIDIM_ADVECTION
500 CADJ STORE localTij(:,:) =
501 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
502 #endif
503 #endif /* ALLOW_AUTODIFF_TAMC */
504
505 IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
506 & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
507 CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme,
508 I SEAICE_deltaTtherm,vTrans,vFld,localTij,
509 O af, myThid )
510 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
511 CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, SEAICE_deltaTtherm,
512 I vTrans, vFld, maskLocS, localTij,
513 O af, myThid )
514 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
515 CALL GAD_DST3_ADV_Y( bi,bj,k, SEAICE_deltaTtherm,
516 I vTrans, vFld, maskLocS, localTij,
517 O af, myThid )
518 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
519 CALL GAD_DST3FL_ADV_Y( bi,bj,k, SEAICE_deltaTtherm,
520 I vTrans, vFld, maskLocS, localTij,
521 O af, myThid )
522 ELSE
523 STOP
524 & 'SEAICE_ADVECTION: adv. scheme incompatibale with mutli-dim'
525 ENDIF
526
527 C- Advective flux in Y : done
528 ENDIF
529
530 #ifndef ALLOW_AUTODIFF_TAMC
531 C- Internal exchange for next calculations in X
532 IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
533 CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
534 ENDIF
535 #endif
536
537 C- Update the local tracer field where needed:
538
539 C update in overlap-Only
540 IF ( overlapOnly ) THEN
541 jMinUpd = 1-Oly+1
542 jMaxUpd = sNy+Oly-1
543 C- notes: these 2 lines below have no real effect (because recip_hFac=0
544 C in corner region) but safer to keep them.
545 IF ( S_edge ) jMinUpd = 1
546 IF ( N_edge ) jMaxUpd = sNy
547
548 IF ( W_edge ) THEN
549 DO j=jMinUpd,jMaxUpd
550 DO i=1-Olx,0
551 localTij(i,j)=localTij(i,j)-SEAICE_deltaTtherm*
552 & maskC(i,j,k,bi,bj)
553 & *recip_rA(i,j,bi,bj)
554 & *( af(i,j+1)-af(i,j)
555 & )
556 ENDDO
557 ENDDO
558 ENDIF
559 IF ( E_edge ) THEN
560 DO j=jMinUpd,jMaxUpd
561 DO i=sNx+1,sNx+Olx
562 localTij(i,j)=localTij(i,j)-SEAICE_deltaTtherm*
563 & maskC(i,j,k,bi,bj)
564 & *recip_rA(i,j,bi,bj)
565 & *( af(i,j+1)-af(i,j)
566 & )
567 ENDDO
568 ENDDO
569 ENDIF
570
571 ELSE
572 C do not only update the overlap
573 iMinUpd = 1-Olx
574 iMaxUpd = sNx+Olx
575 IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
576 IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
577 DO j=1-Oly+1,sNy+Oly-1
578 DO i=iMinUpd,iMaxUpd
579 localTij(i,j)=localTij(i,j)-SEAICE_deltaTtherm*
580 & maskC(i,j,k,bi,bj)
581 & *recip_rA(i,j,bi,bj)
582 & *( af(i,j+1)-af(i,j)
583 & )
584 ENDDO
585 ENDDO
586 C-- keep advective flux (for diagnostics)
587 DO j=1-Oly,sNy+Oly
588 DO i=1-Olx,sNx+Olx
589 afy(i,j) = af(i,j)
590 ENDDO
591 ENDDO
592
593 C-- Save this for later
594 CML#ifdef ALLOW_OBCS
595 CMLC- Apply open boundary conditions
596 CML IF (useOBCS) THEN
597 CML IF (tracerIdentity.EQ.GAD_HEFF) THEN
598 CML CALL OBCS_APPLY_HEFF( bi, bj, k, localTij, myThid )
599 CML ELSEIF (tracerIdentity.EQ.GAD_AREA) THEN
600 CML CALL OBCS_APPLY_AREA( bi, bj, k, localTij, myThid )
601 CML ENDIF
602 CML ENDIF
603 CML#endif /* ALLOW_OBCS */
604
605 C end if/else update overlap-Only
606 ENDIF
607
608 C-- End of Y direction
609 ENDIF
610
611 C-- End of ipass loop
612 ENDDO
613
614 C- explicit advection is done ; store tendency in gTracer:
615 DO j=1-Oly,sNy+Oly
616 DO i=1-Olx,sNx+Olx
617 gTracer(i,j,bi,bj)=
618 & (localTij(i,j)-tracer(i,j,bi,bj))/SEAICE_deltaTtherm
619 ENDDO
620 ENDDO
621
622 CML#ifdef ALLOW_DIAGNOSTICS
623 CML IF ( useDiagnostics ) THEN
624 CML diagName = 'ADVx'//diagSufx
625 CML CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid)
626 CML diagName = 'ADVy'//diagSufx
627 CML CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid)
628 CML ENDIF
629 CML#endif
630
631 #ifdef ALLOW_DEBUG
632 IF ( debugLevel .GE. debLevB
633 & .AND. tracerIdentity.EQ.GAD_HEFF
634 & .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
635 & .AND. nPx.EQ.1 .AND. nPy.EQ.1
636 & .AND. useCubedSphereExchange ) THEN
637 CALL DEBUG_CS_CORNER_UV( ' afx,afy from SEAICE_ADVECTION',
638 & afx,afy, k, standardMessageUnit,bi,bj,myThid )
639 ENDIF
640 #endif /* ALLOW_DEBUG */
641
642 RETURN
643 END

  ViewVC Help
Powered by ViewVC 1.1.22