/[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.1 - (show annotations) (download)
Wed Apr 4 02:40:42 2007 UTC (17 years, 2 months ago) by jmc
Branch: MAIN
code to advect pkg/thSIce fields (testing is in progress).

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

  ViewVC Help
Powered by ViewVC 1.1.22