/[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.2 - (show annotations) (download)
Sun Apr 8 18:53:16 2007 UTC (17 years, 1 month ago) by jmc
Branch: MAIN
Changes since 1.1: +4 -1 lines
add #ifdef arround pkg/generic_advdiff source code.

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_advection.F,v 1.1 2007/04/04 02:40:42 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 useGridVolume,
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 "extensive" 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 #include "THSICE_SIZE.h"
52 #ifdef ALLOW_GENERIC_ADVDIFF
53 # include "GAD.h"
54 #endif
55 #ifdef ALLOW_EXCH2
56 #include "W2_EXCH2_TOPOLOGY.h"
57 #include "W2_EXCH2_PARAMS.h"
58 #endif /* ALLOW_EXCH2 */
59
60 C !INPUT PARAMETERS: ===================================================
61 C tracerIdentity :: tracer identifier (required only for OBCS)
62 C advectionScheme :: advection scheme to use (Horizontal plane)
63 C useGridVolume :: use grid-cell Area & Volume (instead of "iceVol" field)
64 C uTrans,vTrans :: volume transports at U,V points
65 C maskOc :: oceanic mask
66 C iceVol :: sea-ice volume
67 C iceFld :: sea-ice field
68 C deltaTadvect :: time-step used for advection [s]
69 C iceEps :: small volume (to avoid division by zero if iceVol==0)
70 C bi,bj :: tile indices
71 C myTime :: current time in simulation [s]
72 C myIter :: current iteration number
73 C myThid :: my thread Id. number
74 INTEGER tracerIdentity
75 INTEGER advectionScheme
76 LOGICAL useGridVolume
77 _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78 _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79 _RS maskOc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80 _RL iceFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81 _RL iceVol(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82 _RL deltaTadvect, iceEps
83 INTEGER bi,bj
84 _RL myTime
85 INTEGER myIter
86 INTEGER myThid
87
88 C !OUTPUT PARAMETERS: ==================================================
89 C iceVol (Updated):: sea-ice volume
90 C iceFld (Updated):: sea-ice field
91 C afx :: horizontal advective flux, x direction
92 C afy :: horizontal advective flux, y direction
93 _RL afx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
94 _RL afy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
95
96 #ifdef ALLOW_GENERIC_ADVDIFF
97 C !LOCAL VARIABLES: ====================================================
98 C maskLocW :: 2-D array for mask at West points
99 C maskLocS :: 2-D array for mask at South points
100 C iMin,iMax, :: loop range for called routines
101 C jMin,jMax :: loop range for called routines
102 C [iMin,iMax]Upd :: loop range to update sea-ice field
103 C [jMin,jMax]Upd :: loop range to update sea-ice field
104 C i,j :: loop indices
105 C uCfl :: CFL number, zonal direction
106 C vCfl :: CFL number, meridional direction
107 C af :: 2-D array for horizontal advective flux
108 C calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
109 C calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
110 C interiorOnly :: only update the interior of myTile, but not the edges
111 C overlapOnly :: only update the edges of myTile, but not the interior
112 C nipass :: number of passes in multi-dimensional method
113 C ipass :: number of the current pass being made
114 C myTile :: variables used to determine which cube face
115 C nCFace :: owns a tile for cube grid runs using
116 C :: multi-dim advection.
117 C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
118 _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
119 _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120 INTEGER iMin,iMax,jMin,jMax
121 INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd
122 INTEGER i,j,k
123 _RL uCfl (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
124 _RL vCfl (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
125 _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
126 LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns
127 LOGICAL interiorOnly, overlapOnly
128 INTEGER nipass,ipass
129 INTEGER nCFace
130 LOGICAL N_edge, S_edge, E_edge, W_edge
131 #ifdef ALLOW_EXCH2
132 INTEGER myTile
133 #endif
134 LOGICAL dBug
135 _RL tmpFac
136 _RL tmpVol
137 CEOP
138
139 dBug = debugLevel.GE.debLevB
140 & .AND. myIter.EQ.nIter0
141 & .AND. ( tracerIdentity.EQ.GAD_SI_HICE .OR.
142 & tracerIdentity.EQ.GAD_SI_QICE2 )
143 c & .AND. tracerIdentity.EQ.GAD_SI_HICE
144
145 C-- Set up work arrays with valid (i.e. not NaN) values
146 C These inital values do not alter the numerical results. They
147 C just ensure that all memory references are to valid floating
148 C point numbers. This prevents spurious hardware signals due to
149 C uninitialised but inert locations.
150
151 C-- Set tile-specific parameters for horizontal fluxes
152 IF (useCubedSphereExchange) THEN
153 nipass=3
154 #ifdef ALLOW_EXCH2
155 myTile = W2_myTileList(bi)
156 nCFace = exch2_myFace(myTile)
157 N_edge = exch2_isNedge(myTile).EQ.1
158 S_edge = exch2_isSedge(myTile).EQ.1
159 E_edge = exch2_isEedge(myTile).EQ.1
160 W_edge = exch2_isWedge(myTile).EQ.1
161 #else
162 nCFace = bi
163 N_edge = .TRUE.
164 S_edge = .TRUE.
165 E_edge = .TRUE.
166 W_edge = .TRUE.
167 #endif
168 ELSE
169 nipass=2
170 nCFace = bi
171 N_edge = .FALSE.
172 S_edge = .FALSE.
173 E_edge = .FALSE.
174 W_edge = .FALSE.
175 ENDIF
176
177 iMin = 1-OLx
178 iMax = sNx+OLx
179 jMin = 1-OLy
180 jMax = sNy+OLy
181
182 C-- Start horizontal fluxes
183
184 C-- set mask West & South
185 DO j=1-OLy,sNy+OLy
186 maskLocW(1-Olx,j) = 0.
187 DO i=2-OLx,sNx+OLx
188 maskLocW(i,j) = MIN( maskOc(i-1,j), maskOc(i,j) )
189 ENDDO
190 ENDDO
191 DO i=1-OLx,sNx+OLx
192 maskLocS(i,1-Oly) = 0.
193 ENDDO
194 DO j=2-OLy,sNy+OLy
195 DO i=1-OLx,sNx+OLx
196 maskLocS(i,j) = MIN( maskOc(i,j-1), maskOc(i,j) )
197 ENDDO
198 ENDDO
199
200 IF (useCubedSphereExchange) THEN
201 withSigns = .FALSE.
202 CALL FILL_CS_CORNER_UV_RS(
203 & withSigns, maskLocW,maskLocS, bi,bj, myThid )
204 ENDIF
205
206 C-- Multiple passes for different directions on different tiles
207 C-- For cube need one pass for each of red, green and blue axes.
208 DO ipass=1,nipass
209
210 interiorOnly = .FALSE.
211 overlapOnly = .FALSE.
212 IF (useCubedSphereExchange) THEN
213 C-- CubedSphere : pass 3 times, with partial update of local seaice field
214 IF (ipass.EQ.1) THEN
215 overlapOnly = MOD(nCFace,3).EQ.0
216 interiorOnly = MOD(nCFace,3).NE.0
217 calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
218 calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
219 ELSEIF (ipass.EQ.2) THEN
220 overlapOnly = MOD(nCFace,3).EQ.2
221 calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
222 calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
223 ELSE
224 calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
225 calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
226 ENDIF
227 ELSE
228 C-- not CubedSphere
229 calc_fluxes_X = MOD(ipass,2).EQ.1
230 calc_fluxes_Y = .NOT.calc_fluxes_X
231 ENDIF
232 IF (dBug.AND.bi.EQ.3 ) WRITE(6,*) 'ICE_adv:',tracerIdentity,
233 & ipass,calc_fluxes_X,calc_fluxes_Y,overlapOnly,interiorOnly
234
235 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
236 C-- X direction
237
238 IF (calc_fluxes_X) THEN
239
240 C- Do not compute fluxes if
241 C a) needed in overlap only
242 C and b) the overlap of myTile are not cube-face Edges
243 IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
244
245 C- Advective flux in X
246 DO j=1-Oly,sNy+Oly
247 DO i=1-Olx,sNx+Olx
248 af(i,j) = 0.
249 ENDDO
250 ENDDO
251
252 C- Internal exchange for calculations in X
253 IF ( useCubedSphereExchange .AND.
254 & ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
255 CALL FILL_CS_CORNER_TR_RL( .TRUE., iceFld, bi,bj, myThid )
256 IF ( .NOT.useGridVolume )
257 & CALL FILL_CS_CORNER_TR_RL( .TRUE., iceVol, bi,bj, myThid )
258 ENDIF
259
260 C- Compute CFL number
261 IF ( useGridVolume ) THEN
262 DO j=1-Oly,sNy+Oly
263 DO i=2-Olx,sNx+Olx
264 uCfl(i,j) = deltaTadvect*(
265 & MAX( uTrans(i,j), 0. _d 0 )*recip_rA(i-1,j,bi,bj)
266 & +MAX(-uTrans(i,j), 0. _d 0 )*recip_rA( i ,j,bi,bj)
267 & )
268 ENDDO
269 ENDDO
270 ELSE
271 DO j=1-Oly,sNy+Oly
272 DO i=2-Olx,sNx+Olx
273 uCfl(i,j) = deltaTadvect*(
274 & MAX( uTrans(i,j), 0. _d 0 )/MAX( iceVol(i-1,j), iceEps )
275 & +MAX(-uTrans(i,j), 0. _d 0 )/MAX( iceVol( i ,j), iceEps )
276 & )
277 ENDDO
278 ENDDO
279 ENDIF
280
281 IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
282 & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
283 CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme, .FALSE.,
284 I deltaTadvect, uTrans, uCfl, iceFld,
285 O af, myThid )
286 IF (dBug.AND. bi.EQ.3) WRITE(6,'(A,1P4E14.6)')
287 & 'ICE_adv: xFx=',af(13,11),iceFld(12,11),uTrans(13,11),
288 & af(13,11)/uTrans(13,11)
289 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
290 CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, .FALSE., deltaTadvect,
291 I uTrans, uCfl, maskLocW, iceFld,
292 O af, myThid )
293 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
294 CALL GAD_DST3_ADV_X( bi,bj,k, .FALSE., deltaTadvect,
295 I uTrans, uCfl, maskLocW, iceFld,
296 O af, myThid )
297 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
298 CALL GAD_DST3FL_ADV_X( bi,bj,k, .FALSE., deltaTadvect,
299 I uTrans, uCfl, maskLocW, iceFld,
300 O af, myThid )
301 ELSE
302 STOP
303 & 'THSICE_ADVECTION: adv. scheme incompatibale with multi-dim'
304 ENDIF
305
306 C-- Advective flux in X : done
307 ENDIF
308
309 C-- Internal exchange for next calculations in Y
310 IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
311 CALL FILL_CS_CORNER_TR_RL(.FALSE., iceFld, bi,bj, myThid )
312 IF ( .NOT.useGridVolume )
313 & CALL FILL_CS_CORNER_TR_RL(.FALSE., iceVol, bi,bj, myThid )
314 ENDIF
315
316 C- Update the local seaice field where needed:
317
318 C update in overlap-Only
319 IF ( overlapOnly ) THEN
320 iMinUpd = 1-OLx+1
321 iMaxUpd = sNx+OLx-1
322 C-- notes: these 2 lines below have no real effect (because recip_hFac=0
323 C in corner region) but safer to keep them.
324 IF ( W_edge ) iMinUpd = 1
325 IF ( E_edge ) iMaxUpd = sNx
326
327 IF ( S_edge .AND. useGridVolume ) THEN
328 DO j=1-OLy,0
329 DO i=iMinUpd,iMaxUpd
330 iceFld(i,j) = iceFld(i,j)
331 & -deltaTadvect*maskOc(i,j)
332 & *recip_rA(i,j,bi,bj)
333 & *( af(i+1,j)-af(i,j) )
334 ENDDO
335 ENDDO
336 ELSEIF ( S_edge ) THEN
337 DO j=1-OLy,0
338 DO i=iMinUpd,iMaxUpd
339 tmpVol = iceVol(i,j)
340 iceVol(i,j) = iceVol(i,j)
341 & -deltaTadvect*maskOc(i,j)
342 & *( uTrans(i+1,j)-uTrans(i,j) )
343 IF ( iceVol(i,j).GT.iceEps )
344 & iceFld(i,j) = ( iceFld(i,j)*tmpVol
345 & -deltaTadvect*maskOc(i,j)
346 & *( af(i+1,j)-af(i,j) )
347 & )/iceVol(i,j)
348 ENDDO
349 ENDDO
350 ENDIF
351 IF ( N_edge .AND. useGridVolume ) THEN
352 DO j=sNy+1,sNy+OLy
353 DO i=iMinUpd,iMaxUpd
354 iceFld(i,j) = iceFld(i,j)
355 & -deltaTadvect*maskOc(i,j)
356 & *recip_rA(i,j,bi,bj)
357 & *( af(i+1,j)-af(i,j) )
358 ENDDO
359 ENDDO
360 ELSEIF ( N_edge ) THEN
361 DO j=sNy+1,sNy+OLy
362 DO i=iMinUpd,iMaxUpd
363 tmpVol = iceVol(i,j)
364 iceVol(i,j) = iceVol(i,j)
365 & -deltaTadvect*maskOc(i,j)
366 & *( uTrans(i+1,j)-uTrans(i,j) )
367 IF ( iceVol(i,j).GT.iceEps )
368 & iceFld(i,j) = ( iceFld(i,j)*tmpVol
369 & -deltaTadvect*maskOc(i,j)
370 & *( af(i+1,j)-af(i,j) )
371 & )/iceVol(i,j)
372 ENDDO
373 ENDDO
374 ENDIF
375 C-- keep advective flux (for diagnostics)
376 IF ( S_edge ) THEN
377 DO j=1-OLy,0
378 DO i=1-OLx+1,sNx+OLx
379 afx(i,j) = af(i,j)
380 ENDDO
381 ENDDO
382 ENDIF
383 IF ( N_edge ) THEN
384 DO j=sNy+1,sNy+OLy
385 DO i=1-OLx+1,sNx+OLx
386 afx(i,j) = af(i,j)
387 ENDDO
388 ENDDO
389 ENDIF
390
391 ELSE
392 C do not only update the overlap
393 jMinUpd = 1-OLy
394 jMaxUpd = sNy+OLy
395 IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
396 IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
397 IF ( useGridVolume ) THEN
398 DO j=jMinUpd,jMaxUpd
399 DO i=1-OLx+1,sNx+OLx-1
400 iceFld(i,j) = iceFld(i,j)
401 & -deltaTadvect*maskOc(i,j)
402 & *recip_rA(i,j,bi,bj)
403 & *( af(i+1,j)-af(i,j) )
404 ENDDO
405 ENDDO
406 ELSE
407 DO j=jMinUpd,jMaxUpd
408 DO i=1-OLx+1,sNx+OLx-1
409 tmpVol = iceVol(i,j)
410 iceVol(i,j) = iceVol(i,j)
411 & -deltaTadvect*maskOc(i,j)
412 & *( uTrans(i+1,j)-uTrans(i,j) )
413 IF ( iceVol(i,j).GT.iceEps )
414 & iceFld(i,j) = ( iceFld(i,j)*tmpVol
415 & -deltaTadvect*maskOc(i,j)
416 & *( af(i+1,j)-af(i,j) )
417 & )/iceVol(i,j)
418 ENDDO
419 ENDDO
420 ENDIF
421 C-- keep advective flux (for diagnostics)
422 DO j=jMinUpd,jMaxUpd
423 DO i=1-OLx+1,sNx+OLx
424 afx(i,j) = af(i,j)
425 ENDDO
426 ENDDO
427
428 C- end if/else update overlap-Only
429 ENDIF
430
431 C-- End of X direction
432 ENDIF
433
434 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
435 C-- Y direction
436
437 IF (calc_fluxes_Y) THEN
438
439 C- Do not compute fluxes if
440 C a) needed in overlap only
441 C and b) the overlap of myTile are not cube-face edges
442 IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
443
444 C- Advective flux in Y
445 DO j=1-OLy,sNy+OLy
446 DO i=1-OLx,sNx+OLx
447 af(i,j) = 0.
448 ENDDO
449 ENDDO
450
451 C- Internal exchange for calculations in Y
452 IF ( useCubedSphereExchange .AND.
453 & ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
454 CALL FILL_CS_CORNER_TR_RL(.FALSE., iceFld, bi,bj, myThid )
455 IF ( .NOT.useGridVolume )
456 & CALL FILL_CS_CORNER_TR_RL(.FALSE., iceVol, bi,bj, myThid )
457 ENDIF
458
459 C- Compute CFL number
460 IF ( useGridVolume ) THEN
461 DO j=2-Oly,sNy+Oly
462 DO i=1-Olx,sNx+Olx
463 vCfl(i,j) = deltaTadvect*(
464 & MAX( vTrans(i,j), 0. _d 0 )*recip_rA(i,j-1,bi,bj)
465 & +MAX(-vTrans(i,j), 0. _d 0 )*recip_rA(i, j ,bi,bj)
466 & )
467 ENDDO
468 ENDDO
469 ELSE
470 DO j=2-Oly,sNy+Oly
471 DO i=1-Olx,sNx+Olx
472 vCfl(i,j) = deltaTadvect*(
473 & MAX( vTrans(i,j), 0. _d 0 )/MAX( iceVol(i,j-1), iceEps )
474 & +MAX(-vTrans(i,j), 0. _d 0 )/MAX( iceVol(i, j ), iceEps )
475 & )
476 ENDDO
477 ENDDO
478 ENDIF
479
480 IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
481 & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
482 CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme, .FALSE.,
483 I deltaTadvect, vTrans, vCfl, iceFld,
484 O af, myThid )
485 IF (dBug.AND. bi.EQ.3) WRITE(6,'(A,1P4E14.6)')
486 & 'ICE_adv: yFx=',af(12,12),iceFld(12,11),vTrans(12,12),
487 & af(12,12)/vTrans(12,12)
488 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
489 CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, .FALSE., deltaTadvect,
490 I vTrans, vCfl, maskLocS, iceFld,
491 O af, myThid )
492 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
493 CALL GAD_DST3_ADV_Y( bi,bj,k, .FALSE., deltaTadvect,
494 I vTrans, vCfl, maskLocS, iceFld,
495 O af, myThid )
496 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
497 CALL GAD_DST3FL_ADV_Y( bi,bj,k, .FALSE., deltaTadvect,
498 I vTrans, vCfl, maskLocS, iceFld,
499 O af, myThid )
500 ELSE
501 STOP
502 & 'THSICE_ADVECTION: adv. scheme incompatibale with mutli-dim'
503 ENDIF
504
505 C- Advective flux in Y : done
506 ENDIF
507
508 IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
509 CALL FILL_CS_CORNER_TR_RL( .TRUE., iceFld, bi,bj, myThid )
510 IF ( .NOT.useGridVolume )
511 & CALL FILL_CS_CORNER_TR_RL( .TRUE., iceVol, bi,bj, myThid )
512 ENDIF
513
514 C- Update the local seaice field where needed:
515
516 C update in overlap-Only
517 IF ( overlapOnly ) THEN
518 jMinUpd = 1-OLy+1
519 jMaxUpd = sNy+OLy-1
520 C- notes: these 2 lines below have no real effect (because recip_hFac=0
521 C in corner region) but safer to keep them.
522 IF ( S_edge ) jMinUpd = 1
523 IF ( N_edge ) jMaxUpd = sNy
524
525 IF ( W_edge .AND. useGridVolume ) THEN
526 DO j=jMinUpd,jMaxUpd
527 DO i=1-OLx,0
528 iceFld(i,j) = iceFld(i,j)
529 & -deltaTadvect*maskOc(i,j)
530 & *recip_rA(i,j,bi,bj)
531 & *( af(i,j+1)-af(i,j) )
532 ENDDO
533 ENDDO
534 ELSEIF ( W_edge ) THEN
535 DO j=jMinUpd,jMaxUpd
536 DO i=1-OLx,0
537 tmpVol = iceVol(i,j)
538 iceVol(i,j) = iceVol(i,j)
539 & -deltaTadvect*maskOc(i,j)
540 & *( vTrans(i,j+1)-vTrans(i,j) )
541 IF ( iceVol(i,j).GT.iceEps )
542 & iceFld(i,j) = ( iceFld(i,j)*tmpVol
543 & -deltaTadvect*maskOc(i,j)
544 & *( af(i,j+1)-af(i,j) )
545 & )/iceVol(i,j)
546 ENDDO
547 ENDDO
548 ENDIF
549 IF ( E_edge .AND. useGridVolume ) THEN
550 DO j=jMinUpd,jMaxUpd
551 DO i=sNx+1,sNx+OLx
552 iceFld(i,j) = iceFld(i,j)
553 & -deltaTadvect*maskOc(i,j)
554 & *recip_rA(i,j,bi,bj)
555 & *( af(i,j+1)-af(i,j) )
556 ENDDO
557 ENDDO
558 ELSEIF ( E_edge ) THEN
559 DO j=jMinUpd,jMaxUpd
560 DO i=sNx+1,sNx+OLx
561 tmpVol = iceVol(i,j)
562 iceVol(i,j) = iceVol(i,j)
563 & -deltaTadvect*maskOc(i,j)
564 & *( vTrans(i,j+1)-vTrans(i,j) )
565 IF ( iceVol(i,j).GT.iceEps )
566 & iceFld(i,j) = ( iceFld(i,j)*tmpVol
567 & -deltaTadvect*maskOc(i,j)
568 & *( af(i,j+1)-af(i,j) )
569 & )/iceVol(i,j)
570 ENDDO
571 ENDDO
572 ENDIF
573 C-- keep advective flux (for diagnostics)
574 IF ( W_edge ) THEN
575 DO j=1-OLy+1,sNy+OLy
576 DO i=1-OLx,0
577 afy(i,j) = af(i,j)
578 ENDDO
579 ENDDO
580 ENDIF
581 IF ( E_edge ) THEN
582 DO j=1-OLy+1,sNy+OLy
583 DO i=sNx+1,sNx+OLx
584 afy(i,j) = af(i,j)
585 ENDDO
586 ENDDO
587 ENDIF
588
589 ELSE
590 C do not only update the overlap
591 iMinUpd = 1-OLx
592 iMaxUpd = sNx+OLx
593 IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
594 IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
595 IF ( useGridVolume ) THEN
596 DO j=1-OLy+1,sNy+OLy-1
597 DO i=iMinUpd,iMaxUpd
598 iceFld(i,j) = iceFld(i,j)
599 & -deltaTadvect*maskOc(i,j)
600 & *recip_rA(i,j,bi,bj)
601 & *( af(i,j+1)-af(i,j) )
602 ENDDO
603 ENDDO
604 ELSE
605 DO j=1-OLy+1,sNy+OLy-1
606 DO i=iMinUpd,iMaxUpd
607 tmpVol = iceVol(i,j)
608 iceVol(i,j) = iceVol(i,j)
609 & -deltaTadvect*maskOc(i,j)
610 & *( vTrans(i,j+1)-vTrans(i,j) )
611 IF ( iceVol(i,j).GT.iceEps )
612 & iceFld(i,j) = ( iceFld(i,j)*tmpVol
613 & -deltaTadvect*maskOc(i,j)
614 & *( af(i,j+1)-af(i,j) )
615 & )/iceVol(i,j)
616 ENDDO
617 ENDDO
618 ENDIF
619 C-- keep advective flux (for diagnostics)
620 DO j=1-OLy+1,sNy+OLy
621 DO i=iMinUpd,iMaxUpd
622 afy(i,j) = af(i,j)
623 ENDDO
624 ENDDO
625
626 C end if/else update overlap-Only
627 ENDIF
628
629 C-- End of Y direction
630 ENDIF
631
632 C-- End of ipass loop
633 ENDDO
634
635 C- explicit advection is done ; add some debugging print
636 IF ( dBug ) THEN
637 DO j=1-OLy,sNy+OLy
638 DO i=1-OLx,sNx+OLx
639 IF ( i.EQ.12 .AND. j.EQ.11 .AND. bi.EQ.3 ) THEN
640 tmpFac= deltaTadvect*recip_rA(i,j,bi,bj)
641 WRITE(6,'(A,1P4E14.6)') 'ICE_adv:',
642 & afx(i,j)*tmpFac,afx(i+1,j)*tmpFac,
643 & afy(i,j)*tmpFac,afy(i,j+1)*tmpFac
644 ENDIF
645 ENDDO
646 ENDDO
647 ENDIF
648
649 #ifdef ALLOW_DEBUG
650 IF ( debugLevel .GE. debLevB
651 & .AND. tracerIdentity.EQ.GAD_SI_HICE
652 & .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
653 & .AND. nPx.EQ.1 .AND. nPy.EQ.1
654 & .AND. useCubedSphereExchange ) THEN
655 CALL DEBUG_CS_CORNER_UV( ' afx,afy from THSICE_ADVECTION',
656 & afx,afy, k, standardMessageUnit,bi,bj,myThid )
657 ENDIF
658 #endif /* ALLOW_DEBUG */
659
660 #endif /* ALLOW_GENERIC_ADVDIFF */
661
662 RETURN
663 END

  ViewVC Help
Powered by ViewVC 1.1.22