/[MITgcm]/MITgcm/pkg/thsice/thsice_advection.F
ViewVC logotype

Contents of /MITgcm/pkg/thsice/thsice_advection.F

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


Revision 1.16 - (show annotations) (download)
Tue Jun 7 22:26:37 2011 UTC (12 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint63, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint62z, HEAD
Changes since 1.15: +3 -3 lines
refine debugLevel criteria when printing messages

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_advection.F,v 1.15 2011/06/02 18:34:34 jmc Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5 #ifdef ALLOW_GENERIC_ADVDIFF
6 # include "GAD_OPTIONS.h"
7 #endif
8
9 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
10 CBOP
11 C !ROUTINE: THSICE_ADVECTION
12
13 C !INTERFACE: ==========================================================
14 SUBROUTINE THSICE_ADVECTION(
15 I tracerIdentity,
16 I advectionScheme,
17 I useGridArea,
18 I uTrans, vTrans, maskOc, deltaTadvect, iceEps,
19 U iceVol, iceFld,
20 O afx, afy,
21 I bi, bj, myTime, myIter, myThid)
22
23 C !DESCRIPTION:
24 C Calculates the tendency of a sea-ice field due to advection.
25 C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}
26 C and can only be used for the non-linear advection schemes such as the
27 C direct-space-time method and flux-limiters.
28 C
29 C This routine is an adaption of the GAD_ADVECTION for 2D-fields.
30 C for Area, effective thickness or other sea-ice field,
31 C the contribution iceFld*div(u) (that is present in gad_advection)
32 C is not included here.
33 C
34 C The algorithm is as follows:
35 C \begin{itemize}
36 C \item{$\theta^{(n+1/2)} = \theta^{(n)}
37 C - \Delta t \partial_x (u\theta^{(n)}) + \theta^{(n)} \partial_x u$}
38 C \item{$\theta^{(n+2/2)} = \theta^{(n+1/2)}
39 C - \Delta t \partial_y (v\theta^{(n+1/2)}) + \theta^{(n)} \partial_y v$}
40 C \item{$G_\theta = ( \theta^{(n+2/2)} - \theta^{(n)} )/\Delta t$}
41 C \end{itemize}
42 C
43 C The tendency (output) is over-written by this routine.
44
45 C !USES: ===============================================================
46 IMPLICIT NONE
47 #include "SIZE.h"
48 #include "EEPARAMS.h"
49 #include "PARAMS.h"
50 #include "GRID.h"
51 #if ( defined ALLOW_DBUG_THSICE || defined ALLOW_AUTODIFF_TAMC )
52 # include "THSICE_SIZE.h"
53 #endif
54 #ifdef ALLOW_GENERIC_ADVDIFF
55 # include "GAD.h"
56 #endif
57 #ifdef ALLOW_EXCH2
58 #include "W2_EXCH2_SIZE.h"
59 #include "W2_EXCH2_TOPOLOGY.h"
60 #endif /* ALLOW_EXCH2 */
61 #ifdef ALLOW_AUTODIFF_TAMC
62 # include "tamc.h"
63 # include "tamc_keys.h"
64 #endif
65
66 C !INPUT PARAMETERS: ===================================================
67 C tracerIdentity :: tracer identifier (required only for OBCS)
68 C advectionScheme :: advection scheme to use (Horizontal plane)
69 C useGridArea :: use grid-cell Area (instead of "iceVol" field)
70 C uTrans,vTrans :: volume transports at U,V points
71 C maskOc :: oceanic mask
72 C iceVol :: sea-ice volume
73 C iceFld :: sea-ice field
74 C deltaTadvect :: time-step used for advection [s]
75 C iceEps :: small volume (to avoid division by zero if iceVol==0)
76 C bi,bj :: tile indices
77 C myTime :: current time in simulation [s]
78 C myIter :: current iteration number
79 C myThid :: my thread Id. number
80 INTEGER tracerIdentity
81 INTEGER advectionScheme
82 LOGICAL useGridArea
83 _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
84 _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
85 _RS maskOc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
86 _RL iceFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87 _RL iceVol(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
88 _RL deltaTadvect, iceEps
89 INTEGER bi,bj
90 _RL myTime
91 INTEGER myIter
92 INTEGER myThid
93
94 C !OUTPUT PARAMETERS: ==================================================
95 C iceVol (Updated):: sea-ice volume
96 C iceFld (Updated):: sea-ice field
97 C afx :: horizontal advective flux, x direction
98 C afy :: horizontal advective flux, y direction
99 _RL afx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
100 _RL afy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
101
102 #ifdef ALLOW_GENERIC_ADVDIFF
103 C !LOCAL VARIABLES: ====================================================
104 C maskLocC :: 2-D array mask at grid-cell center
105 C maskLocW :: 2-D array for mask at West points
106 C maskLocS :: 2-D array for mask at South points
107 C iMin,iMax, :: loop range for called routines
108 C jMin,jMax :: loop range for called routines
109 C [iMin,iMax]Upd :: loop range to update sea-ice field
110 C [jMin,jMax]Upd :: loop range to update sea-ice field
111 C i,j :: loop indices
112 C uCfl :: CFL number, zonal direction
113 C vCfl :: CFL number, meridional direction
114 C af :: 2-D array for horizontal advective flux
115 C calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
116 C calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
117 C interiorOnly :: only update the interior of myTile, but not the edges
118 C overlapOnly :: only update the edges of myTile, but not the interior
119 C nipass :: number of passes in multi-dimensional method
120 C ipass :: number of the current pass being made
121 C myTile :: variables used to determine which cube face
122 C nCFace :: owns a tile for cube grid runs using
123 C :: multi-dim advection.
124 C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
125 _RS maskLocC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
126 _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
127 _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
128 INTEGER iMin,iMax,jMin,jMax
129 INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd
130 INTEGER i,j,k
131 _RL uCfl (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
132 _RL vCfl (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
133 _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
134 _RL tmpVol
135 LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns
136 LOGICAL interiorOnly, overlapOnly
137 INTEGER nipass,ipass
138 INTEGER nCFace
139 LOGICAL N_edge, S_edge, E_edge, W_edge
140 #ifdef ALLOW_EXCH2
141 INTEGER myTile
142 #endif
143 #ifdef ALLOW_DBUG_THSICE
144 LOGICAL dBugFlag
145 INTEGER idb,jdb,biDb
146 _RL tmpFac
147 #endif /* ALLOW_DBUG_THSICE */
148 CEOP
149
150 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
151
152 k = 1
153 #ifdef ALLOW_AUTODIFF_TAMC
154 act1 = bi - myBxLo(myThid)
155 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
156 act2 = bj - myByLo(myThid)
157 max2 = myByHi(myThid) - myByLo(myThid) + 1
158 act3 = myThid - 1
159 max3 = nTx*nTy
160 act4 = ikey_dynamics - 1
161 ticekey = (act1 + 1) + act2*max1
162 & + act3*max1*max2
163 & + act4*max1*max2*max3
164 #endif /* ALLOW_AUTODIFF_TAMC */
165
166 #ifdef ALLOW_DBUG_THSICE
167 dBugFlag = debugLevel.GE.debLevC
168 & .AND. myIter.EQ.nIter0
169 & .AND. ( tracerIdentity.EQ.GAD_SI_HICE .OR.
170 & tracerIdentity.EQ.GAD_SI_QICE2 )
171 c & .AND. tracerIdentity.EQ.GAD_SI_FRAC
172 idb = MIN(13,sNx)
173 jdb = MOD(17,sNy)
174 biDb = nSx/2
175 #endif /* ALLOW_DBUG_THSICE */
176
177 C-- Set up work arrays with valid (i.e. not NaN) values
178 C These inital values do not alter the numerical results. They
179 C just ensure that all memory references are to valid floating
180 C point numbers. This prevents spurious hardware signals due to
181 C uninitialised but inert locations.
182
183 C-- Set tile-specific parameters for horizontal fluxes
184 IF (useCubedSphereExchange) THEN
185 nipass=3
186 #ifdef ALLOW_EXCH2
187 myTile = W2_myTileList(bi,bj)
188 nCFace = exch2_myFace(myTile)
189 N_edge = exch2_isNedge(myTile).EQ.1
190 S_edge = exch2_isSedge(myTile).EQ.1
191 E_edge = exch2_isEedge(myTile).EQ.1
192 W_edge = exch2_isWedge(myTile).EQ.1
193 #else
194 nCFace = bi
195 N_edge = .TRUE.
196 S_edge = .TRUE.
197 E_edge = .TRUE.
198 W_edge = .TRUE.
199 #endif
200 ELSE
201 nipass=2
202 nCFace = bi
203 N_edge = .FALSE.
204 S_edge = .FALSE.
205 E_edge = .FALSE.
206 W_edge = .FALSE.
207 ENDIF
208
209 iMin = 1-OLx
210 iMax = sNx+OLx
211 jMin = 1-OLy
212 jMax = sNy+OLy
213
214 C-- Start horizontal fluxes
215
216 C-- set mask West & South (and local Centered mask)
217 DO j=1-OLy,sNy+OLy
218 maskLocW(1-Olx,j) = 0.
219 DO i=2-OLx,sNx+OLx
220 maskLocW(i,j) = MIN( maskOc(i-1,j), maskOc(i,j) )
221 #ifdef ALLOW_OBCS
222 & * maskInW(i,j,bi,bj)
223 #endif /* ALLOW_OBCS */
224 ENDDO
225 ENDDO
226 DO i=1-OLx,sNx+OLx
227 maskLocS(i,1-Oly) = 0.
228 ENDDO
229 DO j=2-OLy,sNy+OLy
230 DO i=1-OLx,sNx+OLx
231 maskLocS(i,j) = MIN( maskOc(i,j-1), maskOc(i,j) )
232 #ifdef ALLOW_OBCS
233 & * maskInS(i,j,bi,bj)
234 #endif /* ALLOW_OBCS */
235 ENDDO
236 ENDDO
237 C maskLocC is just a local copy of Ocean mask (maskOc) except if using OBCS:
238 C use "maksInC" to prevent updating tracer field in OB regions
239 DO j=1-OLy,sNy+OLy
240 DO i=1-OLx,sNx+OLx
241 maskLocC(i,j) = maskOc(i,j)
242 #ifdef ALLOW_OBCS
243 & * maskInC(i,j,bi,bj)
244 #endif /* ALLOW_OBCS */
245 ENDDO
246 ENDDO
247
248 cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
249 IF (useCubedSphereExchange) THEN
250 withSigns = .FALSE.
251 CALL FILL_CS_CORNER_UV_RS(
252 & withSigns, maskLocW,maskLocS, bi,bj, myThid )
253 ENDIF
254 cph-exch2#endif
255
256 C-- Multiple passes for different directions on different tiles
257 C-- For cube need one pass for each of red, green and blue axes.
258 DO ipass=1,nipass
259 #ifdef ALLOW_AUTODIFF_TAMC
260 ikey_4 = ipass
261 & + nipass*act1
262 & + nipass*max1*act2
263 & + nipass*max1*max2*act3
264 & + nipass*max1*max2*max3*act4
265 #endif
266
267 #ifdef ALLOW_AUTODIFF_TAMC
268 CADJ STORE iceFld(:,:) = comlev1_thsice_4, key=ikey_4, byte=isbyte
269 CADJ STORE iceVol(:,:) = comlev1_thsice_4, key=ikey_4, byte=isbyte
270 CADJ STORE af(:,:) = comlev1_thsice_4, key=ikey_4, byte=isbyte
271 #endif
272
273 interiorOnly = .FALSE.
274 overlapOnly = .FALSE.
275 IF (useCubedSphereExchange) THEN
276 C-- CubedSphere : pass 3 times, with partial update of local seaice field
277 IF (ipass.EQ.1) THEN
278 overlapOnly = MOD(nCFace,3).EQ.0
279 interiorOnly = MOD(nCFace,3).NE.0
280 calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
281 calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
282 ELSEIF (ipass.EQ.2) THEN
283 overlapOnly = MOD(nCFace,3).EQ.2
284 interiorOnly = MOD(nCFace,3).EQ.1
285 calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
286 calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
287 ELSE
288 interiorOnly = .TRUE.
289 calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
290 calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
291 ENDIF
292 ELSE
293 C-- not CubedSphere
294 calc_fluxes_X = MOD(ipass,2).EQ.1
295 calc_fluxes_Y = .NOT.calc_fluxes_X
296 ENDIF
297 #ifdef ALLOW_DBUG_THSICE
298 IF (dBugFlag.AND.bi.EQ.biDb ) WRITE(6,'(A,3I4,2I5,4L5)')
299 & 'ICE_adv:', tracerIdentity, ipass, bi, idb, jdb,
300 & calc_fluxes_X, calc_fluxes_Y, overlapOnly, interiorOnly
301 #endif /* ALLOW_DBUG_THSICE */
302
303 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
304 C-- X direction
305
306 IF (calc_fluxes_X) THEN
307
308 C- Do not compute fluxes if
309 C a) needed in overlap only
310 C and b) the overlap of myTile are not cube-face Edges
311 #ifdef ALLOW_AUTODIFF_TAMC
312 CADJ STORE iceFld(:,:) = comlev1_thsice_4, key=ikey_4, byte=isbyte
313 CADJ STORE iceVol(:,:) = comlev1_thsice_4, key=ikey_4, byte=isbyte
314 CADJ STORE af(:,:) = comlev1_thsice_4, key=ikey_4, byte=isbyte
315 #endif
316 IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
317
318 C- Advective flux in X
319 DO j=1-Oly,sNy+Oly
320 DO i=1-Olx,sNx+Olx
321 af(i,j) = 0.
322 ENDDO
323 ENDDO
324
325 cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
326 C- Internal exchange for calculations in X
327 IF ( overlapOnly ) THEN
328 CALL FILL_CS_CORNER_TR_RL( 1, .FALSE.,
329 & iceFld, bi,bj, myThid )
330 IF ( .NOT.useGridArea )
331 & CALL FILL_CS_CORNER_TR_RL( 1, .FALSE.,
332 & iceVol, bi,bj, myThid )
333 ENDIF
334 cph-exch2#endif
335
336 C- Compute CFL number
337 IF ( useGridArea ) THEN
338 DO j=1-Oly,sNy+Oly
339 DO i=2-Olx,sNx+Olx
340 uCfl(i,j) = deltaTadvect*(
341 & MAX( uTrans(i,j), 0. _d 0 )*recip_rA(i-1,j,bi,bj)
342 & +MAX(-uTrans(i,j), 0. _d 0 )*recip_rA( i ,j,bi,bj)
343 & )
344 ENDDO
345 ENDDO
346 ELSE
347 DO j=1-Oly,sNy+Oly
348 DO i=2-Olx,sNx+Olx
349 uCfl(i,j) = deltaTadvect*(
350 & MAX( uTrans(i,j), 0. _d 0 )/MAX( iceVol(i-1,j), iceEps )
351 & +MAX(-uTrans(i,j), 0. _d 0 )/MAX( iceVol( i ,j), iceEps )
352 & )
353 ENDDO
354 ENDDO
355 ENDIF
356
357 IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
358 & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
359 CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme, .FALSE.,
360 I deltaTadvect, uTrans, uCfl, iceFld,
361 O af, myThid )
362 #ifdef ALLOW_DBUG_THSICE
363 IF (dBugFlag.AND.bi.EQ.biDb ) WRITE(6,'(A,1P4E14.6)')
364 & 'ICE_adv: xFx=', af(idb,jdb), iceFld(idb,jdb),
365 & uTrans(idb,jdb), af(idb,jdb)/uTrans(idb,jdb)
366 #endif /* ALLOW_DBUG_THSICE */
367 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
368 CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, .FALSE., deltaTadvect,
369 I uTrans, uCfl, maskLocW, iceFld,
370 O af, myThid )
371 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
372 CALL GAD_DST3_ADV_X( bi,bj,k, .FALSE., deltaTadvect,
373 I uTrans, uCfl, maskLocW, iceFld,
374 O af, myThid )
375 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
376 CALL GAD_DST3FL_ADV_X( bi,bj,k, .FALSE., deltaTadvect,
377 I uTrans, uCfl, maskLocW, iceFld,
378 O af, myThid )
379 ELSE
380 STOP
381 & 'THSICE_ADVECTION: adv. scheme incompatibale with multi-dim'
382 ENDIF
383
384 cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
385 C-- Internal exchange for next calculations in Y
386 IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
387 CALL FILL_CS_CORNER_TR_RL( 2, .FALSE.,
388 & iceFld, bi,bj, myThid )
389 IF ( .NOT.useGridArea )
390 & CALL FILL_CS_CORNER_TR_RL( 2, .FALSE.,
391 & iceVol, bi,bj, myThid )
392 ENDIF
393 cph-exch2#endif
394
395 C-- Advective flux in X : done
396 ENDIF
397
398 C- Update the local seaice field where needed:
399
400 C update in overlap-Only
401 IF ( overlapOnly ) THEN
402 iMinUpd = 1-OLx+1
403 iMaxUpd = sNx+OLx-1
404 C-- notes: these 2 lines below have no real effect (because recip_hFac=0
405 C in corner region) but safer to keep them.
406 IF ( W_edge ) iMinUpd = 1
407 IF ( E_edge ) iMaxUpd = sNx
408
409 #ifdef ALLOW_AUTODIFF_TAMC
410 CADJ STORE iceFld(:,:) = comlev1_thsice_4, key=ikey_4, byte=isbyte
411 CADJ STORE iceVol(:,:) = comlev1_thsice_4, key=ikey_4, byte=isbyte
412 #endif
413 IF ( S_edge ) THEN
414 IF ( useGridArea ) THEN
415 DO j=1-OLy,0
416 DO i=iMinUpd,iMaxUpd
417 iceFld(i,j) = iceFld(i,j)
418 & -deltaTadvect*maskLocC(i,j)
419 & *recip_rA(i,j,bi,bj)
420 & *( af(i+1,j)-af(i,j) )
421 ENDDO
422 ENDDO
423 ELSE
424 DO j=1-OLy,0
425 DO i=iMinUpd,iMaxUpd
426 tmpVol = iceVol(i,j)
427 iceVol(i,j) = iceVol(i,j)
428 & -deltaTadvect*maskLocC(i,j)
429 & *( uTrans(i+1,j)-uTrans(i,j) )
430 IF ( iceVol(i,j).GT.iceEps )
431 & iceFld(i,j) = ( iceFld(i,j)*tmpVol
432 & -deltaTadvect*maskLocC(i,j)
433 & *( af(i+1,j)-af(i,j) )
434 & )/iceVol(i,j)
435 ENDDO
436 ENDDO
437 ENDIF
438 C- keep advective flux (for diagnostics)
439 DO j=1-OLy,0
440 DO i=1-OLx+1,sNx+OLx
441 afx(i,j) = af(i,j)
442 ENDDO
443 ENDDO
444 C- end if South Edge
445 ENDIF
446 IF ( N_edge ) THEN
447 IF ( useGridArea ) THEN
448 DO j=sNy+1,sNy+OLy
449 DO i=iMinUpd,iMaxUpd
450 iceFld(i,j) = iceFld(i,j)
451 & -deltaTadvect*maskLocC(i,j)
452 & *recip_rA(i,j,bi,bj)
453 & *( af(i+1,j)-af(i,j) )
454 ENDDO
455 ENDDO
456 ELSE
457 DO j=sNy+1,sNy+OLy
458 DO i=iMinUpd,iMaxUpd
459 tmpVol = iceVol(i,j)
460 iceVol(i,j) = iceVol(i,j)
461 & -deltaTadvect*maskLocC(i,j)
462 & *( uTrans(i+1,j)-uTrans(i,j) )
463 IF ( iceVol(i,j).GT.iceEps )
464 & iceFld(i,j) = ( iceFld(i,j)*tmpVol
465 & -deltaTadvect*maskLocC(i,j)
466 & *( af(i+1,j)-af(i,j) )
467 & )/iceVol(i,j)
468 ENDDO
469 ENDDO
470 ENDIF
471 C- keep advective flux (for diagnostics)
472 DO j=sNy+1,sNy+OLy
473 DO i=1-OLx+1,sNx+OLx
474 afx(i,j) = af(i,j)
475 ENDDO
476 ENDDO
477 C- end if North Edge
478 ENDIF
479
480 ELSE
481 C do not only update the overlap
482 jMinUpd = 1-OLy
483 jMaxUpd = sNy+OLy
484 IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
485 IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
486 IF ( useGridArea ) THEN
487 DO j=jMinUpd,jMaxUpd
488 DO i=1-OLx+1,sNx+OLx-1
489 iceFld(i,j) = iceFld(i,j)
490 & -deltaTadvect*maskLocC(i,j)
491 & *recip_rA(i,j,bi,bj)
492 & *( af(i+1,j)-af(i,j) )
493 ENDDO
494 ENDDO
495 ELSE
496 DO j=jMinUpd,jMaxUpd
497 DO i=1-OLx+1,sNx+OLx-1
498 tmpVol = iceVol(i,j)
499 iceVol(i,j) = iceVol(i,j)
500 & -deltaTadvect*maskLocC(i,j)
501 & *( uTrans(i+1,j)-uTrans(i,j) )
502 IF ( iceVol(i,j).GT.iceEps )
503 & iceFld(i,j) = ( iceFld(i,j)*tmpVol
504 & -deltaTadvect*maskLocC(i,j)
505 & *( af(i+1,j)-af(i,j) )
506 & )/iceVol(i,j)
507 ENDDO
508 ENDDO
509 ENDIF
510 C- keep advective flux (for diagnostics)
511 DO j=jMinUpd,jMaxUpd
512 DO i=1-OLx+1,sNx+OLx
513 afx(i,j) = af(i,j)
514 ENDDO
515 ENDDO
516
517 C- end if/else update overlap-Only
518 ENDIF
519
520 C-- End of X direction
521 ENDIF
522
523 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
524 C-- Y direction
525
526 IF (calc_fluxes_Y) THEN
527
528 C- Do not compute fluxes if
529 C a) needed in overlap only
530 C and b) the overlap of myTile are not cube-face edges
531 #ifdef ALLOW_AUTODIFF_TAMC
532 CADJ STORE iceFld(:,:) = comlev1_thsice_4, key=ikey_4, byte=isbyte
533 CADJ STORE iceVol(:,:) = comlev1_thsice_4, key=ikey_4, byte=isbyte
534 CADJ STORE af(:,:) = comlev1_thsice_4, key=ikey_4, byte=isbyte
535 #endif
536 IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
537
538 C- Advective flux in Y
539 DO j=1-OLy,sNy+OLy
540 DO i=1-OLx,sNx+OLx
541 af(i,j) = 0.
542 ENDDO
543 ENDDO
544
545 cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
546 C- Internal exchange for calculations in Y
547 IF ( overlapOnly ) THEN
548 CALL FILL_CS_CORNER_TR_RL( 2, .FALSE.,
549 & iceFld, bi,bj, myThid )
550 IF ( .NOT.useGridArea )
551 & CALL FILL_CS_CORNER_TR_RL( 2, .FALSE.,
552 & iceVol, bi,bj, myThid )
553 ENDIF
554 cph-exch2#endif
555
556 C- Compute CFL number
557 IF ( useGridArea ) THEN
558 DO j=2-Oly,sNy+Oly
559 DO i=1-Olx,sNx+Olx
560 vCfl(i,j) = deltaTadvect*(
561 & MAX( vTrans(i,j), 0. _d 0 )*recip_rA(i,j-1,bi,bj)
562 & +MAX(-vTrans(i,j), 0. _d 0 )*recip_rA(i, j ,bi,bj)
563 & )
564 ENDDO
565 ENDDO
566 ELSE
567 DO j=2-Oly,sNy+Oly
568 DO i=1-Olx,sNx+Olx
569 vCfl(i,j) = deltaTadvect*(
570 & MAX( vTrans(i,j), 0. _d 0 )/MAX( iceVol(i,j-1), iceEps )
571 & +MAX(-vTrans(i,j), 0. _d 0 )/MAX( iceVol(i, j ), iceEps )
572 & )
573 ENDDO
574 ENDDO
575 ENDIF
576
577 IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
578 & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
579 CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme, .FALSE.,
580 I deltaTadvect, vTrans, vCfl, iceFld,
581 O af, myThid )
582 #ifdef ALLOW_DBUG_THSICE
583 IF (dBugFlag.AND.bi.EQ.biDb ) WRITE(6,'(A,1P4E14.6)')
584 & 'ICE_adv: yFx=', af(idb,jdb), iceFld(idb,jdb),
585 & vTrans(idb,jdb), af(idb,jdb)/vTrans(idb,jdb)
586 #endif /* ALLOW_DBUG_THSICE */
587 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
588 CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, .FALSE., deltaTadvect,
589 I vTrans, vCfl, maskLocS, iceFld,
590 O af, myThid )
591 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
592 CALL GAD_DST3_ADV_Y( bi,bj,k, .FALSE., deltaTadvect,
593 I vTrans, vCfl, maskLocS, iceFld,
594 O af, myThid )
595 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
596 CALL GAD_DST3FL_ADV_Y( bi,bj,k, .FALSE., deltaTadvect,
597 I vTrans, vCfl, maskLocS, iceFld,
598 O af, myThid )
599 ELSE
600 STOP
601 & 'THSICE_ADVECTION: adv. scheme incompatibale with mutli-dim'
602 ENDIF
603
604 cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
605 IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
606 CALL FILL_CS_CORNER_TR_RL( 1, .FALSE.,
607 & iceFld, bi,bj, myThid )
608 IF ( .NOT.useGridArea )
609 & CALL FILL_CS_CORNER_TR_RL( 1, .FALSE.,
610 & iceVol, bi,bj, myThid )
611 ENDIF
612 cph-exch2#endif
613
614 C- Advective flux in Y : done
615 ENDIF
616
617 C- Update the local seaice field where needed:
618
619 C update in overlap-Only
620 IF ( overlapOnly ) THEN
621 jMinUpd = 1-OLy+1
622 jMaxUpd = sNy+OLy-1
623 C- notes: these 2 lines below have no real effect (because recip_hFac=0
624 C in corner region) but safer to keep them.
625 IF ( S_edge ) jMinUpd = 1
626 IF ( N_edge ) jMaxUpd = sNy
627
628 #ifdef ALLOW_AUTODIFF_TAMC
629 CADJ STORE iceFld(:,:) = comlev1_thsice_4, key=ikey_4, byte=isbyte
630 CADJ STORE iceVol(:,:) = comlev1_thsice_4, key=ikey_4, byte=isbyte
631 #endif
632 IF ( W_edge ) THEN
633 IF ( useGridArea ) THEN
634 DO j=jMinUpd,jMaxUpd
635 DO i=1-OLx,0
636 iceFld(i,j) = iceFld(i,j)
637 & -deltaTadvect*maskLocC(i,j)
638 & *recip_rA(i,j,bi,bj)
639 & *( af(i,j+1)-af(i,j) )
640 ENDDO
641 ENDDO
642 ELSE
643 DO j=jMinUpd,jMaxUpd
644 DO i=1-OLx,0
645 tmpVol = iceVol(i,j)
646 iceVol(i,j) = iceVol(i,j)
647 & -deltaTadvect*maskLocC(i,j)
648 & *( vTrans(i,j+1)-vTrans(i,j) )
649 IF ( iceVol(i,j).GT.iceEps )
650 & iceFld(i,j) = ( iceFld(i,j)*tmpVol
651 & -deltaTadvect*maskLocC(i,j)
652 & *( af(i,j+1)-af(i,j) )
653 & )/iceVol(i,j)
654 ENDDO
655 ENDDO
656 ENDIF
657 C- keep advective flux (for diagnostics)
658 DO j=1-OLy+1,sNy+OLy
659 DO i=1-OLx,0
660 afy(i,j) = af(i,j)
661 ENDDO
662 ENDDO
663 C- end if West Edge
664 ENDIF
665 IF ( E_edge ) THEN
666 IF ( useGridArea ) THEN
667 DO j=jMinUpd,jMaxUpd
668 DO i=sNx+1,sNx+OLx
669 iceFld(i,j) = iceFld(i,j)
670 & -deltaTadvect*maskLocC(i,j)
671 & *recip_rA(i,j,bi,bj)
672 & *( af(i,j+1)-af(i,j) )
673 ENDDO
674 ENDDO
675 ELSE
676 DO j=jMinUpd,jMaxUpd
677 DO i=sNx+1,sNx+OLx
678 tmpVol = iceVol(i,j)
679 iceVol(i,j) = iceVol(i,j)
680 & -deltaTadvect*maskLocC(i,j)
681 & *( vTrans(i,j+1)-vTrans(i,j) )
682 IF ( iceVol(i,j).GT.iceEps )
683 & iceFld(i,j) = ( iceFld(i,j)*tmpVol
684 & -deltaTadvect*maskLocC(i,j)
685 & *( af(i,j+1)-af(i,j) )
686 & )/iceVol(i,j)
687 ENDDO
688 ENDDO
689 ENDIF
690 C- keep advective flux (for diagnostics)
691 DO j=1-OLy+1,sNy+OLy
692 DO i=sNx+1,sNx+OLx
693 afy(i,j) = af(i,j)
694 ENDDO
695 ENDDO
696 C- end if East Edge
697 ENDIF
698
699 ELSE
700 C do not only update the overlap
701 iMinUpd = 1-OLx
702 iMaxUpd = sNx+OLx
703 IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
704 IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
705 IF ( useGridArea ) THEN
706 DO j=1-OLy+1,sNy+OLy-1
707 DO i=iMinUpd,iMaxUpd
708 iceFld(i,j) = iceFld(i,j)
709 & -deltaTadvect*maskLocC(i,j)
710 & *recip_rA(i,j,bi,bj)
711 & *( af(i,j+1)-af(i,j) )
712 ENDDO
713 ENDDO
714 ELSE
715 DO j=1-OLy+1,sNy+OLy-1
716 DO i=iMinUpd,iMaxUpd
717 tmpVol = iceVol(i,j)
718 iceVol(i,j) = iceVol(i,j)
719 & -deltaTadvect*maskLocC(i,j)
720 & *( vTrans(i,j+1)-vTrans(i,j) )
721 IF ( iceVol(i,j).GT.iceEps )
722 & iceFld(i,j) = ( iceFld(i,j)*tmpVol
723 & -deltaTadvect*maskLocC(i,j)
724 & *( af(i,j+1)-af(i,j) )
725 & )/iceVol(i,j)
726 ENDDO
727 ENDDO
728 ENDIF
729 C- keep advective flux (for diagnostics)
730 DO j=1-OLy+1,sNy+OLy
731 DO i=iMinUpd,iMaxUpd
732 afy(i,j) = af(i,j)
733 ENDDO
734 ENDDO
735
736 C end if/else update overlap-Only
737 ENDIF
738
739 C-- End of Y direction
740 ENDIF
741
742 C-- End of ipass loop
743 ENDDO
744
745 C- explicit advection is done ; add some debugging print
746 #ifdef ALLOW_DBUG_THSICE
747 IF ( dBugFlag ) THEN
748 DO j=1-OLy,sNy+OLy
749 DO i=1-OLx,sNx+OLx
750 IF ( i.EQ.idb .AND. j.EQ.jdb .AND. bi.EQ.biDb ) THEN
751 tmpFac= deltaTadvect*recip_rA(i,j,bi,bj)
752 WRITE(6,'(A,1P4E14.6)') 'ICE_adv:',
753 & afx(i,j)*tmpFac,afx(i+1,j)*tmpFac,
754 & afy(i,j)*tmpFac,afy(i,j+1)*tmpFac
755 ENDIF
756 ENDDO
757 ENDDO
758 ENDIF
759
760 #ifdef ALLOW_DEBUG
761 IF ( debugLevel .GE. debLevC
762 & .AND. tracerIdentity.EQ.GAD_SI_HICE
763 & .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
764 & .AND. nPx.EQ.1 .AND. nPy.EQ.1
765 & .AND. useCubedSphereExchange ) THEN
766 CALL DEBUG_CS_CORNER_UV( ' afx,afy from THSICE_ADVECTION',
767 & afx,afy, k, standardMessageUnit,bi,bj,myThid )
768 ENDIF
769 #endif /* ALLOW_DEBUG */
770 #endif /* ALLOW_DBUG_THSICE */
771
772 #endif /* ALLOW_GENERIC_ADVDIFF */
773
774 RETURN
775 END

  ViewVC Help
Powered by ViewVC 1.1.22