/[MITgcm]/MITgcm/pkg/generic_advdiff/gad_som_advect.F
ViewVC logotype

Contents of /MITgcm/pkg/generic_advdiff/gad_som_advect.F

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


Revision 1.10 - (show annotations) (download)
Mon Mar 5 17:59:15 2012 UTC (12 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64d, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63k, checkpoint64
Changes since 1.9: +4 -39 lines
first attempt to allow the use of OBCS with SOM

1 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_som_advect.F,v 1.9 2011/06/06 15:44:00 jmc 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: GAD_SOM_ADVECT
9
10 C !INTERFACE: ==========================================================
11 SUBROUTINE GAD_SOM_ADVECT(
12 I implicitAdvection, advectionScheme, vertAdvecScheme,
13 I tracerIdentity, deltaTLev,
14 I uVel, vVel, wVel, tracer,
15 U smTr,
16 O gTracer,
17 I bi,bj, myTime,myIter,myThid)
18
19 C !DESCRIPTION:
20 C Calculates the tendency of a tracer due to advection.
21 C It uses the 2nd-Order moment advection scheme with multi-dimensional method
22 C see Prather, 1986, JGR, v.91, D-6, pp.6671-6681.
23 C
24 C The tendency (output) is over-written by this routine.
25
26 C !USES: ===============================================================
27 IMPLICIT NONE
28 #include "SIZE.h"
29 #include "EEPARAMS.h"
30 #include "PARAMS.h"
31 #include "GRID.h"
32 #include "GAD.h"
33 #ifdef ALLOW_EXCH2
34 #include "W2_EXCH2_SIZE.h"
35 #include "W2_EXCH2_TOPOLOGY.h"
36 #endif /* ALLOW_EXCH2 */
37
38 C !INPUT PARAMETERS: ===================================================
39 C implicitAdvection :: implicit vertical advection (later on)
40 C advectionScheme :: advection scheme to use (Horizontal plane)
41 C vertAdvecScheme :: advection scheme to use (vertical direction)
42 C tracerIdentity :: tracer identifier (required only for OBCS)
43 C uVel :: velocity, zonal component
44 C vVel :: velocity, meridional component
45 C wVel :: velocity, vertical component
46 C tracer :: tracer field
47 C bi,bj :: tile indices
48 C myTime :: current time
49 C myIter :: iteration number
50 C myThid :: thread number
51 LOGICAL implicitAdvection
52 INTEGER advectionScheme, vertAdvecScheme
53 INTEGER tracerIdentity
54 _RL deltaTLev(Nr)
55 _RL uVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
56 _RL vVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
57 _RL wVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
58 _RL tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
59 INTEGER bi,bj
60 _RL myTime
61 INTEGER myIter
62 INTEGER myThid
63
64 C !OUTPUT PARAMETERS: ==================================================
65 C smTr :: tracer 1rst & 2nd Order moments
66 C gTracer :: tendency array
67 _RL smTr (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy,nSOM)
68 _RL gTracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
69
70 C !LOCAL VARIABLES: ====================================================
71 C maskUp :: 2-D array mask for W points
72 C i,j,k :: loop indices
73 C kUp :: index into 2 1/2D array, toggles between 1 and 2
74 C kDown :: index into 2 1/2D array, toggles between 2 and 1
75 C xA,yA :: areas of X and Y face of tracer cells
76 C uFld,vFld :: 2-D local copy of horizontal velocity, U,V components
77 C wFld :: 2-D local copy of vertical velocity
78 C uTrans,vTrans :: 2-D arrays of volume transports at U,V points
79 C rTrans :: 2-D arrays of volume transports at W points
80 C afx :: 2-D array for horizontal advective flux, x direction
81 C afy :: 2-D array for horizontal advective flux, y direction
82 C afr :: 2-D array for vertical advective flux
83 C fVerT :: 2 1/2D arrays for vertical advective flux
84 C calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
85 C calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
86 C interiorOnly :: only update the interior of myTile, but not the edges
87 C overlapOnly :: only update the edges of myTile, but not the interior
88 C npass :: number of passes in multi-dimensional method
89 C ipass :: number of the current pass being made
90 C myTile :: variables used to determine which cube face
91 C nCFace :: owns a tile for cube grid runs using
92 C :: multi-dim advection.
93 C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
94 C msgBuf :: Informational/error meesage buffer
95 _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96 INTEGER i,j,k,km1,kUp,kDown
97 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
99 _RL uFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
100 _RL vFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
101 _RL wFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
102 _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
103 _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
104 _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
105 _RL afx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
106 _RL afy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
107 _RL afr (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
108 _RL smVol (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
109 _RL smTr0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
110 _RL alp (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
111 _RL aln (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
112 _RL fp_v (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
113 _RL fn_v (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
114 _RL fp_o (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
115 _RL fn_o (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
116 _RL fp_x (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
117 _RL fn_x (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
118 _RL fp_y (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
119 _RL fn_y (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
120 _RL fp_z (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
121 _RL fn_z (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
122 _RL fp_xx (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
123 _RL fn_xx (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
124 _RL fp_yy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
125 _RL fn_yy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
126 _RL fp_zz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
127 _RL fn_zz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
128 _RL fp_xy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
129 _RL fn_xy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
130 _RL fp_xz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
131 _RL fn_xz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
132 _RL fp_yz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
133 _RL fn_yz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
134 _RL smCorners(OLx,OLy,4,-1:nSOM)
135 c _RL localTr
136 LOGICAL calc_fluxes_X, calc_fluxes_Y
137 LOGICAL interiorOnly, overlapOnly
138 INTEGER limiter
139 INTEGER npass, ipass
140 INTEGER nCFace, n
141 LOGICAL N_edge, S_edge, E_edge, W_edge
142 CHARACTER*(MAX_LEN_MBUF) msgBuf
143 #ifdef ALLOW_EXCH2
144 INTEGER myTile
145 #endif
146 #ifdef ALLOW_DIAGNOSTICS
147 CHARACTER*8 diagName
148 CHARACTER*4 diagSufx
149 LOGICAL doDiagAdvX, doDiagAdvY, doDiagAdvR
150 C- Functions:
151 CHARACTER*4 GAD_DIAG_SUFX
152 EXTERNAL GAD_DIAG_SUFX
153 LOGICAL DIAGNOSTICS_IS_ON
154 EXTERNAL DIAGNOSTICS_IS_ON
155 #endif
156 CEOP
157
158 #ifdef ALLOW_DIAGNOSTICS
159 C-- Set diagnostics flags and suffix for the current tracer
160 doDiagAdvX = .FALSE.
161 doDiagAdvY = .FALSE.
162 doDiagAdvR = .FALSE.
163 IF ( useDiagnostics ) THEN
164 diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
165 diagName = 'ADVx'//diagSufx
166 doDiagAdvX = DIAGNOSTICS_IS_ON( diagName, myThid )
167 diagName = 'ADVy'//diagSufx
168 doDiagAdvY = DIAGNOSTICS_IS_ON( diagName, myThid )
169 diagName = 'ADVr'//diagSufx
170 doDiagAdvR = DIAGNOSTICS_IS_ON( diagName, myThid )
171 ENDIF
172 #endif
173
174 C-- Set up work arrays with valid (i.e. not NaN) values
175 C These inital values do not alter the numerical results. They
176 C just ensure that all memory references are to valid floating
177 C point numbers. This prevents spurious hardware signals due to
178 C uninitialised but inert locations.
179 DO j=1-OLy,sNy+OLy
180 DO i=1-OLx,sNx+OLx
181 afx(i,j) = 0.
182 afy(i,j) = 0.
183 C- xA,yA,uFld,vFld,uTrans,vTrans are set over the full domain
184 C in CALC_COMMON_FACTORS: no need for extra initialisation
185 c xA(i,j) = 0. _d 0
186 c yA(i,j) = 0. _d 0
187 c uTrans(i,j) = 0. _d 0
188 c vTrans(i,j) = 0. _d 0
189 C- rTrans is set over the full domain: no need for extra initialisation
190 c rTrans(i,j) = 0. _d 0
191 ENDDO
192 ENDDO
193 DO n=-1,nSOM
194 DO k=1,4
195 DO j=1,OLy
196 DO i=1,OLx
197 smCorners(i,j,k,n) = 0.
198 ENDDO
199 ENDDO
200 ENDDO
201 ENDDO
202
203 IF ( implicitAdvection ) THEN
204 WRITE(msgBuf,'(2A)') 'S/R GAD_SOM_ADVECT: ',
205 & 'not coded for implicit-vertical Advection'
206 CALL PRINT_ERROR( msgBuf, myThid )
207 STOP 'ABNORMAL END: S/R GAD_SOM_ADVECT'
208 ENDIF
209 IF ( vertAdvecScheme .NE. advectionScheme ) THEN
210 WRITE(msgBuf,'(2A)') 'S/R GAD_SOM_ADVECT: ',
211 & 'not coded for different vertAdvecScheme'
212 CALL PRINT_ERROR( msgBuf, myThid )
213 STOP 'ABNORMAL END: S/R GAD_SOM_ADVECT'
214 ENDIF
215
216 C-- Set tile-specific parameters for horizontal fluxes
217 IF (useCubedSphereExchange) THEN
218 npass = 3
219 #ifdef ALLOW_EXCH2
220 myTile = W2_myTileList(bi,bj)
221 nCFace = exch2_myFace(myTile)
222 N_edge = exch2_isNedge(myTile).EQ.1
223 S_edge = exch2_isSedge(myTile).EQ.1
224 E_edge = exch2_isEedge(myTile).EQ.1
225 W_edge = exch2_isWedge(myTile).EQ.1
226 #else
227 nCFace = bi
228 N_edge = .TRUE.
229 S_edge = .TRUE.
230 E_edge = .TRUE.
231 W_edge = .TRUE.
232 #endif
233 ELSE
234 npass = 2
235 nCFace = 0
236 N_edge = .FALSE.
237 S_edge = .FALSE.
238 E_edge = .FALSE.
239 W_edge = .FALSE.
240 ENDIF
241
242 limiter = MOD(advectionScheme, 10)
243
244 C-- Start of k loop for horizontal fluxes
245 DO k=1,Nr
246
247 C-- Get temporary terms used by tendency routines
248 CALL CALC_COMMON_FACTORS (
249 I uVel, vVel,
250 O uFld, vFld, uTrans, vTrans, xA, yA,
251 I k,bi,bj, myThid )
252
253 #ifdef ALLOW_GMREDI
254 C-- Residual transp = Bolus transp + Eulerian transp
255 IF (useGMRedi)
256 & CALL GMREDI_CALC_UVFLOW(
257 U uFld, vFld, uTrans, vTrans,
258 I k, bi, bj, myThid )
259 #endif /* ALLOW_GMREDI */
260
261 C-- grid-box volume and tracer content (zero order moment)
262 DO j=1-OLy,sNy+OLy
263 DO i=1-OLx,sNx+OLx
264 smVol(i,j,k) = rA(i,j,bi,bj)*deepFac2C(k)
265 & *drF(k)*hFacC(i,j,k,bi,bj)
266 & *rhoFacC(k)
267 smTr0(i,j,k) = tracer(i,j,k,bi,bj)*smVol(i,j,k)
268 C- fill empty grid-box:
269 smVol(i,j,k) = smVol(i,j,k)
270 & + (1. _d 0 - maskC(i,j,k,bi,bj))
271 ENDDO
272 ENDDO
273
274 C-- Multiple passes for different directions on different tiles
275 C-- For cube need one pass for each of red, green and blue axes.
276 DO ipass=1,npass
277
278 interiorOnly = .FALSE.
279 overlapOnly = .FALSE.
280 IF (useCubedSphereExchange) THEN
281 C- CubedSphere : pass 3 times, with partial update of local tracer field
282 IF (ipass.EQ.1) THEN
283 overlapOnly = MOD(nCFace,3).EQ.0
284 interiorOnly = MOD(nCFace,3).NE.0
285 calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
286 calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
287 ELSEIF (ipass.EQ.2) THEN
288 overlapOnly = MOD(nCFace,3).EQ.2
289 interiorOnly = MOD(nCFace,3).EQ.1
290 calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
291 calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
292 ELSE
293 interiorOnly = .TRUE.
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
305 C-- X direction
306 C- Do not compute fluxes if
307 C a) needed in overlap only
308 C and b) the overlap of myTile are not cube-face Edges
309 IF ( calc_fluxes_X .AND.
310 & (.NOT.overlapOnly .OR. N_edge .OR. S_edge)
311 & ) THEN
312
313 C- Internal exchange for calculations in X
314 IF ( useCubedSphereExchange .AND. .NOT.interiorOnly ) THEN
315 CALL GAD_SOM_PREP_CS_CORNER(
316 U smVol, smTr0, smTr, smCorners,
317 I .TRUE., overlapOnly, interiorOnly,
318 I N_edge, S_edge, E_edge, W_edge,
319 I ipass, k, Nr, bi, bj, myThid )
320 ENDIF
321
322 C- Solve advection in X and update moments
323 IF ( advectionScheme.EQ.ENUM_SOM_PRATHER
324 & .OR. advectionScheme.EQ.ENUM_SOM_LIMITER ) THEN
325 CALL GAD_SOM_ADV_X(
326 I bi,bj,k, limiter,
327 I overlapOnly, interiorOnly,
328 I N_edge, S_edge, E_edge, W_edge,
329 I deltaTLev(k), uTrans,
330 I maskInC(1-OLx,1-OLy,bi,bj),
331 U smVol(1-OLx,1-OLy,k),
332 U smTr0(1-OLx,1-OLy,k),
333 U smTr(1-OLx,1-OLy,k,bi,bj,1),
334 U smTr(1-OLx,1-OLy,k,bi,bj,2),
335 U smTr(1-OLx,1-OLy,k,bi,bj,3),
336 U smTr(1-OLx,1-OLy,k,bi,bj,4),
337 U smTr(1-OLx,1-OLy,k,bi,bj,5),
338 U smTr(1-OLx,1-OLy,k,bi,bj,6),
339 U smTr(1-OLx,1-OLy,k,bi,bj,7),
340 U smTr(1-OLx,1-OLy,k,bi,bj,8),
341 U smTr(1-OLx,1-OLy,k,bi,bj,9),
342 O afx, myThid )
343 ELSE
344 STOP 'GAD_SOM_ADVECT: adv. scheme incompatibale with SOM'
345 ENDIF
346
347 C-- End of X direction
348 ENDIF
349
350 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
351
352 C-- Y direction
353 C- Do not compute fluxes if
354 C a) needed in overlap only
355 C and b) the overlap of myTile are not cube-face edges
356 IF ( calc_fluxes_Y .AND.
357 & (.NOT.overlapOnly .OR. E_edge .OR. W_edge)
358 & ) THEN
359
360 C- Internal exchange for calculations in Y
361 IF ( useCubedSphereExchange .AND. .NOT.interiorOnly ) THEN
362 CALL GAD_SOM_PREP_CS_CORNER(
363 U smVol, smTr0, smTr, smCorners,
364 I .FALSE., overlapOnly, interiorOnly,
365 I N_edge, S_edge, E_edge, W_edge,
366 I iPass, k, Nr, bi, bj, myThid )
367 ENDIF
368
369 C- Solve advection in Y and update moments
370 IF ( advectionScheme.EQ.ENUM_SOM_PRATHER
371 & .OR. advectionScheme.EQ.ENUM_SOM_LIMITER ) THEN
372 CALL GAD_SOM_ADV_Y(
373 I bi,bj,k, limiter,
374 I overlapOnly, interiorOnly,
375 I N_edge, S_edge, E_edge, W_edge,
376 I deltaTLev(k), vTrans,
377 I maskInC(1-OLx,1-OLy,bi,bj),
378 U smVol(1-OLx,1-OLy,k),
379 U smTr0(1-OLx,1-OLy,k),
380 U smTr(1-OLx,1-OLy,k,bi,bj,1),
381 U smTr(1-OLx,1-OLy,k,bi,bj,2),
382 U smTr(1-OLx,1-OLy,k,bi,bj,3),
383 U smTr(1-OLx,1-OLy,k,bi,bj,4),
384 U smTr(1-OLx,1-OLy,k,bi,bj,5),
385 U smTr(1-OLx,1-OLy,k,bi,bj,6),
386 U smTr(1-OLx,1-OLy,k,bi,bj,7),
387 U smTr(1-OLx,1-OLy,k,bi,bj,8),
388 U smTr(1-OLx,1-OLy,k,bi,bj,9),
389 O afy, myThid )
390 ELSE
391 STOP 'GAD_SOM_ADVECT: adv. scheme incompatibale with SOM'
392 ENDIF
393
394 C-- End of Y direction
395 ENDIF
396
397 C-- End of ipass loop
398 ENDDO
399
400 IF ( implicitAdvection ) THEN
401 C- explicit advection is done ; store tendency in gTracer:
402 DO j=1-OLy,sNy+OLy
403 DO i=1-OLx,sNx+OLx
404 C-- without rescaling of tendencies:
405 c localTr = smTr0(i,j,k)/smVol(i,j,k)
406 c gTracer(i,j,k,bi,bj) = ( localTr - tracer(i,j,k,bi,bj) )
407 c & / deltaTLev(k)
408 C-- consistent with rescaling of tendencies (in FREESURF_RESCALE_G):
409 gTracer(i,j,k,bi,bj) =
410 & ( smTr0(i,j,k) - tracer(i,j,k,bi,bj)*smVol(i,j,k) )
411 & *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
412 & *recip_drF(k)*_recip_hFacC(i,j,k,bi,bj)
413 & *recip_rhoFacC(k)
414 & /deltaTLev(k)
415 ENDDO
416 ENDDO
417 ENDIF
418
419 #ifdef ALLOW_DIAGNOSTICS
420 IF ( doDiagAdvX ) THEN
421 diagName = 'ADVx'//diagSufx
422 CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid )
423 ENDIF
424 IF ( doDiagAdvY ) THEN
425 diagName = 'ADVy'//diagSufx
426 CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid )
427 ENDIF
428 #endif
429
430 #ifdef ALLOW_DEBUG
431 IF ( debugLevel .GE. debLevC
432 & .AND. tracerIdentity.EQ.GAD_TEMPERATURE
433 & .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
434 & .AND. nPx.EQ.1 .AND. nPy.EQ.1
435 & .AND. useCubedSphereExchange ) THEN
436 CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_SOM_ADVECT',
437 & afx,afy, k, standardMessageUnit,bi,bj,myThid )
438 ENDIF
439 #endif /* ALLOW_DEBUG */
440
441 C-- End of K loop for horizontal fluxes
442 ENDDO
443
444 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
445
446 IF ( .NOT.implicitAdvection ) THEN
447 C-- Apply limiter (if any):
448 CALL GAD_SOM_LIM_R( bi,bj, limiter,
449 U smVol,
450 U smTr0,
451 U smTr(1-OLx,1-OLy,1,bi,bj,1),
452 U smTr(1-OLx,1-OLy,1,bi,bj,2),
453 U smTr(1-OLx,1-OLy,1,bi,bj,3),
454 U smTr(1-OLx,1-OLy,1,bi,bj,4),
455 U smTr(1-OLx,1-OLy,1,bi,bj,5),
456 U smTr(1-OLx,1-OLy,1,bi,bj,6),
457 U smTr(1-OLx,1-OLy,1,bi,bj,7),
458 U smTr(1-OLx,1-OLy,1,bi,bj,8),
459 U smTr(1-OLx,1-OLy,1,bi,bj,9),
460 I myThid )
461
462 C-- Start of k loop for vertical flux
463 DO k=Nr,1,-1
464 C-- kUp Cycles through 1,2 to point to w-layer above
465 C-- kDown Cycles through 2,1 to point to w-layer below
466 kUp = 1+MOD(Nr-k,2)
467 kDown= 1+MOD(Nr-k+1,2)
468 IF (k.EQ.Nr) THEN
469 C-- Set advective fluxes at the very bottom:
470 DO j=1-OLy,sNy+OLy
471 DO i=1-OLx,sNx+OLx
472 alp (i,j,kDown) = 0. _d 0
473 aln (i,j,kDown) = 0. _d 0
474 fp_v (i,j,kDown) = 0. _d 0
475 fn_v (i,j,kDown) = 0. _d 0
476 fp_o (i,j,kDown) = 0. _d 0
477 fn_o (i,j,kDown) = 0. _d 0
478 fp_x (i,j,kDown) = 0. _d 0
479 fn_x (i,j,kDown) = 0. _d 0
480 fp_y (i,j,kDown) = 0. _d 0
481 fn_y (i,j,kDown) = 0. _d 0
482 fp_z (i,j,kDown) = 0. _d 0
483 fn_z (i,j,kDown) = 0. _d 0
484 fp_xx(i,j,kDown) = 0. _d 0
485 fn_xx(i,j,kDown) = 0. _d 0
486 fp_yy(i,j,kDown) = 0. _d 0
487 fn_yy(i,j,kDown) = 0. _d 0
488 fp_zz(i,j,kDown) = 0. _d 0
489 fn_zz(i,j,kDown) = 0. _d 0
490 fp_xy(i,j,kDown) = 0. _d 0
491 fn_xy(i,j,kDown) = 0. _d 0
492 fp_xz(i,j,kDown) = 0. _d 0
493 fn_xz(i,j,kDown) = 0. _d 0
494 fp_yz(i,j,kDown) = 0. _d 0
495 fn_yz(i,j,kDown) = 0. _d 0
496 ENDDO
497 ENDDO
498 ENDIF
499
500 C-- Compute Vertical transport
501 #ifdef ALLOW_AIM
502 C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
503 c IF ( k.EQ.1 .OR.
504 c & (useAIM .AND. tracerIdentity.EQ.GAD_SALINITY .AND. k.EQ.Nr)
505 c & ) THEN
506 #else
507 c IF ( k.EQ.1 ) THEN
508 #endif
509 IF ( (rigidLid.OR.nonlinFreeSurf.GE.1) .AND. k.EQ.1 ) THEN
510 C- Surface interface :
511 DO j=1-OLy,sNy+OLy
512 DO i=1-OLx,sNx+OLx
513 wFld(i,j) = 0.
514 rTrans(i,j) = 0.
515 maskUp(i,j) = 0.
516 ENDDO
517 ENDDO
518
519 ELSEIF ( rigidLid.OR.nonlinFreeSurf.GE.1 ) THEN
520 C- Interior interface :
521 DO j=1-OLy,sNy+OLy
522 DO i=1-OLx,sNx+OLx
523 wFld(i,j) = wVel(i,j,k,bi,bj)
524 rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
525 & *deepFac2F(k)*rhoFacF(k)
526 & *maskC(i,j,k-1,bi,bj)
527 maskUp(i,j) = 1.
528 ENDDO
529 ENDDO
530
531 ELSE
532 C- Linear Free-Surface: do not mask rTrans :
533 km1= MAX(k-1,1)
534 DO j=1-OLy,sNy+OLy
535 DO i=1-OLx,sNx+OLx
536 wFld(i,j) = wVel(i,j,k,bi,bj)
537 rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
538 & *deepFac2F(k)*rhoFacF(k)
539 maskUp(i,j) = maskC(i,j,km1,bi,bj)*maskC(i,j,k,bi,bj)
540 ENDDO
541 ENDDO
542
543 C- end Surface/Interior if bloc
544 ENDIF
545
546 #ifdef ALLOW_GMREDI
547 C-- Residual transp = Bolus transp + Eulerian transp
548 IF (useGMRedi .AND. k.GT.1 )
549 & CALL GMREDI_CALC_WFLOW(
550 U wFld, rTrans,
551 I k, bi, bj, myThid )
552 #endif /* ALLOW_GMREDI */
553
554 C- Compute vertical advective flux in the interior:
555 IF ( vertAdvecScheme.EQ.ENUM_SOM_PRATHER
556 & .OR. vertAdvecScheme.EQ.ENUM_SOM_LIMITER ) THEN
557 CALL GAD_SOM_ADV_R(
558 I bi,bj,k, kUp, kDown,
559 I deltaTLev(k), rTrans, maskUp,
560 I maskInC(1-OLx,1-OLy,bi,bj),
561 U smVol,
562 U smTr0,
563 U smTr(1-OLx,1-OLy,1,bi,bj,1),
564 U smTr(1-OLx,1-OLy,1,bi,bj,2),
565 U smTr(1-OLx,1-OLy,1,bi,bj,3),
566 U smTr(1-OLx,1-OLy,1,bi,bj,4),
567 U smTr(1-OLx,1-OLy,1,bi,bj,5),
568 U smTr(1-OLx,1-OLy,1,bi,bj,6),
569 U smTr(1-OLx,1-OLy,1,bi,bj,7),
570 U smTr(1-OLx,1-OLy,1,bi,bj,8),
571 U smTr(1-OLx,1-OLy,1,bi,bj,9),
572 U alp, aln, fp_v, fn_v, fp_o, fn_o,
573 U fp_x, fn_x, fp_y, fn_y, fp_z, fn_z,
574 U fp_xx, fn_xx, fp_yy, fn_yy, fp_zz, fn_zz,
575 U fp_xy, fn_xy, fp_xz, fn_xz, fp_yz, fn_yz,
576 O afr, myThid )
577 ELSE
578 STOP 'GAD_SOM_ADVECT: adv. scheme incompatibale with SOM'
579 ENDIF
580
581 C-- Compute new tracer value and store tracer tendency
582 DO j=1-OLy,sNy+OLy
583 DO i=1-OLx,sNx+OLx
584 C-- without rescaling of tendencies:
585 c localTr = smTr0(i,j,k)/smVol(i,j,k)
586 c gTracer(i,j,k,bi,bj) = ( localTr - tracer(i,j,k,bi,bj) )
587 c & / deltaTLev(k)
588 C-- consistent with rescaling of tendencies (in FREESURF_RESCALE_G):
589 gTracer(i,j,k,bi,bj) =
590 & ( smTr0(i,j,k) - tracer(i,j,k,bi,bj)*smVol(i,j,k) )
591 & *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
592 & *recip_drF(k)*_recip_hFacC(i,j,k,bi,bj)
593 & *recip_rhoFacC(k)
594 & /deltaTLev(k)
595 ENDDO
596 ENDDO
597
598 #ifdef ALLOW_DIAGNOSTICS
599 IF ( doDiagAdvR ) THEN
600 diagName = 'ADVr'//diagSufx
601 CALL DIAGNOSTICS_FILL( afr,
602 & diagName, k,1, 2,bi,bj, myThid )
603 ENDIF
604 #endif
605
606 C-- End of k loop for vertical flux
607 ENDDO
608 C-- end of if not.implicitAdvection block
609 ENDIF
610
611 RETURN
612 END

  ViewVC Help
Powered by ViewVC 1.1.22