/[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.11 - (show annotations) (download)
Sat Mar 2 00:32:30 2013 UTC (11 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64q, checkpoint64p, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64e, checkpoint64g, checkpoint64f
Changes since 1.10: +14 -5 lines
- fix for linear Free-Surf in r*
- add more documentation (to help me remember)

1 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_som_advect.F,v 1.10 2012/03/05 17:59:15 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 message 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 LOGICAL noFlowAcrossSurf
143 CHARACTER*(MAX_LEN_MBUF) msgBuf
144 #ifdef ALLOW_EXCH2
145 INTEGER myTile
146 #endif
147 #ifdef ALLOW_DIAGNOSTICS
148 CHARACTER*8 diagName
149 CHARACTER*4 diagSufx
150 LOGICAL doDiagAdvX, doDiagAdvY, doDiagAdvR
151 C- Functions:
152 CHARACTER*4 GAD_DIAG_SUFX
153 EXTERNAL GAD_DIAG_SUFX
154 LOGICAL DIAGNOSTICS_IS_ON
155 EXTERNAL DIAGNOSTICS_IS_ON
156 #endif
157 CEOP
158
159 #ifdef ALLOW_DIAGNOSTICS
160 C-- Set diagnostics flags and suffix for the current tracer
161 doDiagAdvX = .FALSE.
162 doDiagAdvY = .FALSE.
163 doDiagAdvR = .FALSE.
164 IF ( useDiagnostics ) THEN
165 diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
166 diagName = 'ADVx'//diagSufx
167 doDiagAdvX = DIAGNOSTICS_IS_ON( diagName, myThid )
168 diagName = 'ADVy'//diagSufx
169 doDiagAdvY = DIAGNOSTICS_IS_ON( diagName, myThid )
170 diagName = 'ADVr'//diagSufx
171 doDiagAdvR = DIAGNOSTICS_IS_ON( diagName, myThid )
172 ENDIF
173 #endif
174
175 C-- Set up work arrays with valid (i.e. not NaN) values
176 C These inital values do not alter the numerical results. They
177 C just ensure that all memory references are to valid floating
178 C point numbers. This prevents spurious hardware signals due to
179 C uninitialised but inert locations.
180 DO j=1-OLy,sNy+OLy
181 DO i=1-OLx,sNx+OLx
182 afx(i,j) = 0.
183 afy(i,j) = 0.
184 C- xA,yA,uFld,vFld,uTrans,vTrans are set over the full domain
185 C in CALC_COMMON_FACTORS: no need for extra initialisation
186 c xA(i,j) = 0. _d 0
187 c yA(i,j) = 0. _d 0
188 c uTrans(i,j) = 0. _d 0
189 c vTrans(i,j) = 0. _d 0
190 C- rTrans is set over the full domain: no need for extra initialisation
191 c rTrans(i,j) = 0. _d 0
192 ENDDO
193 ENDDO
194 DO n=-1,nSOM
195 DO k=1,4
196 DO j=1,OLy
197 DO i=1,OLx
198 smCorners(i,j,k,n) = 0.
199 ENDDO
200 ENDDO
201 ENDDO
202 ENDDO
203
204 IF ( implicitAdvection ) THEN
205 WRITE(msgBuf,'(2A)') 'S/R GAD_SOM_ADVECT: ',
206 & 'not coded for implicit-vertical Advection'
207 CALL PRINT_ERROR( msgBuf, myThid )
208 STOP 'ABNORMAL END: S/R GAD_SOM_ADVECT'
209 ENDIF
210 IF ( vertAdvecScheme .NE. advectionScheme ) THEN
211 WRITE(msgBuf,'(2A)') 'S/R GAD_SOM_ADVECT: ',
212 & 'not coded for different vertAdvecScheme'
213 CALL PRINT_ERROR( msgBuf, myThid )
214 STOP 'ABNORMAL END: S/R GAD_SOM_ADVECT'
215 ENDIF
216
217 C-- Set tile-specific parameters for horizontal fluxes
218 IF (useCubedSphereExchange) THEN
219 npass = 3
220 #ifdef ALLOW_EXCH2
221 myTile = W2_myTileList(bi,bj)
222 nCFace = exch2_myFace(myTile)
223 N_edge = exch2_isNedge(myTile).EQ.1
224 S_edge = exch2_isSedge(myTile).EQ.1
225 E_edge = exch2_isEedge(myTile).EQ.1
226 W_edge = exch2_isWedge(myTile).EQ.1
227 #else
228 nCFace = bi
229 N_edge = .TRUE.
230 S_edge = .TRUE.
231 E_edge = .TRUE.
232 W_edge = .TRUE.
233 #endif
234 ELSE
235 npass = 2
236 nCFace = 0
237 N_edge = .FALSE.
238 S_edge = .FALSE.
239 E_edge = .FALSE.
240 W_edge = .FALSE.
241 ENDIF
242
243 limiter = MOD(advectionScheme, 10)
244
245 C-- Start of k loop for horizontal fluxes
246 DO k=1,Nr
247
248 C-- Get temporary terms used by tendency routines
249 CALL CALC_COMMON_FACTORS (
250 I uVel, vVel,
251 O uFld, vFld, uTrans, vTrans, xA, yA,
252 I k,bi,bj, myThid )
253
254 #ifdef ALLOW_GMREDI
255 C-- Residual transp = Bolus transp + Eulerian transp
256 IF (useGMRedi)
257 & CALL GMREDI_CALC_UVFLOW(
258 U uFld, vFld, uTrans, vTrans,
259 I k, bi, bj, myThid )
260 #endif /* ALLOW_GMREDI */
261
262 C-- grid-box volume and tracer content (zero order moment)
263 DO j=1-OLy,sNy+OLy
264 DO i=1-OLx,sNx+OLx
265 smVol(i,j,k) = rA(i,j,bi,bj)*deepFac2C(k)
266 & *drF(k)*hFacC(i,j,k,bi,bj)
267 & *rhoFacC(k)
268 smTr0(i,j,k) = tracer(i,j,k,bi,bj)*smVol(i,j,k)
269 C- fill empty grid-box:
270 smVol(i,j,k) = smVol(i,j,k)
271 & + (1. _d 0 - maskC(i,j,k,bi,bj))
272 ENDDO
273 ENDDO
274
275 C-- Multiple passes for different directions on different tiles
276 C-- For cube need one pass for each of red, green and blue axes.
277 DO ipass=1,npass
278
279 interiorOnly = .FALSE.
280 overlapOnly = .FALSE.
281 IF (useCubedSphereExchange) THEN
282 C- CubedSphere : pass 3 times, with partial update of local tracer field
283 IF (ipass.EQ.1) THEN
284 overlapOnly = MOD(nCFace,3).EQ.0
285 interiorOnly = MOD(nCFace,3).NE.0
286 calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
287 calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
288 ELSEIF (ipass.EQ.2) THEN
289 overlapOnly = MOD(nCFace,3).EQ.2
290 interiorOnly = MOD(nCFace,3).EQ.1
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 interiorOnly = .TRUE.
295 calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
296 calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
297 ENDIF
298 ELSE
299 C- not CubedSphere
300 calc_fluxes_X = MOD(ipass,2).EQ.1
301 calc_fluxes_Y = .NOT.calc_fluxes_X
302 ENDIF
303
304 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
305
306 C-- X direction
307 C- Do not compute fluxes if
308 C a) needed in overlap only
309 C and b) the overlap of myTile are not cube-face Edges
310 IF ( calc_fluxes_X .AND.
311 & (.NOT.overlapOnly .OR. N_edge .OR. S_edge)
312 & ) THEN
313
314 C- Internal exchange for calculations in X
315 IF ( useCubedSphereExchange .AND. .NOT.interiorOnly ) THEN
316 CALL GAD_SOM_PREP_CS_CORNER(
317 U smVol, smTr0, smTr, smCorners,
318 I .TRUE., overlapOnly, interiorOnly,
319 I N_edge, S_edge, E_edge, W_edge,
320 I ipass, k, Nr, bi, bj, myThid )
321 ENDIF
322
323 C- Solve advection in X and update moments
324 IF ( advectionScheme.EQ.ENUM_SOM_PRATHER
325 & .OR. advectionScheme.EQ.ENUM_SOM_LIMITER ) THEN
326 CALL GAD_SOM_ADV_X(
327 I bi,bj,k, limiter,
328 I overlapOnly, interiorOnly,
329 I N_edge, S_edge, E_edge, W_edge,
330 I deltaTLev(k), uTrans,
331 I maskInC(1-OLx,1-OLy,bi,bj),
332 U smVol(1-OLx,1-OLy,k),
333 U smTr0(1-OLx,1-OLy,k),
334 U smTr(1-OLx,1-OLy,k,bi,bj,1),
335 U smTr(1-OLx,1-OLy,k,bi,bj,2),
336 U smTr(1-OLx,1-OLy,k,bi,bj,3),
337 U smTr(1-OLx,1-OLy,k,bi,bj,4),
338 U smTr(1-OLx,1-OLy,k,bi,bj,5),
339 U smTr(1-OLx,1-OLy,k,bi,bj,6),
340 U smTr(1-OLx,1-OLy,k,bi,bj,7),
341 U smTr(1-OLx,1-OLy,k,bi,bj,8),
342 U smTr(1-OLx,1-OLy,k,bi,bj,9),
343 O afx, myThid )
344 ELSE
345 STOP 'GAD_SOM_ADVECT: adv. scheme incompatibale with SOM'
346 ENDIF
347
348 C-- End of X direction
349 ENDIF
350
351 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
352
353 C-- Y direction
354 C- Do not compute fluxes if
355 C a) needed in overlap only
356 C and b) the overlap of myTile are not cube-face edges
357 IF ( calc_fluxes_Y .AND.
358 & (.NOT.overlapOnly .OR. E_edge .OR. W_edge)
359 & ) THEN
360
361 C- Internal exchange for calculations in Y
362 IF ( useCubedSphereExchange .AND. .NOT.interiorOnly ) THEN
363 CALL GAD_SOM_PREP_CS_CORNER(
364 U smVol, smTr0, smTr, smCorners,
365 I .FALSE., overlapOnly, interiorOnly,
366 I N_edge, S_edge, E_edge, W_edge,
367 I iPass, k, Nr, bi, bj, myThid )
368 ENDIF
369
370 C- Solve advection in Y and update moments
371 IF ( advectionScheme.EQ.ENUM_SOM_PRATHER
372 & .OR. advectionScheme.EQ.ENUM_SOM_LIMITER ) THEN
373 CALL GAD_SOM_ADV_Y(
374 I bi,bj,k, limiter,
375 I overlapOnly, interiorOnly,
376 I N_edge, S_edge, E_edge, W_edge,
377 I deltaTLev(k), vTrans,
378 I maskInC(1-OLx,1-OLy,bi,bj),
379 U smVol(1-OLx,1-OLy,k),
380 U smTr0(1-OLx,1-OLy,k),
381 U smTr(1-OLx,1-OLy,k,bi,bj,1),
382 U smTr(1-OLx,1-OLy,k,bi,bj,2),
383 U smTr(1-OLx,1-OLy,k,bi,bj,3),
384 U smTr(1-OLx,1-OLy,k,bi,bj,4),
385 U smTr(1-OLx,1-OLy,k,bi,bj,5),
386 U smTr(1-OLx,1-OLy,k,bi,bj,6),
387 U smTr(1-OLx,1-OLy,k,bi,bj,7),
388 U smTr(1-OLx,1-OLy,k,bi,bj,8),
389 U smTr(1-OLx,1-OLy,k,bi,bj,9),
390 O afy, myThid )
391 ELSE
392 STOP 'GAD_SOM_ADVECT: adv. scheme incompatibale with SOM'
393 ENDIF
394
395 C-- End of Y direction
396 ENDIF
397
398 C-- End of ipass loop
399 ENDDO
400
401 IF ( implicitAdvection ) THEN
402 C- explicit advection is done ; store tendency in gTracer:
403 DO j=1-OLy,sNy+OLy
404 DO i=1-OLx,sNx+OLx
405 C-- without rescaling of tendencies:
406 c localTr = smTr0(i,j,k)/smVol(i,j,k)
407 c gTracer(i,j,k,bi,bj) = ( localTr - tracer(i,j,k,bi,bj) )
408 c & / deltaTLev(k)
409 C-- consistent with rescaling of tendencies (in FREESURF_RESCALE_G):
410 gTracer(i,j,k,bi,bj) =
411 & ( smTr0(i,j,k) - tracer(i,j,k,bi,bj)*smVol(i,j,k) )
412 & *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
413 & *recip_drF(k)*_recip_hFacC(i,j,k,bi,bj)
414 & *recip_rhoFacC(k)
415 & /deltaTLev(k)
416 ENDDO
417 ENDDO
418 ENDIF
419
420 #ifdef ALLOW_DIAGNOSTICS
421 IF ( doDiagAdvX ) THEN
422 diagName = 'ADVx'//diagSufx
423 CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid )
424 ENDIF
425 IF ( doDiagAdvY ) THEN
426 diagName = 'ADVy'//diagSufx
427 CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid )
428 ENDIF
429 #endif
430
431 #ifdef ALLOW_DEBUG
432 IF ( debugLevel .GE. debLevC
433 & .AND. tracerIdentity.EQ.GAD_TEMPERATURE
434 & .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
435 & .AND. nPx.EQ.1 .AND. nPy.EQ.1
436 & .AND. useCubedSphereExchange ) THEN
437 CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_SOM_ADVECT',
438 & afx,afy, k, standardMessageUnit,bi,bj,myThid )
439 ENDIF
440 #endif /* ALLOW_DEBUG */
441
442 C-- End of K loop for horizontal fluxes
443 ENDDO
444
445 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
446
447 noFlowAcrossSurf = rigidLid .OR. nonlinFreeSurf.GE.1
448 & .OR. select_rStar.NE.0
449
450 IF ( .NOT.implicitAdvection ) THEN
451 C-- Apply limiter (if any):
452 CALL GAD_SOM_LIM_R( bi,bj, limiter,
453 U smVol,
454 U smTr0,
455 U smTr(1-OLx,1-OLy,1,bi,bj,1),
456 U smTr(1-OLx,1-OLy,1,bi,bj,2),
457 U smTr(1-OLx,1-OLy,1,bi,bj,3),
458 U smTr(1-OLx,1-OLy,1,bi,bj,4),
459 U smTr(1-OLx,1-OLy,1,bi,bj,5),
460 U smTr(1-OLx,1-OLy,1,bi,bj,6),
461 U smTr(1-OLx,1-OLy,1,bi,bj,7),
462 U smTr(1-OLx,1-OLy,1,bi,bj,8),
463 U smTr(1-OLx,1-OLy,1,bi,bj,9),
464 I myThid )
465
466 C-- Start of k loop for vertical flux
467 DO k=Nr,1,-1
468 C-- kUp Cycles through 1,2 to point to w-layer above
469 C-- kDown Cycles through 2,1 to point to w-layer below
470 kUp = 1+MOD(Nr-k,2)
471 kDown= 1+MOD(Nr-k+1,2)
472 IF (k.EQ.Nr) THEN
473 C-- Set advective fluxes at the very bottom:
474 DO j=1-OLy,sNy+OLy
475 DO i=1-OLx,sNx+OLx
476 alp (i,j,kDown) = 0. _d 0
477 aln (i,j,kDown) = 0. _d 0
478 fp_v (i,j,kDown) = 0. _d 0
479 fn_v (i,j,kDown) = 0. _d 0
480 fp_o (i,j,kDown) = 0. _d 0
481 fn_o (i,j,kDown) = 0. _d 0
482 fp_x (i,j,kDown) = 0. _d 0
483 fn_x (i,j,kDown) = 0. _d 0
484 fp_y (i,j,kDown) = 0. _d 0
485 fn_y (i,j,kDown) = 0. _d 0
486 fp_z (i,j,kDown) = 0. _d 0
487 fn_z (i,j,kDown) = 0. _d 0
488 fp_xx(i,j,kDown) = 0. _d 0
489 fn_xx(i,j,kDown) = 0. _d 0
490 fp_yy(i,j,kDown) = 0. _d 0
491 fn_yy(i,j,kDown) = 0. _d 0
492 fp_zz(i,j,kDown) = 0. _d 0
493 fn_zz(i,j,kDown) = 0. _d 0
494 fp_xy(i,j,kDown) = 0. _d 0
495 fn_xy(i,j,kDown) = 0. _d 0
496 fp_xz(i,j,kDown) = 0. _d 0
497 fn_xz(i,j,kDown) = 0. _d 0
498 fp_yz(i,j,kDown) = 0. _d 0
499 fn_yz(i,j,kDown) = 0. _d 0
500 ENDDO
501 ENDDO
502 ENDIF
503
504 C-- Compute Vertical transport
505 #ifdef ALLOW_AIM
506 C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
507 c IF ( k.EQ.1 .OR.
508 c & (useAIM .AND. tracerIdentity.EQ.GAD_SALINITY .AND. k.EQ.Nr)
509 c & ) THEN
510 #else
511 c IF ( k.EQ.1 ) THEN
512 #endif
513 IF ( noFlowAcrossSurf .AND. k.EQ.1 ) THEN
514 C- Surface interface :
515 DO j=1-OLy,sNy+OLy
516 DO i=1-OLx,sNx+OLx
517 wFld(i,j) = 0.
518 rTrans(i,j) = 0.
519 maskUp(i,j) = 0.
520 ENDDO
521 ENDDO
522
523 ELSEIF ( noFlowAcrossSurf ) THEN
524 C- Interior interface :
525 DO j=1-OLy,sNy+OLy
526 DO i=1-OLx,sNx+OLx
527 wFld(i,j) = wVel(i,j,k,bi,bj)
528 rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
529 & *deepFac2F(k)*rhoFacF(k)
530 & *maskC(i,j,k-1,bi,bj)
531 maskUp(i,j) = 1.
532 ENDDO
533 ENDDO
534
535 ELSE
536 C- Linear Free-Surface: do not mask rTrans :
537 km1= MAX(k-1,1)
538 DO j=1-OLy,sNy+OLy
539 DO i=1-OLx,sNx+OLx
540 wFld(i,j) = wVel(i,j,k,bi,bj)
541 rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
542 & *deepFac2F(k)*rhoFacF(k)
543 maskUp(i,j) = maskC(i,j,km1,bi,bj)*maskC(i,j,k,bi,bj)
544 ENDDO
545 ENDDO
546
547 C- end Surface/Interior if bloc
548 ENDIF
549
550 #ifdef ALLOW_GMREDI
551 C-- Residual transp = Bolus transp + Eulerian transp
552 IF (useGMRedi .AND. k.GT.1 )
553 & CALL GMREDI_CALC_WFLOW(
554 U wFld, rTrans,
555 I k, bi, bj, myThid )
556 #endif /* ALLOW_GMREDI */
557
558 C- Compute vertical advective flux in the interior:
559 IF ( vertAdvecScheme.EQ.ENUM_SOM_PRATHER
560 & .OR. vertAdvecScheme.EQ.ENUM_SOM_LIMITER ) THEN
561 CALL GAD_SOM_ADV_R(
562 I bi,bj,k, kUp, kDown,
563 I deltaTLev(k), rTrans, maskUp,
564 I maskInC(1-OLx,1-OLy,bi,bj),
565 U smVol,
566 U smTr0,
567 U smTr(1-OLx,1-OLy,1,bi,bj,1),
568 U smTr(1-OLx,1-OLy,1,bi,bj,2),
569 U smTr(1-OLx,1-OLy,1,bi,bj,3),
570 U smTr(1-OLx,1-OLy,1,bi,bj,4),
571 U smTr(1-OLx,1-OLy,1,bi,bj,5),
572 U smTr(1-OLx,1-OLy,1,bi,bj,6),
573 U smTr(1-OLx,1-OLy,1,bi,bj,7),
574 U smTr(1-OLx,1-OLy,1,bi,bj,8),
575 U smTr(1-OLx,1-OLy,1,bi,bj,9),
576 U alp, aln, fp_v, fn_v, fp_o, fn_o,
577 U fp_x, fn_x, fp_y, fn_y, fp_z, fn_z,
578 U fp_xx, fn_xx, fp_yy, fn_yy, fp_zz, fn_zz,
579 U fp_xy, fn_xy, fp_xz, fn_xz, fp_yz, fn_yz,
580 O afr, myThid )
581 ELSE
582 STOP 'GAD_SOM_ADVECT: adv. scheme incompatibale with SOM'
583 ENDIF
584
585 C-- Compute new tracer value and store tracer tendency
586 DO j=1-OLy,sNy+OLy
587 DO i=1-OLx,sNx+OLx
588 C-- without rescaling of tendencies:
589 c localTr = smTr0(i,j,k)/smVol(i,j,k)
590 c gTracer(i,j,k,bi,bj) = ( localTr - tracer(i,j,k,bi,bj) )
591 c & / deltaTLev(k)
592 C-- Non-Lin Free-Surf: consistent with rescaling of tendencies
593 C (in FREESURF_RESCALE_G) and RealFreshFlux/addMass.
594 C Also valid for linear Free-Surf (r & r* coords) except that surf tracer
595 C loss/gain is computed (in GAD_SOM_ADV_R) from partially updated tracer
596 C (instead of from Tr^n as fresh-water dilution effect) resulting in
597 C inaccurate linFSConserveTr and "surfExpan_" monitor.
598 gTracer(i,j,k,bi,bj) =
599 & ( smTr0(i,j,k) - tracer(i,j,k,bi,bj)*smVol(i,j,k) )
600 & *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
601 & *recip_drF(k)*_recip_hFacC(i,j,k,bi,bj)
602 & *recip_rhoFacC(k)
603 & /deltaTLev(k)
604 ENDDO
605 ENDDO
606
607 #ifdef ALLOW_DIAGNOSTICS
608 IF ( doDiagAdvR ) THEN
609 diagName = 'ADVr'//diagSufx
610 CALL DIAGNOSTICS_FILL( afr,
611 & diagName, k,1, 2,bi,bj, myThid )
612 ENDIF
613 #endif
614
615 C-- End of k loop for vertical flux
616 ENDDO
617 C-- end of if not.implicitAdvection block
618 ENDIF
619
620 RETURN
621 END

  ViewVC Help
Powered by ViewVC 1.1.22